From gitlab at gitlab.haskell.org Sat Mar 1 01:54:19 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 28 Feb 2025 20:54:19 -0500 Subject: [Git][ghc/ghc][master] 2 commits: compiler: Add export list to GHC.SysTools.Tasks Message-ID: <67c268cb5b2b1_126b48fc60c0677d2@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 8 changed files: - compiler/GHC/Settings/IO.hs - compiler/GHC/SysTools/Tasks.hs - distrib/configure.ac.in - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - m4/fp_settings.m4 Changes: ===================================== compiler/GHC/Settings/IO.hs ===================================== @@ -168,6 +168,7 @@ initSettings top_dir = do lc_prog <- getSetting "LLVM llc command" lo_prog <- getSetting "LLVM opt command" las_prog <- getSetting "LLVM llvm-as command" + las_args <- map Option . unescapeArgs <$> getSetting "LLVM llvm-as flags" let iserv_prog = libexec "ghc-iserv" @@ -225,7 +226,7 @@ initSettings top_dir = do , toolSettings_pgm_ranlib = ranlib_path , toolSettings_pgm_lo = (lo_prog,[]) , toolSettings_pgm_lc = (lc_prog,[]) - , toolSettings_pgm_las = (las_prog, []) + , toolSettings_pgm_las = (las_prog, las_args) , toolSettings_pgm_i = iserv_prog , toolSettings_opt_L = [] , toolSettings_opt_P = [] ===================================== compiler/GHC/SysTools/Tasks.hs ===================================== @@ -7,7 +7,26 @@ -- (c) The GHC Team 2017 -- ----------------------------------------------------------------------------- -module GHC.SysTools.Tasks where +module GHC.SysTools.Tasks + ( runUnlit + , SourceCodePreprocessor(..) + , runSourceCodePreprocessor + , runPp + , runCc + , askLd + , runAs + , runLlvmOpt + , runLlvmLlc + , runLlvmAs + , runEmscripten + , figureLlvmVersion + , runMergeObjects + , runAr + , askOtool + , runInstallNameTool + , runRanlib + , runWindres + ) where import GHC.Prelude import GHC.ForeignSrcLang ===================================== distrib/configure.ac.in ===================================== @@ -214,6 +214,13 @@ FIND_LLVM_PROG([LLVMAS], [clang], [$LlvmMinVersion], [$LlvmMaxVersion]) LlvmAsCmd="$LLVMAS" AC_SUBST([LlvmAsCmd]) +dnl We know that `clang` supports `--target` and it is necessary to pass it +dnl lest we see #25793. +if test -z "$LlvmAsFlags" ; then + LlvmAsFlags="--target=$LlvmTarget" +fi +AC_SUBST([LlvmAsFlags]) + dnl ** Check gcc version and flags we need to pass it ** FP_GCC_VERSION FP_GCC_SUPPORTS_NO_PIE ===================================== hadrian/bindist/Makefile ===================================== @@ -131,6 +131,7 @@ lib/settings : config.mk @echo ',("LLVM llc command", "$(SettingsLlcCommand)")' >> $@ @echo ',("LLVM opt command", "$(SettingsOptCommand)")' >> $@ @echo ',("LLVM llvm-as command", "$(SettingsLlvmAsCommand)")' >> $@ + @echo ',("LLVM llvm-as flags", "$(SettingsLlvmAsFlags)")' >> $@ @echo ',("Use inplace MinGW toolchain", "$(SettingsUseDistroMINGW)")' >> $@ @echo @echo ',("target RTS linker only supports shared libraries", "$(TargetRTSLinkerOnlySupportsSharedLibs)")' >> $@ ===================================== hadrian/cfg/system.config.in ===================================== @@ -85,6 +85,7 @@ settings-install_name_tool-command = @SettingsInstallNameToolCommand@ settings-llc-command = @SettingsLlcCommand@ settings-opt-command = @SettingsOptCommand@ settings-llvm-as-command = @SettingsLlvmAsCommand@ +settings-llvm-as-flags = @SettingsLlvmAsFlags@ settings-use-distro-mingw = @SettingsUseDistroMINGW@ target-has-libm = @TargetHasLibm@ ===================================== hadrian/src/Oracles/Setting.hs ===================================== @@ -91,6 +91,7 @@ data ToolchainSetting | ToolchainSetting_LlcCommand | ToolchainSetting_OptCommand | ToolchainSetting_LlvmAsCommand + | ToolchainSetting_LlvmAsFlags | ToolchainSetting_DistroMinGW -- | Look up the value of a 'Setting' in @cfg/system.config@, tracking the @@ -144,6 +145,7 @@ settingsFileSetting key = lookupSystemConfig $ case key of ToolchainSetting_LlcCommand -> "settings-llc-command" ToolchainSetting_OptCommand -> "settings-opt-command" ToolchainSetting_LlvmAsCommand -> "settings-llvm-as-command" + ToolchainSetting_LlvmAsFlags -> "settings-llvm-as-flags" ToolchainSetting_DistroMinGW -> "settings-use-distro-mingw" -- ROMES:TODO: This option doesn't seem to be in ghc-toolchain yet. It corresponds to EnableDistroToolchain -- | An expression that looks up the value of a 'Setting' in @cfg/system.config@, ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -528,6 +528,7 @@ generateSettings settingsFile = do , ("LLVM llc command", expr $ settingsFileSetting ToolchainSetting_LlcCommand) , ("LLVM opt command", expr $ settingsFileSetting ToolchainSetting_OptCommand) , ("LLVM llvm-as command", expr $ settingsFileSetting ToolchainSetting_LlvmAsCommand) + , ("LLVM llvm-as flags", expr $ settingsFileSetting ToolchainSetting_LlvmAsFlags) , ("Use inplace MinGW toolchain", expr $ settingsFileSetting ToolchainSetting_DistroMinGW) , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs) ===================================== m4/fp_settings.m4 ===================================== @@ -89,6 +89,7 @@ AC_DEFUN([FP_SETTINGS], SettingsLlcCommand="$LlcCmd" SettingsOptCommand="$OptCmd" SettingsLlvmAsCommand="$LlvmAsCmd" + SettingsLlvmAsFlags="$LlvmAsCmd" if test "$EnableDistroToolchain" = "YES"; then # If the user specified --enable-distro-toolchain then we just use the @@ -131,6 +132,7 @@ AC_DEFUN([FP_SETTINGS], SUBST_TOOLDIR([SettingsLlcCommand]) SUBST_TOOLDIR([SettingsOptCommand]) SUBST_TOOLDIR([SettingsLlvmAsCommand]) + SUBST_TOOLDIR([SettingsLlvmAsFlags]) fi # Mac-only tools @@ -171,5 +173,6 @@ AC_DEFUN([FP_SETTINGS], AC_SUBST(SettingsLlcCommand) AC_SUBST(SettingsOptCommand) AC_SUBST(SettingsLlvmAsCommand) + AC_SUBST(SettingsLlvmAsFlags) AC_SUBST(SettingsUseDistroMINGW) ]) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d427df93bfcb0aef1a84a816b82ab2204dcce76a...ec826009b3a9d5f8e975ca2c8002832276043c18 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d427df93bfcb0aef1a84a816b82ab2204dcce76a...ec826009b3a9d5f8e975ca2c8002832276043c18 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250228/ff624b6f/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 1 01:54:53 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 28 Feb 2025 20:54:53 -0500 Subject: [Git][ghc/ghc][master] cmmMachOpFoldM: Add missing pattern matches for bitcasts. Message-ID: <67c268edd13ab_126b4810380e4718a7@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 1 changed file: - compiler/GHC/Cmm/Opt.hs Changes: ===================================== compiler/GHC/Cmm/Opt.hs ===================================== @@ -63,18 +63,23 @@ cmmMachOpFoldM _ (MO_VF_Broadcast lg _w) exprs = [CmmLit l] -> Just $! CmmLit (CmmVec $ replicate lg l) _ -> Nothing cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] - = Just $! case op of - MO_S_Neg _ -> CmmLit (CmmInt (narrowS rep (-x)) rep) - MO_Not _ -> CmmLit (CmmInt (complement x) rep) + = case op of + MO_S_Neg _ -> Just $! CmmLit (CmmInt (narrowS rep (-x)) rep) + MO_Not _ -> Just $! CmmLit (CmmInt (complement x) rep) -- these are interesting: we must first narrow to the -- "from" type, in order to truncate to the correct size. -- The final narrow/widen to the destination type -- is implicit in the CmmLit. - MO_SF_Round _frm to -> CmmLit (CmmFloat (fromInteger x) to) - MO_SS_Conv from to -> CmmLit (CmmInt (narrowS from x) to) - MO_UU_Conv from to -> CmmLit (CmmInt (narrowU from x) to) - MO_XX_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + MO_SF_Round _frm to -> Just $! CmmLit (CmmFloat (fromInteger x) to) + MO_SS_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) + MO_UU_Conv from to -> Just $! CmmLit (CmmInt (narrowU from x) to) + MO_XX_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) + + -- Not as simply as it seems, since CmmFloat uses Rational, so skipping those + -- for now ... + MO_WF_Bitcast _w -> Nothing + MO_FW_Bitcast _w -> Nothing _ -> panic $ "cmmMachOpFoldM: unknown unary op: " ++ show op -- Eliminate shifts that are wider than the shiftee View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c1647d1557834f277fe9d4040789c60c9ef8e3d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c1647d1557834f277fe9d4040789c60c9ef8e3d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250228/e9b9a757/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 1 08:34:46 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sat, 01 Mar 2025 03:34:46 -0500 Subject: [Git][ghc/ghc][wip/supersven/riscv-fix-switch-jump-tables] 52 commits: Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. Message-ID: <67c2c6a629e09_295a2d1a1eb3087092@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-fix-switch-jump-tables at Glasgow Haskell Compiler / GHC Commits: 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - ce12dce7 by Sven Tennie at 2025-03-01T09:33:36+01:00 RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738) J_TBL result in local jumps, there should not deallocate stack slots (see Note [extra spill slots].) J is for non-local jumps, these may need to deallocate stack slots. - - - - - 275 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - ghc/GHCi/UI.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Parser.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/linker/MachO.c - testsuite/driver/testlib.py - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod185.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/all.T - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Transform.hs - − utils/deriveConstants/Makefile - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/abcac361262d9f5ddc677645ace255b0ed704ad6...ce12dce7bbf51456feecfd8753936321e1096570 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/abcac361262d9f5ddc677645ace255b0ed704ad6...ce12dce7bbf51456feecfd8753936321e1096570 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250301/f2af2561/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 1 11:01:40 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Sat, 01 Mar 2025 06:01:40 -0500 Subject: [Git][ghc/ghc][wip/T25657] More updates Message-ID: <67c2e914993bc_397892bb22f433591@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25657 at Glasgow Haskell Compiler / GHC Commits: 14118210 by Simon Peyton Jones at 2025-03-01T11:01:12+00:00 More updates - - - - - 2 changed files: - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Utils/Panic.hs Changes: ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -1163,7 +1163,10 @@ instEnvMatchesAndUnifiers (InstEnv rm) vis_mods cls tys -- Unification will break badly if the variables overlap -- They shouldn't because we allocate separate uniques for them -- See Note [Template tyvars are fresh] - case tcUnifyTysFG dontCareBindFam instanceBindFun tpl_tys tys of + case tcUnifyTysFG alwaysBindFam instanceBindFun tpl_tys tys of + -- alwaysBindFam: the family-application can't be in the instance head, + -- but it certainly can be in the Wanted constraint we are matching! + -- -- We consider MaybeApart to be a case where the instance might -- apply in the future. This covers an instance like C Int and -- a target like [W] C (F a), where F is a type family. ===================================== compiler/GHC/Utils/Panic.hs ===================================== @@ -191,7 +191,7 @@ pprPanic :: HasCallStack => String -> SDoc -> a pprPanic s doc = panicDoc s (doc $$ callStackDoc) -- | Throw an exception saying "bug in GHC" -panicDoc :: String -> SDoc -> a +panicDoc :: HasCallStack => String -> SDoc -> a panicDoc x doc = throwGhcException (PprPanic x doc) -- | Throw an exception saying "this isn't finished yet" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/14118210a0d812b1ad8511feb7919d9dc270a0ef -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/14118210a0d812b1ad8511feb7919d9dc270a0ef You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250301/37c07631/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 1 16:18:36 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 01 Mar 2025 11:18:36 -0500 Subject: [Git][ghc/ghc][wip/strict-level] SetLevels: Track binding context Message-ID: <67c3335c26b20_109013382ed07837c@gitlab.mail> Ben Gamari pushed to branch wip/strict-level at Glasgow Haskell Compiler / GHC Commits: c1acee39 by Ben Gamari at 2025-02-28T12:39:18-05:00 SetLevels: Track binding context - - - - - 1 changed file: - compiler/GHC/Core/Opt/SetLevels.hs Changes: ===================================== compiler/GHC/Core/Opt/SetLevels.hs ===================================== @@ -1221,41 +1221,42 @@ lvlBind :: LevelEnv -> CoreBindWithFVs -> LvlM (LevelledBind, LevelEnv) -lvlBind env (AnnNonRec bndr rhs) +lvlBind env0 (AnnNonRec bndr rhs) | isTyVar bndr -- Don't float TyVar binders (simplifier gets rid of them pronto) || isCoVar bndr -- Don't float CoVars: difficult to fix up CoVar occurrences -- (see extendPolyLvlEnv) - || not (wantToFloat env NonRecursive dest_lvl is_join is_top_bindable) + || not (wantToFloat env0 NonRecursive dest_lvl is_join is_top_bindable) = -- No float - do { rhs' <- lvlRhs env NonRecursive is_bot_lam mb_join_arity rhs - ; let bind_lvl = incMinorLvl (le_ctxt_lvl env) - (env', Identity bndr') = substAndLvlBndrs NonRecursive env bind_lvl (Identity bndr) - ; return (NonRec bndr' rhs', env') } + do { rhs' <- lvlRhs env1 NonRecursive is_bot_lam mb_join_arity rhs + ; let bind_lvl = incMinorLvl (le_ctxt_lvl env1) + (env2, Identity bndr') = substAndLvlBndrs NonRecursive env1 bind_lvl (Identity bndr) + ; return (NonRec bndr' rhs', env2) } -- Otherwise we are going to float | null abs_vars = do { -- No type abstraction; clone existing binder - rhs' <- lvlFloatRhs [] dest_lvl env NonRecursive + rhs' <- lvlFloatRhs [] dest_lvl env1 NonRecursive is_bot_lam NotJoinPoint rhs - ; (env', Identity bndr') <- cloneLetVars NonRecursive env dest_lvl (Identity bndr) + ; (env2, Identity bndr') <- cloneLetVars NonRecursive env1 dest_lvl (Identity bndr) ; let bndr2 = annotateBotStr bndr' 0 mb_bot_str - ; return (NonRec (TB bndr2 (FloatMe dest_lvl)) rhs', env') } + ; return (NonRec (TB bndr2 (FloatMe dest_lvl)) rhs', env2) } | otherwise = do { -- Yes, type abstraction; create a new binder, extend substitution, etc - rhs' <- lvlFloatRhs abs_vars dest_lvl env NonRecursive + rhs' <- lvlFloatRhs abs_vars dest_lvl env1 NonRecursive is_bot_lam NotJoinPoint rhs - ; (env', Identity bndr') <- newPolyBndrs dest_lvl env abs_vars (Identity bndr) + ; (env2, Identity bndr') <- newPolyBndrs dest_lvl env1 abs_vars (Identity bndr) ; let bndr2 = annotateBotStr bndr' n_extra mb_bot_str - ; return (NonRec (TB bndr2 (FloatMe dest_lvl)) rhs', env') } + ; return (NonRec (TB bndr2 (FloatMe dest_lvl)) rhs', env2) } where + env1 = pushBindContext env0 bndr bndr_ty = idType bndr ty_fvs = tyCoVarsOfType bndr_ty rhs_fvs = freeVarsOf rhs bind_fvs = rhs_fvs `unionDVarSet` dIdFreeVars bndr - abs_vars = abstractVars dest_lvl env bind_fvs - dest_lvl = destLevel env bind_fvs ty_fvs (isFunction rhs) is_bot_lam + abs_vars = abstractVars dest_lvl env0 bind_fvs + dest_lvl = destLevel env0 bind_fvs ty_fvs (isFunction rhs) is_bot_lam deann_rhs = deAnnotate rhs mb_bot_str = exprBotStrictness_maybe deann_rhs @@ -1275,7 +1276,8 @@ lvlBind env (AnnRec pairs) = -- No float do { let bind_lvl = incMinorLvl (le_ctxt_lvl env) (env', bndrs') = substAndLvlBndrs Recursive env bind_lvl bndrs - lvl_rhs (b,r) = lvlRhs env' Recursive is_bot (idJoinPointHood b) r + lvl_rhs (b,r) = lvlRhs env'' Recursive is_bot (idJoinPointHood b) r + where env'' = pushBindContext env' b ; rhss' <- mapM lvl_rhs pairs ; return (Rec (bndrs' `zip` rhss'), env') } @@ -1300,8 +1302,9 @@ lvlBind env (AnnRec pairs) -- mutually recursive functions, but it's quite a bit more complicated -- -- This all seems a bit ad hoc -- sigh - let (rhs_env, abs_vars_w_lvls) = lvlLamBndrs env dest_lvl abs_vars + let (rhs_env, abs_vars_w_lvls) = lvlLamBndrs env' dest_lvl abs_vars rhs_lvl = le_ctxt_lvl rhs_env + env' = pushBindContext env bndr (rhs_env', Identity new_bndr) <- cloneLetVars Recursive rhs_env rhs_lvl (Identity bndr) let @@ -1309,7 +1312,7 @@ lvlBind env (AnnRec pairs) (body_env1, lam_bndrs1) = substBndrsSL NonRecursive rhs_env' lam_bndrs (body_env2, lam_bndrs2) = lvlLamBndrs body_env1 rhs_lvl lam_bndrs1 new_rhs_body <- lvlRhs body_env2 Recursive is_bot NotJoinPoint rhs_body - (poly_env, Identity poly_bndr) <- newPolyBndrs dest_lvl env abs_vars (Identity bndr) + (poly_env, Identity poly_bndr) <- newPolyBndrs dest_lvl env' abs_vars (Identity bndr) return (Rec [(TB poly_bndr (FloatMe dest_lvl) , mkLams abs_vars_w_lvls $ mkLams lam_bndrs2 $ @@ -1334,9 +1337,10 @@ lvlBind env (AnnRec pairs) -- function in a Rec, and we don't much care what -- happens to it. False is simple! - do_rhs env (_,rhs) = lvlFloatRhs abs_vars dest_lvl env Recursive - is_bot NotJoinPoint - rhs + do_rhs env (b,rhs) = + lvlFloatRhs abs_vars dest_lvl env' Recursive + is_bot NotJoinPoint rhs + where env' = pushBindContext env b -- Finding the free vars of the binding group is annoying bind_fvs = ((unionDVarSets [ freeVarsOf rhs | (_, rhs) <- pairs]) @@ -1638,16 +1642,17 @@ countFreeIds = nonDetStrictFoldUDFM add 0 . getUniqDSet -} data LevelEnv - = LE { le_switches :: FloatOutSwitches - , le_ctxt_lvl :: !Level -- The current level - , le_lvl_env :: VarEnv Level -- Domain is *post-cloned* TyVars and Ids + = LE { le_switches :: FloatOutSwitches + , le_bind_ctxt :: [Id] + , le_ctxt_lvl :: !Level -- The current level + , le_lvl_env :: VarEnv Level -- Domain is *post-cloned* TyVars and Ids -- See Note [le_subst and le_env] - , le_subst :: Subst -- Domain is pre-cloned TyVars and Ids - -- The Id -> CoreExpr in the Subst is ignored - -- (since we want to substitute a LevelledExpr for - -- an Id via le_env) but we do use the Co/TyVar substs - , le_env :: IdEnv ([OutVar], LevelledExpr) -- Domain is pre-cloned Ids + , le_subst :: Subst -- Domain is pre-cloned TyVars and Ids + -- The Id -> CoreExpr in the Subst is ignored + -- (since we want to substitute a LevelledExpr for + -- an Id via le_env) but we do use the Co/TyVar substs + , le_env :: IdEnv ([OutVar], LevelledExpr) -- Domain is pre-cloned Ids } {- Note [le_subst and le_env] @@ -1684,6 +1689,7 @@ The domain of the le_lvl_env is the *post-cloned* Ids initialEnv :: FloatOutSwitches -> CoreProgram -> LevelEnv initialEnv float_lams binds = LE { le_switches = float_lams + , le_bind_ctxt = [] , le_ctxt_lvl = tOP_LEVEL , le_lvl_env = emptyVarEnv , le_subst = mkEmptySubst in_scope_toplvl @@ -1696,6 +1702,9 @@ initialEnv float_lams binds -- to a later one. So here we put all the top-level binders in scope before -- we start, to satisfy the lookupIdSubst invariants (#20200 and #20294) +pushBindContext :: LevelEnv -> Id -> LevelEnv +pushBindContext env i = env { le_bind_ctxt = i : le_bind_ctxt env } + addLvl :: Level -> VarEnv Level -> OutVar -> VarEnv Level addLvl dest_lvl env v' = extendVarEnv env v' dest_lvl View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c1acee39b0d7527157571d5f63c9529054f3f17a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c1acee39b0d7527157571d5f63c9529054f3f17a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250301/d827a086/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 1 16:40:44 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 01 Mar 2025 11:40:44 -0500 Subject: [Git][ghc/ghc][wip/strict-level] SetLevels: Name `lvl` binders according to context Message-ID: <67c3388cc9b70_10901374692c8008e@gitlab.mail> Ben Gamari pushed to branch wip/strict-level at Glasgow Haskell Compiler / GHC Commits: 30dabb0c by Ben Gamari at 2025-03-01T11:40:36-05:00 SetLevels: Name `lvl` binders according to context See #25802 - - - - - 1 changed file: - compiler/GHC/Core/Opt/SetLevels.hs Changes: ===================================== compiler/GHC/Core/Opt/SetLevels.hs ===================================== @@ -107,7 +107,7 @@ import GHC.Types.Literal ( litIsTrivial ) import GHC.Types.Demand ( DmdSig, prependArgsDmdSig ) import GHC.Types.Cpr ( CprSig, prependArgsCprSig ) import GHC.Types.Name ( getOccName, mkSystemVarName ) -import GHC.Types.Name.Occurrence ( occNameFS ) +import GHC.Types.Name.Occurrence ( occNameFS, occNameString ) import GHC.Types.Unique ( hasKey ) import GHC.Types.Tickish ( tickishIsCode ) import GHC.Types.Unique.Supply @@ -128,6 +128,7 @@ import GHC.Utils.Panic import Data.Foldable ( toList ) import Data.Functor.Identity ( Identity (..) ) import Data.List.NonEmpty ( NonEmpty (..) ) +import Data.List ( intercalate ) import Data.Maybe {- @@ -637,7 +638,7 @@ lvlMFE env strict_ctxt ann_expr = do { expr1 <- lvlFloatRhs abs_vars dest_lvl rhs_env NonRecursive is_bot_lam NotJoinPoint ann_expr -- Treat the expr just like a right-hand side - ; var <- newLvlVar expr1 NotJoinPoint is_mk_static + ; var <- newLvlVar env expr1 NotJoinPoint is_mk_static ; let var2 = annotateBotStr var float_n_lams mb_bot_str ; return (Let (NonRec (TB var2 (FloatMe dest_lvl)) expr1) (mkVarApps (Var var2) abs_vars)) } @@ -658,7 +659,7 @@ lvlMFE env strict_ctxt ann_expr Case expr1 (stayPut l1r ubx_bndr) box_ty [Alt DEFAULT [] (App boxing_expr (Var ubx_bndr))] - ; var <- newLvlVar float_rhs NotJoinPoint is_mk_static + ; var <- newLvlVar env float_rhs NotJoinPoint is_mk_static ; let l1u = incMinorLvlFrom env use_expr = Case (mkVarApps (Var var) abs_vars) (stayPut l1u bx_bndr) expr_ty @@ -1846,11 +1847,12 @@ newPolyBndrs dest_lvl {-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> NonEmpty InId -> m (LevelEnv, NonEmpty OutId) #-} {-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> Pair InId -> m (LevelEnv, Pair OutId) #-} -newLvlVar :: LevelledExpr -- The RHS of the new binding +newLvlVar :: LevelEnv + -> LevelledExpr -- The RHS of the new binding -> JoinPointHood -- Its join arity, if it is a join point -> Bool -- True <=> the RHS looks like (makeStatic ...) -> LvlM Id -newLvlVar lvld_rhs join_arity_maybe is_mk_static +newLvlVar env lvld_rhs join_arity_maybe is_mk_static = do { uniq <- getUniqueM ; return (add_join_info (mk_id uniq rhs_ty)) } @@ -1865,7 +1867,12 @@ newLvlVar lvld_rhs join_arity_maybe is_mk_static = mkExportedVanillaId (mkSystemVarName uniq (mkFastString "static_ptr")) rhs_ty | otherwise - = mkSysLocal (mkFastString "lvl") uniq ManyTy rhs_ty + = mkSysLocal stem uniq ManyTy rhs_ty + + stem = + case le_bind_ctxt env of + [] -> mkFastString "lvl" + ctx -> mkFastString $ intercalate "_" ("lvl" : map (occNameString . getOccName) ctx) -- | Clone the binders bound by a single-alternative case. cloneCaseBndrs :: Traversable t => LevelEnv -> Level -> t Var -> LvlM (LevelEnv, t Var) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/30dabb0c7a0a79b68aeb7f315f75e9f55ef7aba2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/30dabb0c7a0a79b68aeb7f315f75e9f55ef7aba2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250301/b59ab714/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 2 10:46:35 2025 From: gitlab at gitlab.haskell.org (Luite Stegeman (@luite)) Date: Sun, 02 Mar 2025 05:46:35 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/ghc-9.6.7 Message-ID: <67c4370b7cda8_394ea5e0b9d81020d8@gitlab.mail> Luite Stegeman deleted branch wip/ghc-9.6.7 at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250302/30d22737/attachment.html> From gitlab at gitlab.haskell.org Sun Mar 2 10:46:39 2025 From: gitlab at gitlab.haskell.org (Luite Stegeman (@luite)) Date: Sun, 02 Mar 2025 05:46:39 -0500 Subject: [Git][ghc/ghc][ghc-9.6] set RELEASE=YES Message-ID: <67c4370fd14ac_394ea5e06d201022ab@gitlab.mail> Luite Stegeman pushed to branch ghc-9.6 at Glasgow Haskell Compiler / GHC Commits: 2b22b6ae by Luite Stegeman at 2025-02-27T03:44:24+01:00 set RELEASE=YES - - - - - 1 changed file: - configure.ac Changes: ===================================== configure.ac ===================================== @@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.6.7], [glasgow-has AC_CONFIG_MACRO_DIRS([m4]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=NO} +: ${RELEASE=YES} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2b22b6ae69c94e721fde8af0108eb0feed97cc82 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2b22b6ae69c94e721fde8af0108eb0feed97cc82 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250302/47ebe290/attachment.html> From gitlab at gitlab.haskell.org Sun Mar 2 13:00:28 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 02 Mar 2025 08:00:28 -0500 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] Better algorithm to inject vector config Message-ID: <67c4566ce0e3e_394ea51af108011029f@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: 44be546e by Sven Tennie at 2025-03-02T13:59:47+01:00 Better algorithm to inject vector config - - - - - 1 changed file: - compiler/GHC/CmmToAsm/RV64/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/RV64/Ppr.hs ===================================== @@ -17,6 +17,7 @@ import GHC.CmmToAsm.Utils import GHC.Platform import GHC.Platform.Reg import GHC.Prelude hiding (EQ) +import GHC.Stack import GHC.Types.Basic (Alignment, alignmentBytes, mkAlignment) import GHC.Types.Unique (getUnique, pprUniqueAlways) import GHC.Utils.Outputable @@ -142,7 +143,7 @@ pprBasicBlock :: pprBasicBlock config info_env (BasicBlock blockid instrs) = maybe_infotable $ pprLabel platform asmLbl - $$ vcat (map (pprInstr platform) (id {-detectTrivialDeadlock-} optInstrs)) + $$ vcat (map (pprInstr platform) (id {-detectTrivialDeadlock-} instrs')) $$ ppWhen (ncgDwarfEnabled config) ( -- Emit both end labels since this may end up being a standalone @@ -153,14 +154,73 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) = ) ) where + instrs' = injectVectorConfig optInstrs -- TODO: Check if we can filter more instructions here. - -- TODO: Shouldn't this be a more general check on a higher level? + -- TODO: Shouldn't this be a more general check on a higher level? And, is this still needed? -- Filter out identity moves. E.g. mov x18, x18 will be dropped. optInstrs = filter f instrs where f (MOV o1 o2) | o1 == o2 = False f _ = True + injectVectorConfig :: [Instr] -> [Instr] + injectVectorConfig instrs = fst $ foldl injectVectorConfig' ([], Nothing) instrs + + -- TODO: Fuse this with optInstrs + -- TODO: Check config and only run this when vectors are configured + -- TODO: Check if vectorMinBits is sufficient for the vector config + injectVectorConfig' :: ([Instr], Maybe Format) -> Instr -> ([Instr], Maybe Format) + injectVectorConfig' (accInstr, configuredVecFmt) currInstr = + let configuredVecFmt' Nothing = Nothing + configuredVecFmt' (Just fmt') = if isJumpishInstr currInstr then Nothing else Just fmt' + in case (configuredVecFmt, instrVecFormat platform currInstr) of + (fmtA, Nothing) -> + -- no vector instruction + ( accInstr + -- TODO: The performance of this appending is probably horrible. Check OrdList. + ++ [ (MULTILINE_COMMENT (text "No vector instruction" <> colon <+> text (instrCon currInstr) <+> pprInstr platform currInstr <> dot <> text "Current context" <> colon <+> ppr fmtA <> comma <+> text "New context" <+> ppr (configuredVecFmt' configuredVecFmt))), + currInstr + ], + configuredVecFmt' configuredVecFmt + ) + (Nothing, Just fmtB) -> + -- vector instruction, but no active config + ( accInstr + -- TODO: The performance of this appending is probably horrible. Check OrdList. + ++ [ COMMENT (text "No active vector config. Setting" <+> ppr fmtB), + (configVec fmtB), + currInstr + ], + configuredVecFmt' (Just fmtB) + ) + (Just fmtA, Just fmtB) -> + if fmtA == fmtB + then + -- vectors already correctly configured + ( accInstr + -- TODO: The performance of this appending is probably horrible. Check OrdList. + ++ [COMMENT (text "Active vector config. Keeping" <+> ppr fmtB), currInstr], + configuredVecFmt' (Just fmtA) + ) + else + -- re-configure + ( accInstr + -- TODO: The performance of this appending is probably horrible. Check OrdList. + ++ [(COMMENT (text "Wrong active vector config. Setting" <+> ppr fmtB)), (configVec fmtB), currInstr], + configuredVecFmt' (Just fmtB) + ) + + configVec :: Format -> Instr + configVec (VecFormat length fmt) = + VSETIVLI + (OpReg II64 zeroReg) + (fromIntegral length) + ((formatToWidth . scalarFormatFormat) fmt) + M1 + TA + MA + configVec fmt = pprPanic "Unsupported vector configuration" ((text . show) fmt) + asmLbl = blockLbl blockid platform = ncgPlatform config maybe_infotable c = case mapLookup blockid info_env of @@ -315,13 +375,13 @@ negOp (OpImm (ImmInt i)) = OpImm (ImmInt (negate i)) negOp (OpImm (ImmInteger i)) = OpImm (ImmInteger (negate i)) negOp op = pprPanic "RV64.negOp" (text $ show op) -pprOps :: (IsLine doc) => Platform -> [Operand] -> doc +pprOps :: (IsLine doc, HasCallStack) => Platform -> [Operand] -> doc pprOps platform = hsep . map (pprOp platform) -- | Pretty print an operand -pprOp :: (IsLine doc) => Platform -> Operand -> doc +pprOp :: (IsLine doc, HasCallStack) => Platform -> Operand -> doc pprOp plat op = case op of - OpReg w r -> pprReg w r + OpReg fmt r -> pprReg fmt r OpImm im -> pprOpImm plat im OpAddr (AddrRegImm r1 im) -> pprOpImm plat im <> char '(' <> pprReg II64 r1 <> char ')' OpAddr (AddrReg r1) -> text "0(" <+> pprReg II64 r1 <+> char ')' @@ -330,7 +390,7 @@ pprOp plat op = case op of -- -- This representation makes it easier to reason about the emitted assembly -- code. -pprReg :: forall doc. (IsLine doc) => Format -> Reg -> doc +pprReg :: forall doc. (IsLine doc, HasCallStack) => Format -> Reg -> doc pprReg fmt r = assertFmtReg fmt r $ case r of RegReal (RealRegSingle i) -> ppr_reg_no i -- virtual regs should not show up, but this is helpful for debugging. @@ -484,7 +544,7 @@ getLabel _platform _other = panic "Cannot turn this into a label" -- -- This function is partial and will panic if the `Instr` is not supported. This -- can happen due to invalid operands or unexpected meta instructions. -pprInstr :: (IsDoc doc) => Platform -> Instr -> doc +pprInstr :: (IsDoc doc, HasCallStack) => Platform -> Instr -> doc pprInstr platform instr = case instr of -- see Note [dualLine and dualDoc] in GHC.Utils.Outputable COMMENT s -> dualDoc (asmComment s) empty @@ -511,7 +571,7 @@ pprInstr platform instr = case instr of ADD o1 o2 o3 | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> op3 (text "\tfadd." <> if isSingleOp o1 then text "s" else text "d") o1 o2 o3 -- This case is used for sign extension: SEXT.W op - | OpReg II64 _ <- o1, OpReg II32 _ <- o2, isImmOp o3 -> op3 (text "\taddiw") o1 o2 o3 + | OpReg II64 _ <- o1, OpReg II32 _ <- o2, isImmOp o3 -> op3 (text "\taddiw") o1 o2 o3 | otherwise -> op3 (text "\tadd") o1 o2 o3 MUL o1 o2 o3 | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> op3 (text "\tfmul." <> if isSingleOp o1 then text "s" else text "d") o1 o2 o3 @@ -555,7 +615,6 @@ pprInstr platform instr = case instr of | isIntRegOp o1 && isFloatRegOp o2 && isSingleOp o2 -> op2 (text "\tfmv.x.w") o1 o2 | isIntRegOp o1 && isFloatRegOp o2 && isDoubleOp o2 -> op2 (text "\tfmv.x.d") o1 o2 -- TODO: Why does this NOP (reg1 == reg2) happen? - -- TODO: Vector config missing | isVectorRegOp o1 && isVectorRegOp o2 -> op2 (text "\tvmv.v.v") o1 o2 | (OpImm (ImmInteger i)) <- o2, fitsIn12bitImm i -> @@ -659,12 +718,12 @@ pprInstr platform instr = case instr of STR II64 o1 o2 -> op2 (text "\tsd") o1 o2 STR FF32 o1 o2 -> op2 (text "\tfsw") o1 o2 STR FF64 o1 o2 -> op2 (text "\tfsd") o1 o2 - STR fmt@(VecFormat _ FmtInt8) o1 o2 -> configVec fmt $$ op2 (text "\tvse8.v") o1 o2 - STR fmt@(VecFormat _ FmtInt16) o1 o2 -> configVec fmt $$ op2 (text "\tvse16.v") o1 o2 - STR fmt@(VecFormat _ FmtInt32) o1 o2 -> configVec fmt $$ op2 (text "\tvse32.v") o1 o2 - STR fmt@(VecFormat _ FmtInt64) o1 o2 -> configVec fmt $$ op2 (text "\tvse64.v") o1 o2 - STR fmt@(VecFormat _ FmtFloat) o1 o2 -> configVec fmt $$ op2 (text "\tvse32.v") o1 o2 - STR fmt@(VecFormat _ FmtDouble) o1 o2 -> configVec fmt $$ op2 (text "\tvse64.v") o1 o2 + STR (VecFormat _ FmtInt8) o1 o2 -> op2 (text "\tvse8.v") o1 o2 + STR (VecFormat _ FmtInt16) o1 o2 -> op2 (text "\tvse16.v") o1 o2 + STR (VecFormat _ FmtInt32) o1 o2 -> op2 (text "\tvse32.v") o1 o2 + STR (VecFormat _ FmtInt64) o1 o2 -> op2 (text "\tvse64.v") o1 o2 + STR (VecFormat _ FmtFloat) o1 o2 -> op2 (text "\tvse32.v") o1 o2 + STR (VecFormat _ FmtDouble) o1 o2 -> op2 (text "\tvse64.v") o1 o2 LDR _f o1 (OpImm (ImmIndex lbl off)) -> lines_ [ text "\tla" <+> pprOp platform o1 <> comma <+> pprAsmLabel platform lbl, @@ -678,12 +737,12 @@ pprInstr platform instr = case instr of LDR II64 o1 o2 -> op2 (text "\tld") o1 o2 LDR FF32 o1 o2 -> op2 (text "\tflw") o1 o2 LDR FF64 o1 o2 -> op2 (text "\tfld") o1 o2 - LDR fmt@(VecFormat _ FmtInt8) o1 o2 -> configVec fmt $$ op2 (text "\tvle8.v") o1 o2 - LDR fmt@(VecFormat _ FmtInt16) o1 o2 -> configVec fmt $$ op2 (text "\tvle16.v") o1 o2 - LDR fmt@(VecFormat _ FmtInt32) o1 o2 -> configVec fmt $$ op2 (text "\tvle32.v") o1 o2 - LDR fmt@(VecFormat _ FmtInt64) o1 o2 -> configVec fmt $$ op2 (text "\tvle64.v") o1 o2 - LDR fmt@(VecFormat _ FmtFloat) o1 o2 -> configVec fmt $$ op2 (text "\tvle32.v") o1 o2 - LDR fmt@(VecFormat _ FmtDouble) o1 o2 -> configVec fmt $$ op2 (text "\tvle64.v") o1 o2 + LDR (VecFormat _ FmtInt8) o1 o2 -> op2 (text "\tvle8.v") o1 o2 + LDR (VecFormat _ FmtInt16) o1 o2 -> op2 (text "\tvle16.v") o1 o2 + LDR (VecFormat _ FmtInt32) o1 o2 -> op2 (text "\tvle32.v") o1 o2 + LDR (VecFormat _ FmtInt64) o1 o2 -> op2 (text "\tvle64.v") o1 o2 + LDR (VecFormat _ FmtFloat) o1 o2 -> op2 (text "\tvle32.v") o1 o2 + LDR (VecFormat _ FmtDouble) o1 o2 -> op2 (text "\tvle64.v") o1 o2 LDRU II8 o1 o2 -> op2 (text "\tlbu") o1 o2 LDRU II16 o1 o2 -> op2 (text "\tlhu") o1 o2 LDRU II32 o1 o2 -> op2 (text "\tlwu") o1 o2 @@ -694,12 +753,12 @@ pprInstr platform instr = case instr of LDRU FF64 o1 o2@(OpAddr (AddrReg _)) -> op2 (text "\tfld") o1 o2 LDRU FF64 o1 o2@(OpAddr (AddrRegImm _ _)) -> op2 (text "\tfld") o1 o2 -- vectors - LDRU fmt@(VecFormat _ FmtInt8) o1 o2 -> configVec fmt $$ op2 (text "\tvle8.v") o1 o2 - LDRU fmt@(VecFormat _ FmtInt16) o1 o2 -> configVec fmt $$ op2 (text "\tvle16.v") o1 o2 - LDRU fmt@(VecFormat _ FmtInt32) o1 o2 -> configVec fmt $$ op2 (text "\tvle32.v") o1 o2 - LDRU fmt@(VecFormat _ FmtInt64) o1 o2 -> configVec fmt $$ op2 (text "\tvle64.v") o1 o2 - LDRU fmt@(VecFormat _ FmtFloat) o1 o2 -> configVec fmt $$ op2 (text "\tvle32.v") o1 o2 - LDRU fmt@(VecFormat _ FmtDouble) o1 o2 -> configVec fmt $$ op2 (text "\tvle64.v") o1 o2 + LDRU (VecFormat _ FmtInt8) o1 o2 -> op2 (text "\tvle8.v") o1 o2 + LDRU (VecFormat _ FmtInt16) o1 o2 -> op2 (text "\tvle16.v") o1 o2 + LDRU (VecFormat _ FmtInt32) o1 o2 -> op2 (text "\tvle32.v") o1 o2 + LDRU (VecFormat _ FmtInt64) o1 o2 -> op2 (text "\tvle64.v") o1 o2 + LDRU (VecFormat _ FmtFloat) o1 o2 -> op2 (text "\tvle32.v") o1 o2 + LDRU (VecFormat _ FmtDouble) o1 o2 -> op2 (text "\tvle64.v") o1 o2 LDRU f o1 o2 -> pprPanic "Unsupported unsigned load" ((text . show) f <+> pprOp platform o1 <+> pprOp platform o2) FENCE r w -> line $ text "\tfence" <+> pprFenceType r <> char ',' <+> pprFenceType w FCVT FloatToFloat o1@(OpReg FF32 _) o2@(OpReg FF64 _) -> op2 (text "\tfcvt.s.d") o1 o2 @@ -729,38 +788,41 @@ pprInstr platform instr = case instr of FMAX o1 o2 o3 | isSingleOp o1 -> op3 (text "\tfmax.s") o1 o2 o3 | isDoubleOp o2 -> op3 (text "\tfmax.d") o1 o2 o3 - FMA variant d r1 r2 r3 | isFloatRegOp d -> - let fma = case variant of - FMAdd -> text "\tfmadd" <> dot <> floatPrecission d - FMSub -> text "\tfmsub" <> dot <> floatPrecission d - FNMAdd -> text "\tfnmadd" <> dot <> floatPrecission d - FNMSub -> text "\tfnmsub" <> dot <> floatPrecission d - in op4 fma d r1 r2 r3 - VFMA variant o1@(OpReg fmt _reg) o2 o3 | VecFormat l fmt' <- fmt -> - let formatString = if (isFloatFormat . scalarFormatFormat) fmt' then text "f" else text "" - prefix = text "v" <> formatString - suffix = text "vv" - fma = case variant of - FMAdd -> text "madd" - FMSub -> text "msub" -- TODO: Works only for floats! - FNMAdd -> text "nmadd" -- TODO: Works only for floats! - FNMSub -> text "nmsub" - in op3 (tab <> prefix <> fma <> dot <> suffix) o1 o2 o3 + FMA variant d r1 r2 r3 + | isFloatRegOp d -> + let fma = case variant of + FMAdd -> text "\tfmadd" <> dot <> floatPrecission d + FMSub -> text "\tfmsub" <> dot <> floatPrecission d + FNMAdd -> text "\tfnmadd" <> dot <> floatPrecission d + FNMSub -> text "\tfnmsub" <> dot <> floatPrecission d + in op4 fma d r1 r2 r3 + VFMA variant o1@(OpReg fmt _reg) o2 o3 + | VecFormat l fmt' <- fmt -> + let formatString = if (isFloatFormat . scalarFormatFormat) fmt' then text "f" else text "" + prefix = text "v" <> formatString + suffix = text "vv" + fma = case variant of + FMAdd -> text "madd" + FMSub -> text "msub" -- TODO: Works only for floats! + FNMAdd -> text "nmadd" -- TODO: Works only for floats! + FNMSub -> text "nmsub" + in op3 (tab <> prefix <> fma <> dot <> suffix) o1 o2 o3 VFMA _variant o1 _o2 _o3 -> pprPanic "RV64.pprInstr - VFMA can only target registers." (pprOp platform o1) - VMV o1@(OpReg fmt _reg) o2 | isFloatOp o1 && isVectorRegOp o2 -> configVec fmt $$ op2 (text "\tvfmv" <> dot <> text "f" <> dot <> text "s") o1 o2 - | isFloatOp o2 -> configVec fmt $$ op2 (text "\tvfmv" <> dot <> opToVInstrSuffix o1 <> dot <> text "f") o1 o2 - | isIntRegOp o1 && isVectorRegOp o2 -> configVec fmt $$ op2 (text "\tvmv" <> dot <> text "x" <> dot <> text "s") o1 o2 - | isIntRegOp o2 -> configVec fmt $$ op2 (text "\tvmv" <> dot <> opToVInstrSuffix o1 <> dot <> text "x") o1 o2 - | isVectorRegOp o1 && isVectorRegOp o2 -> configVec fmt $$ op2 (text "\tvmv" <> dot <> opToVInstrSuffix o1 <> dot <> text "v") o1 o2 - | True -> pprPanic "RV64.pprInstr - impossible vector move (VMV)" (pprOp platform o1 <+> pprOp platform o2 <+> text "fmt" <> colon <> (text . show) fmt) - VMV o1 _o2 -> pprPanic "RV64.pprInstr - VMV can only target registers." (pprOp platform o1) - VID op@(OpReg fmt _reg) -> configVec fmt $$ op1 (text "\tvid.v") op + VMV o1@(OpReg fmt _reg) o2 + | isFloatOp o1 && isVectorRegOp o2 -> op2 (text "\tvfmv" <> dot <> text "f" <> dot <> text "s") o1 o2 + | isVectorRegOp o1 && isFloatOp o2 -> op2 (text "\tvfmv" <> dot <> opToVInstrSuffix o1 <> dot <> text "f") o1 o2 + | isIntRegOp o1 && isVectorRegOp o2 -> op2 (text "\tvmv" <> dot <> text "x" <> dot <> text "s") o1 o2 + | isVectorRegOp o1 && isIntRegOp o2 -> op2 (text "\tvmv" <> dot <> opToVInstrSuffix o1 <> dot <> text "x") o1 o2 + | isVectorRegOp o1 && isVectorRegOp o2 -> op2 (text "\tvmv" <> dot <> opToVInstrSuffix o1 <> dot <> text "v") o1 o2 + | True -> pprPanic "RV64.pprInstr - impossible vector move (VMV)" (pprOp platform o1 <+> pprOp platform o2 <+> text "fmt" <> colon <> (text . show) fmt) + VMV o1 o2 -> pprPanic "RV64.pprInstr - invalid VMV instruction" (text "VMV" <+> pprOp platform o1 <> comma <+> pprOp platform o2) + VID op | isVectorRegOp op -> op1 (text "\tvid.v") op VID op -> pprPanic "RV64.pprInstr - VID can only target registers." (pprOp platform op) - VMSEQ o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2] && isIntOp o3 -> configVec fmt $$ op3 (text "\tvmseq.vx") o1 o2 o3 + VMSEQ o1 o2 o3 | allVectorRegOps [o1, o2] && isIntOp o3 -> op3 (text "\tvmseq.vx") o1 o2 o3 VMSEQ o1 o2 o3 -> pprPanic "RV64.pprInstr - VMSEQ wrong operands." (pprOps platform [o1, o2, o3]) - VMERGE o1@(OpReg fmt _reg) o2 o3 o4 | allVectorRegOps [o1, o2, o3, o4] -> configVec fmt $$ op4 (text "\tvmerge.vvm") o1 o2 o3 o4 + VMERGE o1 o2 o3 o4 | allVectorRegOps [o1, o2, o3, o4] -> op4 (text "\tvmerge.vvm") o1 o2 o3 o4 VMERGE o1 o2 o3 o4 -> pprPanic "RV64.pprInstr - VMERGE wrong operands." (pprOps platform [o1, o2, o3, o4]) - VSLIDEDOWN o1@(OpReg fmt _reg) o2 o3 |allVectorRegOps [o1, o2] && isIntOp o3-> configVec fmt $$ op3 (text "\tvslidedown.vx") o1 o2 o3 + VSLIDEDOWN o1 o2 o3 | allVectorRegOps [o1, o2] && isIntOp o3 -> op3 (text "\tvslidedown.vx") o1 o2 o3 VSLIDEDOWN o1 o2 o3 -> pprPanic "RV64.pprInstr - VSLIDEDOWN wrong operands." (pprOps platform [o1, o2, o3]) -- TODO: adjust VSETIVLI to contain only format? VSETIVLI (OpReg fmt dst) len width grouping ta ma -> @@ -778,31 +840,32 @@ pprInstr platform instr = case instr of <> comma <+> pprMasking ma VSETIVLI o1 _ _ _ _ _ -> pprPanic "RV64.pprInstr - VSETIVLI wrong operands." (pprOp platform o1) - VNEG o1@(OpReg fmt _reg) o2 | allVectorRegOps [o1, o2] -> configVec fmt $$ op2 (text "\tvfneg.v") o1 o2 + VNEG o1 o2 | allVectorRegOps [o1, o2] -> op2 (text "\tvfneg.v") o1 o2 VNEG o1 o2 -> pprPanic "RV64.pprInstr - VNEG wrong operands." (pprOps platform [o1, o2]) - VADD o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvfadd.vv") o1 o2 o3 + VADD o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvfadd.vv") o1 o2 o3 VADD o1 o2 o3 -> pprPanic "RV64.pprInstr - VADD wrong operands." (pprOps platform [o1, o2, o3]) - VSUB o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvfsub.vv") o1 o2 o3 + VSUB o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvfsub.vv") o1 o2 o3 VSUB o1 o2 o3 -> pprPanic "RV64.pprInstr - VSUB wrong operands." (pprOps platform [o1, o2, o3]) - VMUL o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvfmul.vv") o1 o2 o3 + VMUL o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvfmul.vv") o1 o2 o3 VMUL o1 o2 o3 -> pprPanic "RV64.pprInstr - VMUL wrong operands." (pprOps platform [o1, o2, o3]) - VQUOT o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvfdiv.vv") o1 o2 o3 + VQUOT o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvfdiv.vv") o1 o2 o3 VQUOT o1 o2 o3 -> pprPanic "RV64.pprInstr - VQUOT wrong operands." (pprOps platform [o1, o2, o3]) - VSMIN o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvmin.vv") o1 o2 o3 + VSMIN o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvmin.vv") o1 o2 o3 VSMIN o1 o2 o3 -> pprPanic "RV64.pprInstr - VSMIN wrong operands." (pprOps platform [o1, o2, o3]) - VSMAX o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvmax.vv") o1 o2 o3 + VSMAX o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvmax.vv") o1 o2 o3 VSMAX o1 o2 o3 -> pprPanic "RV64.pprInstr - VSMAX wrong operands." (pprOps platform [o1, o2, o3]) - VUMIN o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvminu.vv") o1 o2 o3 + VUMIN o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvminu.vv") o1 o2 o3 VUMIN o1 o2 o3 -> pprPanic "RV64.pprInstr - VUMIN wrong operands." (pprOps platform [o1, o2, o3]) - VUMAX o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvmaxu.vv") o1 o2 o3 + VUMAX o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvmaxu.vv") o1 o2 o3 VUMAX o1 o2 o3 -> pprPanic "RV64.pprInstr - VUMAX wrong operands." (pprOps platform [o1, o2, o3]) - VFMIN o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvfmin.vv") o1 o2 o3 + VFMIN o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvfmin.vv") o1 o2 o3 VFMIN o1 o2 o3 -> pprPanic "RV64.pprInstr - VFMIN wrong operands." (pprOps platform [o1, o2, o3]) - VFMAX o1@(OpReg fmt _reg) o2 o3 | allVectorRegOps [o1, o2, o3] -> configVec fmt $$ op3 (text "\tvfmax.vv") o1 o2 o3 + VFMAX o1 o2 o3 | allVectorRegOps [o1, o2, o3] -> op3 (text "\tvfmax.vv") o1 o2 o3 VFMAX o1 o2 o3 -> pprPanic "RV64.pprInstr - VFMAX wrong operands." (pprOps platform [o1, o2, o3]) instr -> panic $ "RV64.pprInstr - Unknown instruction: " ++ instrCon instr where op1 op o1 = line $ op <+> pprOp platform o1 + op2 :: (IsLine (Line t), IsDoc t, HasCallStack) => Line t -> Operand -> Operand -> t op2 op o1 o2 = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2 op3 op o1 o2 o3 = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 op4 op o1 o2 o3 o4 = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 <> comma <+> pprOp platform o4 @@ -841,11 +904,6 @@ pprInstr platform instr = case instr of opToVInstrSuffix op | isVectorRegOp op = text "v" opToVInstrSuffix op = pprPanic "Unsupported operand for vector instruction" (pprOp platform op) - configVec :: (IsDoc doc) => Format -> doc - configVec (VecFormat length fmt) = - pprInstr platform (VSETIVLI (OpReg II64 zeroReg) (fromIntegral length) ((formatToWidth . scalarFormatFormat) fmt) M1 TA MA) - configVec fmt = pprPanic "Unsupported vector configuration" ((text . show) fmt) - floatOpPrecision :: Platform -> Operand -> Operand -> String floatOpPrecision _p l r | isFloatOp l && isFloatOp r && isSingleOp l && isSingleOp r = "s" -- single precision floatOpPrecision _p l r | isFloatOp l && isFloatOp r && isDoubleOp l && isDoubleOp r = "d" -- double precision @@ -872,3 +930,77 @@ pprBcond c = text "b" <> pprCond c UGT -> text "gtu" -- BCOND cannot handle floating point comparisons / registers _ -> panic $ "RV64.ppr: unhandled BCOND conditional: " ++ show c + +-- | Get the `Format` to configure for a vector operation (if any) +-- +-- If an `Instr` is is a vector insruction, we have to configure the correct +-- `Format` such that the vector registers are correctly interpreted by the CPU. +instrVecFormat :: Platform -> Instr -> Maybe Format +instrVecFormat platform instr = case instr of + ANN _doc instr' -> instrVecFormat platform instr' + STR fmt _o1 _o2 | isVecFormat fmt -> Just fmt + LDR fmt _o1 _o2 | isVecFormat fmt -> Just fmt + LDRU fmt _o1 _o2 | isVecFormat fmt -> Just fmt + MOV (OpReg fmt _reg) _o2 + | isVecFormat fmt -> checkedJustFmt fmt + MOV _o1 (OpReg fmt _reg) + | isVecFormat fmt -> checkedJustFmt fmt + VFMA _v (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VMV (OpReg fmt _reg) _o2 + | isVecFormat fmt -> checkedJustFmt fmt + VMV _o1 (OpReg fmt _reg) + | isVecFormat fmt -> checkedJustFmt fmt + VMV _o1 _o2 -> pprPanic "Did not match" (pprInstr platform instr) + VID (OpReg fmt _reg) + | isVecFormat fmt -> checkedJustFmt fmt + VID _o1 -> pprPanic "Did not match" (pprInstr platform instr) + VMSEQ (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VMSEQ _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VMERGE (OpReg fmt _reg) _o2 _o3 _o4 + | isVecFormat fmt -> checkedJustFmt fmt + VMERGE _o1 _o2 _o3 _o4 -> pprPanic "Did not match" (pprInstr platform instr) + VSLIDEDOWN (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VSLIDEDOWN _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VNEG (OpReg fmt _reg) _o2 + | isVecFormat fmt -> checkedJustFmt fmt + VNEG _o1 _o2 -> pprPanic "Did not match" (pprInstr platform instr) + VADD (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VADD _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VSUB (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VSUB _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VMUL (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VMUL _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VQUOT (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VQUOT _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VSMIN (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VSMIN _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VSMAX (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VSMAX _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VUMIN (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VUMIN _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VUMAX (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VUMAX _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VFMIN (OpReg fmt _reg) _o2 _o3 + | isVecFormat fmt -> checkedJustFmt fmt + VFMIN _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + VFMAX (OpReg fmt _reg) _o2 _o3 -> checkedJustFmt fmt + VFMAX _o1 _o2 _o3 -> pprPanic "Did not match" (pprInstr platform instr) + _ -> Nothing + where + checkedJustFmt :: Format -> Maybe Format + checkedJustFmt fmt | isVecFormat fmt = Just fmt + checkedJustFmt fmt = + pprPanic + ("Vector format expected but got " ++ show fmt) + (pprInstr platform instr) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/44be546ec6b181df1154794aa931f480ddb13ef9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/44be546ec6b181df1154794aa931f480ddb13ef9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250302/624d366b/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 2 14:46:48 2025 From: gitlab at gitlab.haskell.org (Adriaan Leijnse (@aidylns)) Date: Sun, 02 Mar 2025 09:46:48 -0500 Subject: [Git][ghc/ghc][wip/aidylns/ttg-remove-hsunboundvar-via-hshole] Rewrite Note "Holes in Expressions" Message-ID: <67c46f5847bda_162397edb645394f@gitlab.mail> Adriaan Leijnse pushed to branch wip/aidylns/ttg-remove-hsunboundvar-via-hshole at Glasgow Haskell Compiler / GHC Commits: a3866ba8 by Adriaan Leijnse at 2025-03-02T14:45:49+00:00 Rewrite Note "Holes in Expressions" - - - - - 1 changed file: - compiler/GHC/Tc/Types/Constraint.hs Changes: ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -648,76 +648,115 @@ type to an ill-kinded one. Note [Holes in expressions] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ -This Note explains how GHC tracks "holes" in expressions. It does not -deal with holes in types, nor with partial type signatures. - -A hole represents a missing bit of an expression. Example: - foo x = x && _ -GHC then emits a diagnostic, describing the bit that is left out: - Foo.hs:5:14: error: [GHC-88464] - • Found hole: _ :: Bool - • In the second argument of ‘(&&)’, namely ‘_’ - In the expression: x && _ - -GHC uses the same mechanism is used to give diagnostics for out-of-scope -variables: - foo x = x && y -gives diagnostic - Foo.hs:5:14: error: [GHC-88464] - Variable not in scope: y :: Bool - -Here is how holes are represented in expressions: - -* If the user wrote "_": - Parser HsHole (HoleVar "_", NoExtField) - Renamer HsHole (HoleVar "_", NoExtField) - Typechecker HsHole (HoleVar "_", ref) - -* If the user wrote "x", where `x` is not in scope - Parser HsVar "x" - Renamer HsHole (HoleVar "x", NoExtField) - Typechecker HsHole (HoleVar "x", ref) - -In both cases (ref::HoleExprRef) contains +This Note explains how GHC uses the `HsHole` constructor. + +`HsHole` is used to represent: + + - holes in expressions (both of the anonymous "_" and "_named" types), + - unbound variables, + - and parse errors. + +This use can be intuited as "thing which is not necessarily a valid or fully +defined program fragment, but for which a type can be derived". Note that holes +in types and partial type signatures are not handled using the mechanisms +described in this Note. + +* User-facing behavior + + While GHC uses the same mechanism to derive the type for any 'HsHole', it + gives different feedback to the user depending on the type of hole. For + example, an anonymous hole of the form + + foo x = x && _ + + gives the diagnostic + + Foo.hs:5:14: error: [GHC-88464] + • Found hole: _ :: Bool + • In the second argument of ‘(&&)’, namely ‘_’ + In the expression: x && _ + + while an expression containing an unbound variable + + foo x = x && y + + gives + + Foo.hs:5:14: error: [GHC-88464] + Variable not in scope: y :: Bool + +* HsHole during parsing, renaming, and type checking + + The usage of `HsHole` during the three phases is listed below. + + Note that for (anonymous) holes and unbound variables only the parsing phase + is distinct. During renaming and type checking these cases are handled + identically. During final error reporting the diagnostic is different + depending on whether or not the 'RdrName' starts with an underscore. + + - Anynomous holes, i.e. the user wrote "_": + + Parser HsHole (HoleVar "_", NoExtField) + Renamer HsHole (HoleVar "_", NoExtField) + Typechecker HsHole (HoleVar "_", ref :: HoleExprRef) + + - Unbound variables and named holes; i.e. the user wrote "x" or "_x", where `x` + or `_x` is not in scope: + + Parser HsVar "x" + Renamer HsHole (HoleVar "x", NoExtField) + Typechecker HsHole (HoleVar "x", ref :: HoleExprRef) + + - Parse errors currently do not survive beyond the parser because an error is + thrown after parsing. However, in the future GHC is intended to be tolerant + of parse errors until the type checking phase to provide diagnostics similar + to holes. This current singular case looks like this: + + Parser HsHole (HoleError, NoExtField) + +* Contents of HoleExprRef + + HoleExprRef is a data structure used during the type derivation process + containing: + - The type of the hole. - A ref-cell that is filled in (by the typechecker) with an error thunk. With -fdefer-type errors we use this as the value of the hole. - A Unique (see Note [Uniques and tags]). -Typechecking holes +* Typechecking holes -* When the typechecker encounters a `HsHole`, it returns one with the + When the typechecker encounters a `HsHole`, it returns one with the HoleExprRef, but also emits a `DelayedError` into the `WantedConstraints`. - -* This DelayedError later triggers the error reporting, and the filling-in of + This DelayedError later triggers the error reporting, and the filling-in of the error thunk, in GHC.Tc.Errors. -* The user has the option of deferring errors until runtime with + The user has the option of deferring errors until runtime with `-fdefer-type-errors`. In this case, the hole carries evidence in its `HoleExprRef`. This evidence is an erroring expression that prints an error and crashes at runtime. -Desugaring holes +* Desugaring holes -* During desugaring, the `(HsHole (HoleVar "x", ref))` is desugared by + During desugaring, the `(HsHole (HoleVar "x", ref))` is desugared by reading the ref-cell to find the error thunk evidence term, put there by the constraint solver. -Wrinkles: +* Wrinkles: -* Prior to fixing #17812, we used to invent an Id to hold the erroring - expression, and then bind it during type-checking. But this does not support - representation-polymorphic out-of-scope identifiers. See - typecheck/should_compile/T17812. We thus use the mutable-CoreExpr approach - described above. + - Prior to fixing #17812, we used to invent an Id to hold the erroring + expression, and then bind it during type-checking. But this does not support + representation-polymorphic out-of-scope identifiers. See + typecheck/should_compile/T17812. We thus use the mutable-CoreExpr approach + described above. -* You might think that the type in the HoleExprRef is the same as the type of the - hole. However, because the hole type (hole_ty) is rewritten with respect to - givens, this might not be the case. That is, the hole_ty is always (~) to the - type of the HoleExprRef, but they might not be `eqType`. We need the type of the generated - evidence to match what is expected in the context of the hole, and so we must - store these types separately. + - You might think that the type in the HoleExprRef is the same as the type of + the hole. However, because the hole type (hole_ty) is rewritten with respect + to givens, this might not be the case. That is, the hole_ty is always (~) to + the type of the HoleExprRef, but they might not be `eqType`. We need the + type of the generated evidence to match what is expected in the context of + the hole, and so we must store these types separately. -} mkNonCanonical :: CtEvidence -> Ct View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a3866ba8c012e8f99d2e42b1559de65971d3f99d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a3866ba8c012e8f99d2e42b1559de65971d3f99d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250302/60abb907/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 2 18:22:49 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Sun, 02 Mar 2025 13:22:49 -0500 Subject: [Git][ghc/ghc][wip/az/ghc-cpp] 85 commits: Propagate long distance info to guarded let binds Message-ID: <67c4a1f99cf2_7218664b92829449@gitlab.mail> Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC Commits: 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - aab5525e by Alan Zimmerman at 2025-03-01T15:43:45+00:00 GHC-CPP: first rough proof of concept Processes #define FOO #ifdef FOO x = 1 #endif Into [ITcppIgnored [L loc ITcppDefine] ,ITcppIgnored [L loc ITcppIfdef] ,ITvarid "x" ,ITequal ,ITinteger (IL {il_text = SourceText "1", il_neg = False, il_value = 1}) ,ITcppIgnored [L loc ITcppEndif] ,ITeof] In time, ITcppIgnored will be pushed into a comment - - - - - beaa7a20 by Alan Zimmerman at 2025-03-01T15:43:45+00:00 Tidy up before re-visiting the continuation mechanic - - - - - 09e539e8 by Alan Zimmerman at 2025-03-01T15:43:45+00:00 Switch preprocessor to continuation passing style Proof of concept, needs tidying up - - - - - d48d892e by Alan Zimmerman at 2025-03-01T15:43:45+00:00 Small cleanup - - - - - 67baf128 by Alan Zimmerman at 2025-03-01T15:43:45+00:00 Get rid of some cruft - - - - - 1ef80c97 by Alan Zimmerman at 2025-03-01T15:43:45+00:00 Starting to integrate. Need to get the pragma recognised and set - - - - - ec7eded6 by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Make cppTokens extend to end of line, and process CPP comments - - - - - a13fba9b by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Remove unused ITcppDefined - - - - - d6f245a4 by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Allow spaces between # and keyword for preprocessor directive - - - - - c7127138 by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Process CPP continuation lines They are emited as separate ITcppContinue tokens. Perhaps the processing should be more like a comment, and keep on going to the end. BUT, the last line needs to be slurped as a whole. - - - - - 7a13d82f by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Accumulate CPP continuations, process when ready Can be simplified further, we only need one CPP token - - - - - 6f8f2f9a by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Simplify Lexer interface. Only ITcpp We transfer directive lines through it, then parse them from scratch in the preprocessor. - - - - - 806ffe58 by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Deal with directive on last line, with no trailing \n - - - - - 4ee273f6 by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Start parsing and processing the directives - - - - - 52a810ed by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Prepare for processing include files - - - - - 19063786 by Alan Zimmerman at 2025-03-01T15:43:46+00:00 Move PpState into PreProcess And initParserState, initPragState too - - - - - a2c7e100 by Alan Zimmerman at 2025-03-01T15:45:01+00:00 Process nested include files Also move PpState out of Lexer.x, so it is easy to evolve it in a ghci session, loading utils/check-cpp/Main.hs - - - - - d0a7936f by Alan Zimmerman at 2025-03-01T15:45:06+00:00 Split into separate files - - - - - d83b2429 by Alan Zimmerman at 2025-03-01T15:45:06+00:00 Starting on expression parser. But it hangs. Time for Text.Parsec.Expr - - - - - 221db369 by Alan Zimmerman at 2025-03-01T15:45:06+00:00 Start integrating the ghc-cpp work >From https://github.com/alanz/ghc-cpp - - - - - dc3483e4 by Alan Zimmerman at 2025-03-01T15:45:06+00:00 WIP - - - - - 6acaf021 by Alan Zimmerman at 2025-03-01T15:45:06+00:00 Fixup after rebase - - - - - 559ce849 by Alan Zimmerman at 2025-03-01T15:45:06+00:00 WIP - - - - - 327adfc9 by Alan Zimmerman at 2025-03-01T15:45:32+00:00 Fixup after rebase, including all tests pass - - - - - f47ad5c4 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Change pragma usage to GHC_CPP from GhcCPP - - - - - 69223742 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Some comments - - - - - cbef8ace by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Reformat - - - - - 2757e654 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Delete unused file - - - - - 1a7efd24 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Rename module Parse to ParsePP - - - - - 1359331f by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Clarify naming in the parser - - - - - 1b9bfa42 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 WIP. Switching to alex/happy to be able to work in-tree Since Parsec is not available - - - - - d7a16ecf by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Layering is now correct - GHC lexer, emits CPP tokens - accumulated in Preprocessor state - Lexed by CPP lexer, CPP command extracted, tokens concated with spaces (to get rid of token pasting via comments) - if directive lexed and parsed by CPP lexer/parser, and evaluated - - - - - 21c37085 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 First example working Loading Example1.hs into ghci, getting the right results ``` {-# LANGUAGE GHC_CPP #-} module Example1 where y = 3 x = "hello" "bye now" foo = putStrLn x ``` - - - - - 15b6413a by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Rebase, and all tests pass except whitespace for generated parser - - - - - ce48e5d8 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 More plumbing. Ready for testing tomorrow. - - - - - 62694623 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Proress. Renamed module State from Types And at first blush it seems to handle preprocessor scopes properly. - - - - - e3d108cd by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Insert basic GHC version macros into parser __GLASGOW_HASKELL__ __GLASGOW_HASKELL_FULL_VERSION__ __GLASGOW_HASKELL_PATCHLEVEL1__ __GLASGOW_HASKELL_PATCHLEVEL2__ - - - - - 546e03f3 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Re-sync check-cpp for easy ghci work - - - - - dab1a131 by Alan Zimmerman at 2025-03-01T15:45:36+00:00 Get rid of warnings - - - - - 9387eb41 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Rework macro processing, in check-cpp Macros kept at the top level, looked up via name, multiple arity versions per name can be stored - - - - - a0563b89 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 WIP. Can crack arguments for #define Next step it to crack out args in an expansion - - - - - e7066548 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 WIP on arg parsing. - - - - - cf104a8f by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Progress. Still screwing up nested parens. - - - - - df4e10f7 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Seems to work, but has redundant code - - - - - 7872ef9f by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Remove redundant code - - - - - 1339246f by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Reformat - - - - - 14e385c1 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Expand args, single pass Still need to repeat until fixpoint - - - - - f2846c98 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Fixed point expansion - - - - - 8c891302 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Sync the playground to compiler - - - - - 5d0a355a by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Working on dumping the GHC_CPP result But We need to keep the BufSpan in a comment - - - - - 5651478c by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Keep BufSpan in queued comments in GHC.Parser.Lexer - - - - - 3ce0f1fc by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Getting close to being able to print the combined tokens showing what is in and what is out - - - - - 9170ce50 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 First implementation of dumpGhcCpp. Example output First dumps all macros in the state, then the source, showing which lines are in and which are out ------------------------------ - |#define FOO(A,B) A + B - |#define FOO(A,B,C) A + B + C - |#if FOO(1,FOO(3,4)) == 8 - |-- a comment |x = 1 - |#else - |x = 5 - |#endif - - - - - ae2db6c2 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Clean up a bit - - - - - 831eaaf2 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Add -ddump-ghc-cpp option and a test based on it - - - - - 9823870b by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Restore Lexer.x rules, we need them for continuation lines - - - - - e4fa675a by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Lexer.x: trying to sort out the span for continuations - We need to match on \n at the end of the line - We cannot simply back up for it - - - - - fb9154c6 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Inserts predefined macros. But does not dump properly Because the cpp tokens have a trailing newline - - - - - d31a65b1 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Remove unnecessary LExer rules We *need* the ones that explicitly match to the end of the line. - - - - - d3ad4a57 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Generate correct span for ITcpp Dump now works, except we do not render trailing `\` for continuation lines. This is good enough for use in test output. - - - - - ee81af9f by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Reduce duplication in lexer - - - - - 2746ac07 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Tweaks - - - - - 23771407 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Insert min_version predefined macros into state The mechanism now works. Still need to flesh out the full set. - - - - - 9014e2c8 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Trying my alternative pragma syntax. It works, but dumpGhcCpp is broken, I suspect from the ITcpp token span update. - - - - - 5f75e638 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Pragma extraction now works, with both CPP and GHC_CPP For the following {-# LANGUAGE CPP #-} #if __GLASGOW_HASKELL__ >= 913 {-# LANGUAGE GHC_CPP #-} #endif We will enable GHC_CPP only - - - - - e6d36b70 by Alan Zimmerman at 2025-03-01T15:45:37+00:00 Remove some tracing - - - - - 25479c0e by Alan Zimmerman at 2025-03-02T18:21:53+00:00 Fix test exes for changes - - - - - 6416d190 by Alan Zimmerman at 2025-03-02T18:22:11+00:00 For GHC_CPP tests, normalise config-time-based macros - - - - - 209 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Parser/Monad.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Parser.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Parser.hs-boot - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - + compiler/GHC/Parser/PreProcess.hs - + compiler/GHC/Parser/PreProcess/Eval.hs - + compiler/GHC/Parser/PreProcess/Lexer.x - + compiler/GHC/Parser/PreProcess/Macro.hs - + compiler/GHC/Parser/PreProcess/ParsePP.hs - + compiler/GHC/Parser/PreProcess/Parser.y - + compiler/GHC/Parser/PreProcess/ParserM.hs - + compiler/GHC/Parser/PreProcess/State.hs - compiler/GHC/Parser/Utils.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/debugging.rst - ghc/GHCi/UI.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Settings/Default.hs - hadrian/stack.yaml.lock - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - m4/fp_settings.m4 - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/T4437.hs - testsuite/tests/ghc-api/T11579.hs - + testsuite/tests/ghc-cpp/GhcCpp01.hs - + testsuite/tests/ghc-cpp/GhcCpp01.stderr - + testsuite/tests/ghc-cpp/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/linters/notes.stdout - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + utils/check-cpp/.ghci - + utils/check-cpp/.gitignore - + utils/check-cpp/Eval.hs - + utils/check-cpp/Example1.hs - + utils/check-cpp/Example2.hs - + utils/check-cpp/Example3.hs - + utils/check-cpp/Example4.hs - + utils/check-cpp/Lexer.x - + utils/check-cpp/Macro.hs - + utils/check-cpp/Main.hs - + utils/check-cpp/ParsePP.hs - + utils/check-cpp/ParseSimulate.hs - + utils/check-cpp/Parser.y - + utils/check-cpp/ParserM.hs - + utils/check-cpp/PreProcess.hs - + utils/check-cpp/README.md - + utils/check-cpp/State.hs - + utils/check-cpp/run.sh - utils/check-exact/Main.hs - utils/check-exact/Parsers.hs - utils/check-exact/Preprocess.hs - utils/check-exact/Utils.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs - utils/haddock/haddock-api/src/Haddock/Parser.hs - utils/haddock/haddock-api/src/Haddock/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b5089bc8b3e9be63a001175c726e1668fbbe3cbb...6416d190834100a491ccaa14fa7cc9a567aae019 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b5089bc8b3e9be63a001175c726e1668fbbe3cbb...6416d190834100a491ccaa14fa7cc9a567aae019 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250302/0a0f39d6/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 2 23:26:45 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Sun, 02 Mar 2025 18:26:45 -0500 Subject: [Git][ghc/ghc][wip/T25657] More wibbles Message-ID: <67c4e935b9f56_ea4892f871c397c9@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25657 at Glasgow Haskell Compiler / GHC Commits: c9ca52c9 by Simon Peyton Jones at 2025-03-02T23:26:16+00:00 More wibbles - - - - - 4 changed files: - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Core/Predicate.hs ===================================== @@ -30,7 +30,11 @@ module GHC.Core.Predicate ( isIPPred_maybe, -- Evidence variables - DictId, isEvVar, isDictId + DictId, isEvVar, isDictId, + + -- Equality left-hand sides + CanEqLHS(..), canEqLHS_maybe, canTyFamEqLHS_maybe, + canEqLHSKind, canEqLHSType, eqCanEqLHS, ) where @@ -38,7 +42,7 @@ import GHC.Prelude import GHC.Core.Type import GHC.Core.Class -import GHC.Core.TyCo.Compare( eqType ) +import GHC.Core.TyCo.Compare( eqType, tcEqTyConApps ) import GHC.Core.TyCon import GHC.Core.TyCon.RecWalk import GHC.Types.Var @@ -52,6 +56,13 @@ import GHC.Utils.Misc import GHC.Utils.Panic import GHC.Data.FastString + +{- ********************************************************************* +* * +* Pred and PredType * +* * +********************************************************************* -} + -- | A predicate in the solver. The solver tries to prove Wanted predicates -- from Given ones. data Pred @@ -229,9 +240,12 @@ predTypeEqRel ty | isReprEqPred ty = ReprEq | otherwise = NomEq -{------------------------------------------- -Predicates on PredType ---------------------------------------------} + +{- ********************************************************************* +* * +* Predicates on PredType * +* * +********************************************************************* -} {- Note [Evidence for quantified constraints] @@ -492,3 +506,61 @@ isEvVar var = isEvVarType (varType var) isDictId :: Id -> Bool isDictId id = isDictTy (varType id) + + +{- ********************************************************************* +* * +* Equality left-hand sides +* * +********************************************************************* -} + +-- | A 'CanEqLHS' is a type that can appear on the left of a canonical +-- equality: a type variable or /exactly-saturated/ type family application. +data CanEqLHS + = TyVarLHS TyVar + | TyFamLHS TyCon -- ^ TyCon of the family + [Type] -- ^ Arguments, /exactly saturating/ the family + +instance Outputable CanEqLHS where + ppr (TyVarLHS tv) = ppr tv + ppr (TyFamLHS fam_tc fam_args) = ppr (mkTyConApp fam_tc fam_args) + +----------------------------------- +-- | Is a type a canonical LHS? That is, is it a tyvar or an exactly-saturated +-- type family application? +-- Does not look through type synonyms. +canEqLHS_maybe :: Type -> Maybe CanEqLHS +canEqLHS_maybe xi + | Just tv <- getTyVar_maybe xi + = Just $ TyVarLHS tv + + | otherwise + = canTyFamEqLHS_maybe xi + +canTyFamEqLHS_maybe :: Type -> Maybe CanEqLHS +canTyFamEqLHS_maybe xi + | Just (tc, args) <- tcSplitTyConApp_maybe xi + , isTypeFamilyTyCon tc + , args `lengthIs` tyConArity tc + = Just $ TyFamLHS tc args + + | otherwise + = Nothing + +-- | Convert a 'CanEqLHS' back into a 'Type' +canEqLHSType :: CanEqLHS -> Type +canEqLHSType (TyVarLHS tv) = mkTyVarTy tv +canEqLHSType (TyFamLHS fam_tc fam_args) = mkTyConApp fam_tc fam_args + +-- | Retrieve the kind of a 'CanEqLHS' +canEqLHSKind :: CanEqLHS -> Kind +canEqLHSKind (TyVarLHS tv) = tyVarKind tv +canEqLHSKind (TyFamLHS fam_tc fam_args) = piResultTys (tyConKind fam_tc) fam_args + +-- | Are two 'CanEqLHS's equal? +eqCanEqLHS :: CanEqLHS -> CanEqLHS -> Bool +eqCanEqLHS (TyVarLHS tv1) (TyVarLHS tv2) = tv1 == tv2 +eqCanEqLHS (TyFamLHS fam_tc1 fam_args1) (TyFamLHS fam_tc2 fam_args2) + = tcEqTyConApps fam_tc1 fam_args1 fam_tc2 fam_args2 +eqCanEqLHS _ _ = False + ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -35,9 +35,10 @@ import GHC.Builtin.Names( tYPETyConKey, cONSTRAINTTyConKey ) import GHC.Core.Type hiding ( getTvSubstEnv ) import GHC.Core.Coercion hiding ( getCvSubstEnv ) import GHC.Core.TyCon +import GHC.Core.Predicate( CanEqLHS(..), canEqLHS_maybe ) import GHC.Core.TyCon.Env import GHC.Core.TyCo.Rep -import GHC.Core.TyCo.Compare ( eqType, tcEqType ) +import GHC.Core.TyCo.Compare ( eqType, tcEqType, tcEqTyConApps ) import GHC.Core.TyCo.FVs ( tyCoVarsOfCoList, tyCoFVsOfTypes ) import GHC.Core.TyCo.Subst ( mkTvSubst ) import GHC.Core.Map.Type @@ -46,7 +47,7 @@ import GHC.Core.Multiplicity import GHC.Utils.FV( FV, fvVarList ) import GHC.Utils.Misc import GHC.Utils.Outputable -import GHC.Types.Basic( SwapFlag(..), isSwapped ) +import GHC.Types.Basic( SwapFlag(..) ) import GHC.Types.Unique.FM import GHC.Exts( oneShot ) import GHC.Utils.Panic @@ -655,7 +656,7 @@ tcUnifyTyForInjectivity tcUnifyTyForInjectivity unif in_scope t1 t2 = case tc_unify_tys alwaysBindFam alwaysBindTv unif -- Am I unifying? - True -- Do injetivity checks + True -- Do injectivity checks False -- Don't check outermost kinds RespectMultiplicities rn_env emptyTvSubstEnv emptyCvSubstEnv @@ -1432,12 +1433,12 @@ unify_ty env (CoercionTy co1) (CoercionTy co2) kco _ -> return () } -unify_ty env ty1@(TyVarTy {}) ty2 kco - = uVarOrFam env ty1 ty2 kco +unify_ty env (TyVarTy tv1) ty2 kco + = uVarOrFam env (TyVarLHS tv1) ty2 kco -unify_ty env ty1 ty2@(TyVarTy {}) kco +unify_ty env ty1 (TyVarTy tv2) kco | um_unif env -- If unifying, can swap args; but not when matching - = uVarOrFam (umSwapRn env) ty2 ty1 (mkSymCo kco) + = uVarOrFam (umSwapRn env) (TyVarLHS tv2) ty1 (mkSymCo kco) -- Deal with TyConApps unify_ty env ty1 ty2 kco @@ -1460,12 +1461,12 @@ unify_ty env ty1 ty2 kco ; unless (um_inj_tf env) $ -- See (end of) Note [Specification of unification] don'tBeSoSure MARTypeFamily $ unify_tys env noninj_tys1 noninj_tys2 } - | Just {} <- mb_sat_fam_app1 - = uVarOrFam env ty1 ty2 kco + | Just (tc,tys) <- mb_sat_fam_app1 + = uVarOrFam env (TyFamLHS tc tys) ty2 kco | um_unif env - , Just {} <- mb_sat_fam_app2 - = uVarOrFam (umSwapRn env) ty2 ty1 (mkSymCo kco) + , Just (tc,tys) <- mb_sat_fam_app2 + = uVarOrFam (umSwapRn env) (TyFamLHS tc tys) ty1 (mkSymCo kco) -- Handle oversaturated type families. Suppose we have -- (F a b) ~ (c d) where F has arity 1 @@ -1594,9 +1595,10 @@ isSatFamApp (TyConApp tc tys) isSatFamApp _ = Nothing --------------------------------- -uVarOrFam :: UMEnv -> InType -> InType -> OutCoercion -> UM () +uVarOrFam :: UMEnv -> CanEqLHS -> InType -> OutCoercion -> UM () -- Invariants: (a) ty1 is a TyVarTy or a saturated type-family application -- (b) If ty1 is a ty-fam-app, then ty2 is NOT a TyVarTy +-- (c) both args have had coreView already applied -- Why saturated? See (ATF4) in Note [Apartness and type families] uVarOrFam env ty1 ty2 kco = do { substs <- getSubstEnvs @@ -1609,18 +1611,11 @@ uVarOrFam env ty1 ty2 kco -- E.g. a ~ F p q -- Starts with: go a (F p q) -- if `a` not bindable, swap to: go (F p q) a - go swapped substs (TyVarTy tv1) ty2 kco + go swapped substs (TyVarLHS tv1) ty2 kco = go_tv swapped substs tv1 ty2 kco - go swapped substs ty1 ty2 kco - | Just (tc,tys) <- isSatFamApp ty1 - = go_fam swapped substs ty1 tc tys ty2 kco - - go swapped _ ty1 ty2 _ - = assertPpr (isSwapped swapped) (ppr ty1 $$ ppr ty2) $ - -- NB: uVarOrFam calls `go` with ty1=tyvar/tyfaapp, - -- but `go` may recurse having swapped - surelyApart + go swapped substs (TyFamLHS tc tys) ty2 kco + = go_fam swapped substs tc tys ty2 kco ----------------------------- -- go_tv: LHS is a type variable @@ -1663,12 +1658,13 @@ uVarOrFam env ty1 ty2 kco extendTvEnv tv1' rhs -- Bind tv1:=rhs and continue -- When unifying, try swapping: - -- e.g. a ~ F p q we might succeed with go_fam - -- e.g. a ~ beta we might be able to bind `beta` but not `a` + -- e.g. a ~ F p q with `a` not bindable: we might succeed with go_fam + -- e.g. a ~ beta with `a` not bindable: we might be able to bind `beta` -- e.g. beta ~ F beta Int occurs check; but MaybeApart after swapping | um_unif env , NotSwapped <- swapped -- If we have swapped already, don't do so again - = go IsSwapped substs ty2 ty1 (mkSymCo kco) + , Just lhs2 <- canEqLHS_maybe ty2 + = go IsSwapped substs lhs2 (mkTyVarTy tv1) (mkSymCo kco) | occurs_check = maybeApart MARInfinite -- Occurs check | otherwise = surelyApart @@ -1694,27 +1690,28 @@ uVarOrFam env ty1 ty2 kco ----------------------------- -- go_fam: LHS is a saturated type-family application -- Invariant: ty2 is not a TyVarTy - go_fam swapped substs ty1 tc tys1 ty2 kco + go_fam swapped substs tc1 tys1 ty2 kco -- If we are under a forall, just give up and return MaybeApart -- see (ATF3) in Note [Apartness and type families] | not (isEmptyVarSet (um_foralls env)) = maybeApart MARTypeFamily -- We are not under any foralls, so the RnEnv2 is empty - | Just ty1' <- lookupFamEnv (um_fam_env substs) tc tys1 + | Just ty1' <- lookupFamEnv (um_fam_env substs) tc1 tys1 = if | um_unif env -> unify_ty env ty1' ty2 kco | (ty1' `mkCastTy` kco) `tcEqType` ty2 -> maybeApart MARTypeFamily | otherwise -> surelyApart -- Check for equality F tys ~ F tys -- otherwise we'd build an infinite substitution - | ty1 `tcEqType` rhs + | TyConApp tc2 tys2 <- ty2 + , tcEqTyConApps tc1 tys1 tc2 tys2 = return () -- Now check if we can bind the (F tys) to the RHS - | BindMe <- um_bind_fam_fun env tc tys1 rhs + | BindMe <- um_bind_fam_fun env tc1 tys1 rhs = -- ToDo: do we need an occurs check here? - do { extendFamEnv tc tys1 rhs + do { extendFamEnv tc1 tys1 rhs ; maybeApart MARTypeFamily } -- Swap in case of (F a b) ~ (G c d e) @@ -1723,7 +1720,8 @@ uVarOrFam env ty1 ty2 kco -- see (ATF6) in Note [Apartness and type families] | um_unif env , NotSwapped <- swapped - = go IsSwapped substs ty2 ty1 (mkSymCo kco) + , Just lhs2 <- canEqLHS_maybe ty2 + = go IsSwapped substs lhs2 (mkTyConApp tc1 tys1) (mkSymCo kco) | otherwise -- See (ATF4) in Note [Apartness and type families] = surelyApart ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -47,9 +47,6 @@ module GHC.Tc.Types.Constraint ( cterRemoveProblem, cterHasOccursCheck, cterFromKind, - CanEqLHS(..), canEqLHS_maybe, canTyFamEqLHS_maybe, - canEqLHSKind, canEqLHSType, eqCanEqLHS, - Hole(..), HoleSort(..), isOutOfScopeHole, DelayedError(..), NotConcreteError(..), @@ -286,17 +283,6 @@ data EqCt -- An equality constraint; see Note [Canonical equalities] eq_eq_rel :: EqRel -- INVARIANT: cc_eq_rel = ctEvEqRel cc_ev } --- | A 'CanEqLHS' is a type that can appear on the left of a canonical --- equality: a type variable or /exactly-saturated/ type family application. -data CanEqLHS - = TyVarLHS TcTyVar - | TyFamLHS TyCon -- ^ TyCon of the family - [Xi] -- ^ Arguments, /exactly saturating/ the family - -instance Outputable CanEqLHS where - ppr (TyVarLHS tv) = ppr tv - ppr (TyFamLHS fam_tc fam_args) = ppr (mkTyConApp fam_tc fam_args) - eqCtEvidence :: EqCt -> CtEvidence eqCtEvidence = eq_ev @@ -777,45 +763,6 @@ instance Outputable Ct where instance Outputable EqCt where ppr (EqCt { eq_ev = ev }) = ppr ev ------------------------------------ --- | Is a type a canonical LHS? That is, is it a tyvar or an exactly-saturated --- type family application? --- Does not look through type synonyms. -canEqLHS_maybe :: Xi -> Maybe CanEqLHS -canEqLHS_maybe xi - | Just tv <- getTyVar_maybe xi - = Just $ TyVarLHS tv - - | otherwise - = canTyFamEqLHS_maybe xi - -canTyFamEqLHS_maybe :: Xi -> Maybe CanEqLHS -canTyFamEqLHS_maybe xi - | Just (tc, args) <- tcSplitTyConApp_maybe xi - , isTypeFamilyTyCon tc - , args `lengthIs` tyConArity tc - = Just $ TyFamLHS tc args - - | otherwise - = Nothing - --- | Convert a 'CanEqLHS' back into a 'Type' -canEqLHSType :: CanEqLHS -> TcType -canEqLHSType (TyVarLHS tv) = mkTyVarTy tv -canEqLHSType (TyFamLHS fam_tc fam_args) = mkTyConApp fam_tc fam_args - --- | Retrieve the kind of a 'CanEqLHS' -canEqLHSKind :: CanEqLHS -> TcKind -canEqLHSKind (TyVarLHS tv) = tyVarKind tv -canEqLHSKind (TyFamLHS fam_tc fam_args) = piResultTys (tyConKind fam_tc) fam_args - --- | Are two 'CanEqLHS's equal? -eqCanEqLHS :: CanEqLHS -> CanEqLHS -> Bool -eqCanEqLHS (TyVarLHS tv1) (TyVarLHS tv2) = tv1 == tv2 -eqCanEqLHS (TyFamLHS fam_tc1 fam_args1) (TyFamLHS fam_tc2 fam_args2) - = tcEqTyConApps fam_tc1 fam_args1 fam_tc2 fam_args2 -eqCanEqLHS _ _ = False - {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -88,7 +88,7 @@ import GHC.Core.TyCo.Ppr( debugPprType {- pprTyVar -} ) import GHC.Core.TyCon import GHC.Core.Coercion import GHC.Core.Unify -import GHC.Core.Predicate( EqRel(..), mkEqPredRole, mkNomEqPred ) +import GHC.Core.Predicate( EqRel(..), CanEqLHS(..), mkEqPredRole, mkNomEqPred ) import GHC.Core.Multiplicity import GHC.Core.Reduction View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c9ca52c97724c8c7f1d1be2fdc96502dbfe2da8e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c9ca52c97724c8c7f1d1be2fdc96502dbfe2da8e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250302/04373e63/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 10:20:17 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 03 Mar 2025 05:20:17 -0500 Subject: [Git][ghc/ghc][wip/romes/ghci-debugger-2] ghci debugger: improve break/resume control flow Message-ID: <67c58261e15de_1dda5431f5b066538@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ghci-debugger-2 at Glasgow Haskell Compiler / GHC Commits: 607e573d by Rodrigo Mesquita at 2025-03-03T10:19:56+00:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - 4 changed files: - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs Changes: ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -18,7 +18,7 @@ module GHC.Runtime.Eval ( abandon, abandonAll, getResumeContext, getHistorySpan, - getModBreaks, + getModBreaks, readModBreaks, getHistoryModule, setupBreakpoint, back, forward, @@ -154,9 +154,8 @@ getHistoryModule = ibi_tick_mod . historyBreakpointId getHistorySpan :: HscEnv -> History -> IO SrcSpan getHistorySpan hsc_env hist = do let ibi = historyBreakpointId hist - HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) >>= pure . \case - Just hmi -> modBreaks_locs (getModBreaks hmi) ! ibi_tick_index ibi - _ -> panic "getHistorySpan" + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi {- | Finds the enclosing top level function name -} -- ToDo: a better way to do this would be to keep hold of the decl_path computed @@ -164,9 +163,8 @@ getHistorySpan hsc_env hist = do -- for each tick. findEnclosingDecls :: HscEnv -> InternalBreakpointId -> IO [String] findEnclosingDecls hsc_env ibi = do - hmi <- expectJust <$> HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) - return $ - modBreaks_decls (getModBreaks hmi) ! ibi_tick_index ibi + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_decls brks ! ibi_tick_index ibi -- | Update fixity environment in the current interactive context. updateFixityEnv :: GhcMonad m => FixityEnv -> m () @@ -231,7 +229,7 @@ execStmt' stmt stmt_text ExecOptions{..} = do status <- liftIO $ do - let eval_opts = initEvalOpts idflags' (isStep execSingleStep) + let eval_opts = initEvalOpts idflags' (enableGhcStepMode execSingleStep) evalStmt interp eval_opts (execWrap hval) let ic = hsc_IC hsc_env @@ -285,6 +283,11 @@ parseImportDecl expr = withSession $ \hsc_env -> liftIO $ hscImport hsc_env expr emptyHistory :: Int -> BoundedList History emptyHistory size = nilBL size +-- | Turn an 'EvalStatus_' result from interpreting Haskell into a GHCi 'ExecResult'. +-- +-- This function is responsible for resuming execution at an intermediate +-- breakpoint if we don't care about that breakpoint (e.g. if using :steplocal +-- or :stepmodule, rather than :step, we only care about certain breakpoints). handleRunStatus :: GhcMonad m => SingleStep -> String -> ResumeBindings @@ -293,92 +296,107 @@ handleRunStatus :: GhcMonad m -> BoundedList History -> m ExecResult -handleRunStatus step expr bindings final_ids status history0 - | RunAndLogSteps <- step = tracing - | otherwise = not_tracing - where - tracing - | EvalBreak apStack_ref (Just eval_break) resume_ctxt _ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - let dflags = hsc_dflags hsc_env - ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break - hmi <- liftIO $ expectJust <$> - lookupHpt (hsc_HPT hsc_env) (moduleName (ibi_tick_mod ibi)) - let breaks = getModBreaks hmi - - b <- liftIO $ - breakpointStatus interp (modBreaks_flags breaks) (ibi_tick_index ibi) - if b - then not_tracing - -- This breakpoint is explicitly enabled; we want to stop - -- instead of just logging it. - else do - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi - let !history' = history1 `consBL` history0 - -- history is strict, otherwise our BoundedList is pointless. - fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - let eval_opts = initEvalOpts dflags True - status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv - handleRunStatus RunAndLogSteps expr bindings final_ids - status history' - | otherwise - = not_tracing - - not_tracing - -- Hit a breakpoint - | EvalBreak apStack_ref maybe_break resume_ctxt ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - ibi <- case maybe_break of - Nothing -> pure Nothing - Just break -> fmap Just $ liftIO $ - evalBreakpointToId (hsc_HPT hsc_env) break - (hsc_env1, names, span, decl) <- liftIO $ - bindLocalsAtBreakpoint hsc_env apStack_fhv ibi - let - resume = Resume - { resumeStmt = expr - , resumeContext = resume_ctxt_fhv - , resumeBindings = bindings - , resumeFinalIds = final_ids - , resumeApStack = apStack_fhv - , resumeBreakpointId = ibi - , resumeSpan = span - , resumeHistory = toListBL history0 - , resumeDecl = decl - , resumeCCS = ccs - , resumeHistoryIx = 0 - } - hsc_env2 = pushResume hsc_env1 resume - - setSession hsc_env2 - return (ExecBreak names ibi) +handleRunStatus step expr bindings final_ids status history0 = do + hsc_env <- getSession + let + interp = hscInterp hsc_env + dflags = hsc_dflags hsc_env + case status of -- Completed successfully - | EvalComplete allocs (EvalSuccess hvals) <- status - = do hsc_env <- getSession - let final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids - final_names = map getName final_ids - interp = hscInterp hsc_env - liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) - hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} - setSession hsc_env' - return (ExecComplete (Right final_names) allocs) + EvalComplete allocs (EvalSuccess hvals) -> do + let + final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids + final_names = map getName final_ids + liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) + hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} + setSession hsc_env' + return (ExecComplete (Right final_names) allocs) -- Completed with an exception - | EvalComplete alloc (EvalException e) <- status - = return (ExecComplete (Left (fromSerializableException e)) alloc) - + EvalComplete alloc (EvalException e) -> + return (ExecComplete (Left (fromSerializableException e)) alloc) + + -- Nothing case: we stopped when an exception was raised, not at a breakpoint. + EvalBreak apStack_ref Nothing resume_ctxt ccs -> do + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + let span = mkGeneralSrcSpan (fsLit "<unknown>") + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span Nothing + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Nothing + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = "<exception thrown>" + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + + setSession hsc_env2 + return (ExecBreak names Nothing) + + -- Just case: we stopped at a breakpoint + EvalBreak apStack_ref (Just eval_break) resume_ctxt ccs -> do + ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break + tick_brks <- liftIO $ readModBreaks hsc_env (ibi_tick_mod ibi) + let + span = modBreaks_locs tick_brks ! ibi_tick_index ibi + decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi + + b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi) + + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + + -- This breakpoint is explicitly enabled; we want to stop + -- instead of just logging it. + if b || breakHere step span then do + -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break. + -- Specifically, for :steplocal or :stepmodule, don't return control + -- and simply resume execution from here until we hit a breakpoint we do want to stop at. + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Just ibi + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = decl + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + setSession hsc_env2 + return (ExecBreak names (Just ibi)) + else do + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) + status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv + history <- if not tracing then pure history0 else do + history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi + let !history' = history1 `consBL` history0 + -- history is strict, otherwise our BoundedList is pointless. + return history' + handleRunStatus step expr bindings final_ids status history + where + tracing | RunAndLogSteps <- step = True + | otherwise = False -resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> Maybe Int +resumeExec :: GhcMonad m => SingleStep -> Maybe Int -> m ExecResult -resumeExec canLogSpan step mbCnt +resumeExec step mbCnt = do hsc_env <- getSession let ic = hsc_IC hsc_env @@ -423,35 +441,34 @@ resumeExec canLogSpan step mbCnt (Just brkpt, Just cnt) -> setupBreakpoint hsc_env (toBreakpointId brkpt) cnt _ -> return () - let eval_opts = initEvalOpts dflags (isStep step) + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv let prevHistoryLst = fromListBL 50 hist hist' = case mb_brkpt of Nothing -> pure prevHistoryLst Just bi - | not $ canLogSpan span -> pure prevHistoryLst - | otherwise -> do + | breakHere step span -> do hist1 <- liftIO (mkHistory hsc_env apStack bi) return $ hist1 `consBL` fromListBL 50 hist + | otherwise -> pure prevHistoryLst handleRunStatus step expr bindings final_ids status =<< hist' setupBreakpoint :: GhcMonad m => HscEnv -> BreakpointId -> Int -> m () -- #19157 setupBreakpoint hsc_env bi cnt = do let modl = bi_tick_mod bi - modBreaks <- getModBreaks . expectJust <$> - liftIO (lookupHpt (hsc_HPT hsc_env) (moduleName modl)) + modBreaks <- liftIO $ readModBreaks hsc_env modl let breakarray = modBreaks_flags modBreaks interp = hscInterp hsc_env _ <- liftIO $ GHCi.storeBreakpoint interp breakarray (bi_tick_index bi) cnt pure () -back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) back n = moveHist (+n) -forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) forward n = moveHist (subtract n) -moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan, String) +moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan) moveHist fn = do hsc_env <- getSession case ic_resume (hsc_IC hsc_env) of @@ -469,15 +486,20 @@ moveHist fn = do let update_ic apStack mb_info = do - (hsc_env1, names, span, decl) <- - liftIO $ bindLocalsAtBreakpoint hsc_env apStack mb_info + span <- case mb_info of + Nothing -> return $ mkGeneralSrcSpan (fsLit "<unknown>") + Just ibi -> liftIO $ do + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi + (hsc_env1, names) <- + liftIO $ bindLocalsAtBreakpoint hsc_env apStack span mb_info let ic = hsc_IC hsc_env1 r' = r { resumeHistoryIx = new_ix } ic' = ic { ic_resume = r':rs } setSession hsc_env1{ hsc_IC = ic' } - return (names, new_ix, span, decl) + return (names, new_ix, span) -- careful: we want apStack to be the AP_STACK itself, not a thunk -- around it, hence the cases are carefully constructed below to @@ -498,19 +520,25 @@ moveHist fn = do result_fs :: FastString result_fs = fsLit "_result" +-- | Read the 'ModBreaks' of the given home 'Module' from the 'HomeUnitGraph'. +readModBreaks :: HscEnv -> Module -> IO ModBreaks +readModBreaks hsc_env mod = + getModBreaks . expectJust <$> + HUG.lookupHugByModule mod (hsc_HUG hsc_env) + bindLocalsAtBreakpoint :: HscEnv -> ForeignHValue + -> SrcSpan -> Maybe InternalBreakpointId - -> IO (HscEnv, [Name], SrcSpan, String) + -> IO (HscEnv, [Name]) -- Nothing case: we stopped when an exception was raised, not at a -- breakpoint. We have no location information or local variables to -- bind, all we can do is bind a local variable to the exception -- value. -bindLocalsAtBreakpoint hsc_env apStack Nothing = do +bindLocalsAtBreakpoint hsc_env apStack span Nothing = do let exn_occ = mkVarOccFS (fsLit "_exception") - span = mkGeneralSrcSpan (fsLit "<unknown>") exn_name <- newInteractiveBinder hsc_env exn_occ span let e_fs = fsLit "e" @@ -523,32 +551,21 @@ bindLocalsAtBreakpoint hsc_env apStack Nothing = do interp = hscInterp hsc_env -- Loader.extendLoadedEnv interp [(exn_name, apStack)] - return (hsc_env{ hsc_IC = ictxt1 }, [exn_name], span, "<exception thrown>") + return (hsc_env{ hsc_IC = ictxt1 }, [exn_name]) -- Just case: we stopped at a breakpoint, we have information about the location -- of the breakpoint and the free variables of the expression. -bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do - let - interp = hscInterp hsc_env - - info_mod = ibi_info_mod ibi - info_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName info_mod) - let - info_brks = getModBreaks info_hmi - info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) - - tick_mod = ibi_tick_mod ibi - tick_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName tick_mod) - let - tick_brks = getModBreaks tick_hmi - occs = modBreaks_vars tick_brks ! ibi_tick_index ibi - span = modBreaks_locs tick_brks ! ibi_tick_index ibi - decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi +bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do + info_brks <- readModBreaks hsc_env (ibi_info_mod ibi) + tick_brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + let info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) + interp = hscInterp hsc_env + occs = modBreaks_vars tick_brks ! ibi_tick_index ibi -- Rehydrate to understand the breakpoint info relative to the current environment. -- This design is critical to preventing leaks (#22530) (mbVars, result_ty) <- initIfaceLoad hsc_env - $ initIfaceLcl info_mod (text "debugger") NotBoot + $ initIfaceLcl (ibi_info_mod ibi) (text "debugger") NotBoot $ hydrateCgBreakInfo info let @@ -595,7 +612,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do Loader.extendLoadedEnv interp (zip names fhvs) when result_ok $ Loader.extendLoadedEnv interp [(result_name, apStack_fhv)] hsc_env1 <- rttiEnvironment hsc_env{ hsc_IC = ictxt1 } - return (hsc_env1, if result_ok then result_name:names else names, span, decl) + return (hsc_env1, if result_ok then result_name:names else names) where -- We need a fresh Unique for each Id we bind, because the linker -- state is single-threaded and otherwise we'd spam old bindings ===================================== compiler/GHC/Runtime/Eval/Types.hs ===================================== @@ -9,7 +9,8 @@ module GHC.Runtime.Eval.Types ( Resume(..), ResumeBindings, IcGlobalRdrEnv(..), History(..), ExecResult(..), - SingleStep(..), isStep, ExecOptions(..) + SingleStep(..), enableGhcStepMode, breakHere, + ExecOptions(..) ) where import GHC.Prelude @@ -35,21 +36,59 @@ data ExecOptions , execWrap :: ForeignHValue -> EvalExpr ForeignHValue } +-- | What kind of stepping are we doing? data SingleStep = RunToCompletion - | SingleStep + + -- | :trace [expr] | RunAndLogSteps -isStep :: SingleStep -> Bool -isStep RunToCompletion = False -isStep _ = True + -- | :step [expr] + | SingleStep + + -- | :steplocal [expr] + | LocalStep + { breakAt :: SrcSpan } + + -- | :stepmodule [expr] + | ModuleStep + { breakAt :: SrcSpan } + +-- | Whether this 'SingleStep' mode requires instructing the interpreter to +-- step at every breakpoint. +enableGhcStepMode :: SingleStep -> Bool +enableGhcStepMode RunToCompletion = False +enableGhcStepMode _ = True + +-- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return +-- @True@ if based on the step-mode alone we should stop at this breakpoint. +-- +-- In particular, this will always be @False@ for @'RunToCompletion'@ and +-- @'RunAndLogSteps'@. We'd need further information e.g. about the user +-- breakpoints to determine whether to break in those modes. +breakHere :: SingleStep -> SrcSpan -> Bool +breakHere step break_span = case step of + RunToCompletion -> False + RunAndLogSteps -> False + SingleStep -> True + LocalStep span -> break_span `isSubspanOf` span + ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span data ExecResult + + -- | Execution is complete = ExecComplete { execResult :: Either SomeException [Name] , execAllocation :: Word64 } - | ExecBreak + + -- | Execution stopped at a breakpoint. + -- + -- Note: `ExecBreak` is only returned by `handleRunStatus` when GHCi should + -- definitely stop at this breakpoint. GHCi is /not/ responsible for + -- subsequently deciding whether to really stop here. + -- `ExecBreak` always means GHCi breaks. + | ExecBreak { breakNames :: [Name] , breakPointId :: Maybe InternalBreakpointId } ===================================== ghc/GHCi/UI.hs ===================================== @@ -1310,7 +1310,7 @@ runStmt input step = do m_result <- GhciMonad.runStmt stmt input step case m_result of Nothing -> return Nothing - Just result -> Just <$> afterRunStmt (const True) result + Just result -> Just <$> afterRunStmt step result -- `x = y` (a declaration) should be treated as `let x = y` (a statement). -- The reason is because GHCi wasn't designed to support `x = y`, but then @@ -1342,7 +1342,7 @@ runStmt input step = do _ <- liftIO $ tryIO $ hFlushAll stdin m_result <- GhciMonad.runDecls' decls forM m_result $ \result -> - afterRunStmt (const True) (GHC.ExecComplete (Right result) 0) + afterRunStmt step (GHC.ExecComplete (Right result) 0) mk_stmt :: SrcSpan -> HsBind GhcPs -> GhciLStmt GhcPs mk_stmt loc bind = @@ -1359,9 +1359,9 @@ runStmt input step = do modStr = moduleNameString $ moduleName $ icInteractiveModule $ ic -- | Clean up the GHCi environment after a statement has run -afterRunStmt :: GhciMonad m - => (SrcSpan -> Bool) -> GHC.ExecResult -> m GHC.ExecResult -afterRunStmt step_here run_result = do +afterRunStmt :: GhciMonad m => SingleStep {-^ Type of step we took just before -} + -> GHC.ExecResult -> m GHC.ExecResult +afterRunStmt step run_result = do resumes <- GHC.getResumeContext case run_result of GHC.ExecComplete{..} -> @@ -1372,9 +1372,7 @@ afterRunStmt step_here run_result = do when show_types $ printTypeOfNames names GHC.ExecBreak names mb_info | first_resume : _ <- resumes - , isNothing mb_info || - step_here (GHC.resumeSpan first_resume) -> do - mb_id_loc <- toBreakIdAndLocation mb_info + -> do mb_id_loc <- toBreakIdAndLocation mb_info let bCmd = maybe "" ( \(_,l) -> onBreakCmd l ) mb_id_loc if (null bCmd) then printStoppedAtBreakInfo first_resume names @@ -1383,8 +1381,9 @@ afterRunStmt step_here run_result = do st <- getGHCiState enqueueCommands [stop st] return () - | otherwise -> resume step_here GHC.SingleStep Nothing >>= - afterRunStmt step_here >> return () + + | otherwise -> resume step Nothing >>= + afterRunStmt step >> return () flushInterpBuffers withSignalHandlers $ do @@ -3810,7 +3809,7 @@ forceCmd = pprintClosureCommand False True stepCmd :: GhciMonad m => String -> m () stepCmd arg = withSandboxOnly ":step" $ step arg where - step [] = doContinue (const True) GHC.SingleStep + step [] = doContinue GHC.SingleStep step expression = runStmt expression GHC.SingleStep >> return () stepLocalCmd :: GhciMonad m => String -> m () @@ -3829,7 +3828,7 @@ stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg Just loc -> do md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule current_toplevel_decl <- enclosingTickSpan md loc - doContinue (`isSubspanOf` RealSrcSpan current_toplevel_decl Strict.Nothing) GHC.SingleStep + doContinue (GHC.LocalStep (RealSrcSpan current_toplevel_decl Strict.Nothing)) stepModuleCmd :: GhciMonad m => String -> m () stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg @@ -3840,9 +3839,7 @@ stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg mb_span <- getCurrentBreakSpan case mb_span of Nothing -> stepCmd [] - Just pan -> do - let f some_span = srcSpanFileName_maybe pan == srcSpanFileName_maybe some_span - doContinue f GHC.SingleStep + Just pan -> doContinue (GHC.ModuleStep pan) -- | Returns the span of the largest tick containing the srcspan given enclosingTickSpan :: GhciMonad m => Module -> SrcSpan -> m RealSrcSpan @@ -3863,14 +3860,14 @@ traceCmd :: GhciMonad m => String -> m () traceCmd arg = withSandboxOnly ":trace" $ tr arg where - tr [] = doContinue (const True) GHC.RunAndLogSteps + tr [] = doContinue GHC.RunAndLogSteps tr expression = runStmt expression GHC.RunAndLogSteps >> return () continueCmd :: GhciMonad m => String -> m () -- #19157 continueCmd argLine = withSandboxOnly ":continue" $ case contSwitch (words argLine) of Left sdoc -> printForUser sdoc - Right mbCnt -> doContinue' (const True) GHC.RunToCompletion mbCnt + Right mbCnt -> doContinue' GHC.RunToCompletion mbCnt where contSwitch :: [String] -> Either SDoc (Maybe Int) contSwitch [ ] = Right Nothing @@ -3878,13 +3875,13 @@ continueCmd argLine = withSandboxOnly ":continue" $ contSwitch _ = Left $ text "After ':continue' only one ignore count is allowed" -doContinue :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> m () -doContinue pre step = doContinue' pre step Nothing +doContinue :: GhciMonad m => SingleStep -> m () +doContinue step = doContinue' step Nothing -doContinue' :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m () -doContinue' pre step mbCnt= do - runResult <- resume pre step mbCnt - _ <- afterRunStmt pre runResult +doContinue' :: GhciMonad m => SingleStep -> Maybe Int -> m () +doContinue' step mbCnt= do + runResult <- resume step mbCnt + _ <- afterRunStmt step runResult return () abandonCmd :: GhciMonad m => String -> m () @@ -4036,7 +4033,7 @@ backCmd arg | otherwise = liftIO $ putStrLn "Syntax: :back [num]" where back num = withSandboxOnly ":back" $ do - (names, _, pan, _) <- GHC.back num + (names, _, pan) <- GHC.back num printForUser $ text "Logged breakpoint at" <+> ppr pan printTypeOfNames names -- run the command set with ":set stop <cmd>" @@ -4050,7 +4047,7 @@ forwardCmd arg | otherwise = liftIO $ putStrLn "Syntax: :forward [num]" where forward num = withSandboxOnly ":forward" $ do - (names, ix, pan, _) <- GHC.forward num + (names, ix, pan) <- GHC.forward num printForUser $ (if (ix == 0) then text "Stopped at" else text "Logged breakpoint at") <+> ppr pan ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -401,14 +401,14 @@ runDecls' decls = do return Nothing) (Just <$> GHC.runParsedDecls decls) -resume :: GhciMonad m => (SrcSpan -> Bool) -> GHC.SingleStep -> Maybe Int -> m GHC.ExecResult -resume canLogSpan step mbIgnoreCnt = do +resume :: GhciMonad m => GHC.SingleStep -> Maybe Int -> m GHC.ExecResult +resume step mbIgnoreCnt = do st <- getGHCiState reifyGHCi $ \x -> withProgName (progname st) $ withArgs (args st) $ reflectGHCi x $ do - GHC.resumeExec canLogSpan step mbIgnoreCnt + GHC.resumeExec step mbIgnoreCnt -- -------------------------------------------------------------------------- -- timing & statistics View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/607e573d9cf837188255fbf8489568631bab7ec7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/607e573d9cf837188255fbf8489568631bab7ec7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/f9edbe4f/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 10:47:38 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 03 Mar 2025 05:47:38 -0500 Subject: [Git][ghc/ghc][wip/wasm-jsffi-sync-export] 9 commits: compiler: Add export list to GHC.SysTools.Tasks Message-ID: <67c588cace527_1e6fd12ff940212ec@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-sync-export at Glasgow Haskell Compiler / GHC Commits: 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 05f0ddd9 by Cheng Shao at 2025-03-03T07:40:51+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - 04c1fa38 by Cheng Shao at 2025-03-03T07:40:51+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 7bf82192 by Cheng Shao at 2025-03-03T07:40:51+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - 0c1c4e58 by Cheng Shao at 2025-03-03T07:40:51+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - 6fd0440c by Cheng Shao at 2025-03-03T07:40:51+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 3add7dc2 by Cheng Shao at 2025-03-03T10:47:05+00:00 wasm: add js_src to WouldBlockException - - - - - 22 changed files: - compiler/GHC/Cmm/Opt.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Gen/Foreign.hs - distrib/configure.ac.in - docs/users_guide/wasm.rst - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - m4/fp_settings.m4 - rts/include/RtsAPI.h - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs Changes: ===================================== compiler/GHC/Cmm/Opt.hs ===================================== @@ -63,18 +63,23 @@ cmmMachOpFoldM _ (MO_VF_Broadcast lg _w) exprs = [CmmLit l] -> Just $! CmmLit (CmmVec $ replicate lg l) _ -> Nothing cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] - = Just $! case op of - MO_S_Neg _ -> CmmLit (CmmInt (narrowS rep (-x)) rep) - MO_Not _ -> CmmLit (CmmInt (complement x) rep) + = case op of + MO_S_Neg _ -> Just $! CmmLit (CmmInt (narrowS rep (-x)) rep) + MO_Not _ -> Just $! CmmLit (CmmInt (complement x) rep) -- these are interesting: we must first narrow to the -- "from" type, in order to truncate to the correct size. -- The final narrow/widen to the destination type -- is implicit in the CmmLit. - MO_SF_Round _frm to -> CmmLit (CmmFloat (fromInteger x) to) - MO_SS_Conv from to -> CmmLit (CmmInt (narrowS from x) to) - MO_UU_Conv from to -> CmmLit (CmmInt (narrowU from x) to) - MO_XX_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + MO_SF_Round _frm to -> Just $! CmmLit (CmmFloat (fromInteger x) to) + MO_SS_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) + MO_UU_Conv from to -> Just $! CmmLit (CmmInt (narrowU from x) to) + MO_XX_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) + + -- Not as simply as it seems, since CmmFloat uses Rational, so skipping those + -- for now ... + MO_WF_Bitcast _w -> Nothing + MO_FW_Bitcast _w -> Nothing _ -> panic $ "cmmMachOpFoldM: unknown unary op: " ++ show op -- Eliminate shifts that are wider than the shiftee ===================================== compiler/GHC/HsToCore/Foreign/C.hs ===================================== @@ -515,8 +515,7 @@ mkFExportCBits dflags c_nm maybe_target arg_htys res_hty is_IO_res_ty cc , text "rts_inCall" <> parens ( char '&' <> cap <> text "rts_apply" <> parens ( - cap <> - text "(HaskellObj)" + cap <> (if is_IO_res_ty then text "runIO_closure" else text "runNonIO_closure") ===================================== compiler/GHC/HsToCore/Foreign/Wasm.hs ===================================== @@ -11,6 +11,7 @@ import Data.List ( intercalate, stripPrefix, ) +import Data.List qualified import Data.Maybe import GHC.Builtin.Names import GHC.Builtin.Types @@ -46,6 +47,9 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import Language.Haskell.Syntax.Basic +data Synchronicity = Sync | Async + deriving (Eq) + dsWasmJSImport :: Id -> Coercion -> @@ -53,10 +57,15 @@ dsWasmJSImport :: Safety -> DsM ([Binding], CHeader, CStub, [Id]) dsWasmJSImport id co (CFunction (StaticTarget _ js_src mUnitId _)) safety - | js_src == "wrapper" = dsWasmJSDynamicExport id co mUnitId + | js_src == "wrapper" = dsWasmJSDynamicExport Async id co mUnitId + | js_src == "wrapper sync" = dsWasmJSDynamicExport Sync id co mUnitId | otherwise = do - (bs, h, c) <- dsWasmJSStaticImport id co (unpackFS js_src) mUnitId safety + (bs, h, c) <- dsWasmJSStaticImport id co (unpackFS js_src) mUnitId sync pure (bs, h, c, []) + where + sync = case safety of + PlayRisky -> Sync + _ -> Async dsWasmJSImport _ _ _ _ = panic "dsWasmJSImport: unreachable" {- @@ -77,17 +86,24 @@ We desugar it to three bindings under the hood: mk_wrapper_worker :: StablePtr HsFuncType -> HsFuncType mk_wrapper_worker sp = unsafeDupablePerformIO (deRefStablePtr sp) -No need to bother with eta-expansion here. Also, the worker function -is marked as a JSFFI static export. +The worker function is marked as a JSFFI static export. It turns a +dynamic export to a static one by prepending a StablePtr to the +argument list. + +We don't actually generate a Core binding for the worker function +though; the JSFFI static export C stub generation logic would just +generate a function that doesn't need to refer to the worker Id's +closure. This is not just for convenience, it's actually required for +correctness, see #25473. 2. The adjustor function foreign import javascript unsafe "(...args) => __exports.mk_wrapper_worker($1, ...args)" mk_wrapper_adjustor :: StablePtr HsFuncType -> IO JSVal -It generates a JavaScript callback that captures the stable pointer. -When the callback is invoked later, it calls our worker function and -passes the stable pointer as well as the rest of the arguments. +Now that mk_wrapper_worker is exported in __exports, we need to make a +JavaScript callback that invokes mk_wrapper_worker with the right +StablePtr as well as the rest of the arguments. 3. The wrapper function @@ -102,43 +118,47 @@ a StablePtr# field which is NULL by default, but for JSFFI dynamic exports, it's set to the Haskell function's stable pointer. This way, when we call freeJSVal, the Haskell function can be freed as well. +By default, JSFFI exports are async JavaScript functions. One can use +"wrapper sync" instead of "wrapper" to indicate the Haskell function +is meant to be exported as a sync JavaScript function. All the +comments above still hold, with only only difference: +mk_wrapper_worker is exported as a sync function. See +Note [Desugaring JSFFI static export] for further details. + -} dsWasmJSDynamicExport :: - Id -> Coercion -> Maybe Unit -> DsM ([Binding], CHeader, CStub, [Id]) -dsWasmJSDynamicExport fn_id co mUnitId = do + Synchronicity -> + Id -> + Coercion -> + Maybe Unit -> + DsM ([Binding], CHeader, CStub, [Id]) +dsWasmJSDynamicExport sync fn_id co mUnitId = do sp_tycon <- dsLookupTyCon stablePtrTyConName let ty = coercionLKind co (tv_bndrs, fun_ty) = tcSplitForAllTyVarBinders ty ([Scaled ManyTy arg_ty], io_jsval_ty) = tcSplitFunTys fun_ty sp_ty = mkTyConApp sp_tycon [arg_ty] - (real_arg_tys, _) = tcSplitFunTys arg_ty sp_id <- newSysLocalMDs sp_ty - work_uniq <- newUnique - work_export_name <- uniqueCFunName - deRefStablePtr_id <- lookupGhcInternalVarId "GHC.Internal.Stable" "deRefStablePtr" + work_export_name <- unpackFS <$> uniqueCFunName + deRefStablePtr_id <- + lookupGhcInternalVarId + "GHC.Internal.Stable" + "deRefStablePtr" unsafeDupablePerformIO_id <- lookupGhcInternalVarId "GHC.Internal.IO.Unsafe" "unsafeDupablePerformIO" - let work_id = - mkExportedVanillaId - ( mkExternalName - work_uniq - (nameModule $ getName fn_id) - (mkVarOcc $ "jsffi_" ++ occNameString (getOccName fn_id) ++ "_work") - generatedSrcSpan - ) - work_ty - work_rhs = + let work_rhs = mkCoreLams ([tv | Bndr tv _ <- tv_bndrs] ++ [sp_id]) $ mkApps (Var unsafeDupablePerformIO_id) [Type arg_ty, mkApps (Var deRefStablePtr_id) [Type arg_ty, Var sp_id]] work_ty = exprType work_rhs (work_h, work_c, _, work_ids, work_bs) <- - dsWasmJSExport - work_id + dsWasmJSExport' + sync + Nothing (mkRepReflCo work_ty) work_export_name adjustor_uniq <- newUnique @@ -157,21 +177,18 @@ dsWasmJSDynamicExport fn_id co mUnitId = do adjustor_ty adjustor_ty = mkForAllTys tv_bndrs $ mkVisFunTysMany [sp_ty] io_jsval_ty adjustor_js_src = - "(" - ++ intercalate "," ["a" ++ show i | i <- [1 .. length real_arg_tys]] - ++ ") => __exports." - ++ unpackFS work_export_name - ++ "($1" - ++ mconcat [",a" ++ show i | i <- [1 .. length real_arg_tys]] - ++ ")" + "(...args) => __exports." ++ work_export_name ++ "($1, ...args)" (adjustor_bs, adjustor_h, adjustor_c) <- dsWasmJSStaticImport adjustor_id (mkRepReflCo adjustor_ty) adjustor_js_src mUnitId - PlayRisky - mkJSCallback_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "mkJSCallback" + Sync + mkJSCallback_id <- + lookupGhcInternalVarId + "GHC.Internal.Wasm.Prim.Exports" + "mkJSCallback" let wrap_rhs = mkCoreLams [tv | Bndr tv _ <- tv_bndrs] $ mkApps @@ -182,7 +199,7 @@ dsWasmJSDynamicExport fn_id co mUnitId = do [Type $ mkTyVarTy tv | Bndr tv _ <- tv_bndrs] ] pure - ( [(fn_id, Cast wrap_rhs co), (work_id, work_rhs)] ++ work_bs ++ adjustor_bs, + ( [(fn_id, Cast wrap_rhs co)] ++ work_bs ++ adjustor_bs, work_h `mappend` adjustor_h, work_c `mappend` adjustor_c, work_ids @@ -194,7 +211,7 @@ Note [Desugaring JSFFI import] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The simplest case is JSFFI sync import, those marked as unsafe. It is -implemented on top of C FFI unsafe import. +implemented on top of C FFI safe import. Unlike C FFI which generates a worker/wrapper pair that unboxes the arguments and boxes the result in Haskell, we only desugar to a single @@ -202,10 +219,11 @@ Haskell binding that case-binds the arguments to ensure they're evaluated, then passes the boxed arguments directly to C and receive the boxed result from C as well. -This is of course less efficient than how C FFI does it, and unboxed -FFI types aren't supported, but it's the easiest way to implement it, +This is slightly less efficient than how C FFI does it, and unboxed +FFI types aren't supported, but it's the simplest way to implement it, especially since leaving all the boxing/unboxing business to C unifies -the implementation of JSFFI imports and exports. +the implementation of JSFFI imports and exports +(rts_mkJSVal/rts_getJSVal). Now, each sync import calls a generated C function with a unique symbol. The C function uses rts_get* to unbox the arguments, call into @@ -240,6 +258,14 @@ module. Note that above is assembly source file, but we're only generating a C stub, so we need to smuggle the assembly code into C via __asm__. +The C FFI import that calls the generated C function is always marked +as safe. There is some extra overhead, but this allows re-entrance by +Haskell -> JavaScript -> Haskell function calls with each call being a +synchronous one. It's possible to steal the "interruptible" keyword to +indicate async imports, "safe" for sync imports and "unsafe" for sync +imports sans the safe C FFI overhead, but it's simply not worth the +extra complexity. + JSFFI async import is implemented on top of JSFFI sync import. We still desugar it to a single Haskell binding that calls C, with some subtle differences: @@ -250,12 +276,6 @@ subtle differences: "($1, $2)". As you can see, it is the arrow function binder, and the post-linker will respect the async binder and allow await in the function body. -- The C import is also marked as safe. This is required since the - JavaScript code may re-enter Haskell. If re-entrance only happens in - future event loop tasks, it's fine to mark the C import as unsafe - since the current Haskell execution context has already been freed - at that point, but there's no such guarantee, so better safe than - sorry here. Now we have the Promise JSVal, we apply stg_blockPromise to it to get a thunk with the desired return type. When the thunk is forced, it @@ -270,9 +290,9 @@ dsWasmJSStaticImport :: Coercion -> String -> Maybe Unit -> - Safety -> + Synchronicity -> DsM ([Binding], CHeader, CStub) -dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do +dsWasmJSStaticImport fn_id co js_src' mUnitId sync = do cfun_name <- uniqueCFunName let ty = coercionLKind co (tvs, fun_ty) = tcSplitForAllInvisTyVars ty @@ -289,36 +309,31 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do ++ ")" | otherwise = js_src' - case safety of - PlayRisky -> do - rhs <- - importBindingRHS - mUnitId - PlayRisky - cfun_name - tvs - arg_tys - orig_res_ty - id + case sync of + Sync -> do + rhs <- importBindingRHS mUnitId cfun_name tvs arg_tys orig_res_ty id pure ( [(fn_id, Cast rhs co)], CHeader commonCDecls, - importCStub - PlayRisky - cfun_name - (map scaledThing arg_tys) - res_ty - js_src + importCStub Sync cfun_name (map scaledThing arg_tys) res_ty js_src ) - _ -> do + Async -> do + err_msg <- mkStringExpr $ js_src io_tycon <- dsLookupTyCon ioTyConName - jsval_ty <- mkTyConTy <$> lookupGhcInternalTyCon "GHC.Internal.Wasm.Prim.Types" "JSVal" + jsval_ty <- + mkTyConTy + <$> lookupGhcInternalTyCon "GHC.Internal.Wasm.Prim.Types" "JSVal" bindIO_id <- dsLookupGlobalId bindIOName returnIO_id <- dsLookupGlobalId returnIOName promise_id <- newSysLocalMDs jsval_ty - blockPromise_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" "stg_blockPromise" + blockPromise_id <- + lookupGhcInternalVarId + "GHC.Internal.Wasm.Prim.Imports" + "stg_blockPromise" msgPromise_id <- - lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" $ "stg_messagePromise" ++ ffiType res_ty + lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" + $ "stg_messagePromise" + ++ ffiType res_ty unsafeDupablePerformIO_id <- lookupGhcInternalVarId "GHC.Internal.IO.Unsafe" @@ -326,7 +341,6 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do rhs <- importBindingRHS mUnitId - PlaySafe cfun_name tvs arg_tys @@ -350,19 +364,14 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do [ Type res_ty, mkApps (Var blockPromise_id) - [Type res_ty, Var promise_id, Var msgPromise_id] + [Type res_ty, err_msg, Var promise_id, Var msgPromise_id] ] ] ) pure ( [(fn_id, Cast rhs co)], CHeader commonCDecls, - importCStub - PlaySafe - cfun_name - (map scaledThing arg_tys) - jsval_ty - js_src + importCStub Async cfun_name (map scaledThing arg_tys) jsval_ty js_src ) uniqueCFunName :: DsM FastString @@ -372,92 +381,91 @@ uniqueCFunName = do importBindingRHS :: Maybe Unit -> - Safety -> FastString -> [TyVar] -> [Scaled Type] -> Type -> (CoreExpr -> CoreExpr) -> DsM CoreExpr -importBindingRHS mUnitId safety cfun_name tvs arg_tys orig_res_ty res_trans = - do - ccall_uniq <- newUnique - args_unevaled <- newSysLocalsDs arg_tys - args_evaled <- newSysLocalsDs arg_tys - -- ccall_action_ty: type of the_call, State# RealWorld -> (# State# RealWorld, a #) - -- res_wrapper: turn the_call to (IO a) or a - (ccall_action_ty, res_wrapper) <- case tcSplitIOType_maybe orig_res_ty of - Just (io_tycon, res_ty) -> do - s0_id <- newSysLocalMDs realWorldStatePrimTy - s1_id <- newSysLocalMDs realWorldStatePrimTy - let io_data_con = tyConSingleDataCon io_tycon - toIOCon = dataConWorkId io_data_con - (ccall_res_ty, wrap) - | res_ty `eqType` unitTy = - ( mkTupleTy Unboxed [realWorldStatePrimTy], - \the_call -> - mkApps - (Var toIOCon) - [ Type res_ty, - Lam s0_id - $ mkWildCase - (App the_call (Var s0_id)) - (unrestricted ccall_res_ty) - (mkTupleTy Unboxed [realWorldStatePrimTy, unitTy]) - [ Alt - (DataAlt (tupleDataCon Unboxed 1)) - [s1_id] - (mkCoreUnboxedTuple [Var s1_id, unitExpr]) - ] - ] - ) - | otherwise = - ( mkTupleTy Unboxed [realWorldStatePrimTy, res_ty], - \the_call -> mkApps (Var toIOCon) [Type res_ty, the_call] - ) - pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) - Nothing -> do - unsafeDupablePerformIO_id <- - lookupGhcInternalVarId - "GHC.Internal.IO.Unsafe" - "unsafeDupablePerformIO" - io_data_con <- dsLookupDataCon ioDataConName - let ccall_res_ty = - mkTupleTy Unboxed [realWorldStatePrimTy, orig_res_ty] - toIOCon = dataConWorkId io_data_con - wrap the_call = - mkApps - (Var unsafeDupablePerformIO_id) - [ Type orig_res_ty, - mkApps (Var toIOCon) [Type orig_res_ty, the_call] - ] - pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) - let cfun_fcall = - CCall - ( CCallSpec - (StaticTarget NoSourceText cfun_name mUnitId True) - CCallConv - safety - ) - call_app = - mkFCall ccall_uniq cfun_fcall (map Var args_evaled) ccall_action_ty - rhs = - mkCoreLams (tvs ++ args_unevaled) - $ foldr - (\(arg_u, arg_e) acc -> mkDefaultCase (Var arg_u) arg_e acc) - -- res_trans transforms the result. When desugaring - -- JSFFI sync imports, the result is just (IO a) or a, - -- and res_trans is id; for async cases, the result is - -- always (IO JSVal), and res_trans will wrap it in a - -- thunk that has the original return type. This way, we - -- can reuse most of the RHS generation logic for both - -- sync/async imports. - (res_trans $ res_wrapper call_app) - (zip args_unevaled args_evaled) - pure rhs - -importCStub :: Safety -> FastString -> [Type] -> Type -> String -> CStub -importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] +importBindingRHS mUnitId cfun_name tvs arg_tys orig_res_ty res_trans = do + ccall_uniq <- newUnique + args_unevaled <- newSysLocalsDs arg_tys + args_evaled <- newSysLocalsDs arg_tys + -- ccall_action_ty: type of the_call, State# RealWorld -> (# State# RealWorld, a #) + -- res_wrapper: turn the_call to (IO a) or a + (ccall_action_ty, res_wrapper) <- case tcSplitIOType_maybe orig_res_ty of + Just (io_tycon, res_ty) -> do + s0_id <- newSysLocalMDs realWorldStatePrimTy + s1_id <- newSysLocalMDs realWorldStatePrimTy + let io_data_con = tyConSingleDataCon io_tycon + toIOCon = dataConWorkId io_data_con + (ccall_res_ty, wrap) + | res_ty `eqType` unitTy = + ( mkTupleTy Unboxed [realWorldStatePrimTy], + \the_call -> + mkApps + (Var toIOCon) + [ Type res_ty, + Lam s0_id + $ mkWildCase + (App the_call (Var s0_id)) + (unrestricted ccall_res_ty) + (mkTupleTy Unboxed [realWorldStatePrimTy, unitTy]) + [ Alt + (DataAlt (tupleDataCon Unboxed 1)) + [s1_id] + (mkCoreUnboxedTuple [Var s1_id, unitExpr]) + ] + ] + ) + | otherwise = + ( mkTupleTy Unboxed [realWorldStatePrimTy, res_ty], + \the_call -> mkApps (Var toIOCon) [Type res_ty, the_call] + ) + pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) + Nothing -> do + unsafeDupablePerformIO_id <- + lookupGhcInternalVarId + "GHC.Internal.IO.Unsafe" + "unsafeDupablePerformIO" + io_data_con <- dsLookupDataCon ioDataConName + let ccall_res_ty = mkTupleTy Unboxed [realWorldStatePrimTy, orig_res_ty] + toIOCon = dataConWorkId io_data_con + wrap the_call = + mkApps + (Var unsafeDupablePerformIO_id) + [ Type orig_res_ty, + mkApps (Var toIOCon) [Type orig_res_ty, the_call] + ] + pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) + let cfun_fcall = + CCall + ( CCallSpec + (StaticTarget NoSourceText cfun_name mUnitId True) + CCallConv + -- Same even for foreign import javascript unsafe, for + -- the sake of re-entrancy. + PlaySafe + ) + call_app = + mkFCall ccall_uniq cfun_fcall (map Var args_evaled) ccall_action_ty + rhs = + mkCoreLams (tvs ++ args_unevaled) + $ foldr + (\(arg_u, arg_e) acc -> mkDefaultCase (Var arg_u) arg_e acc) + -- res_trans transforms the result. When desugaring + -- JSFFI sync imports, the result is just (IO a) or a, + -- and res_trans is id; for async cases, the result is + -- always (IO JSVal), and res_trans will wrap it in a + -- thunk that has the original return type. This way, we + -- can reuse most of the RHS generation logic for both + -- sync/async imports. + (res_trans $ res_wrapper call_app) + (zip args_unevaled args_evaled) + pure rhs + +importCStub :: Synchronicity -> FastString -> [Type] -> Type -> String -> CStub +importCStub sync cfun_name arg_tys res_ty js_src = CStub c_doc [] [] where import_name = fromJust $ stripPrefix "ghczuwasmzujsffi" (unpackFS cfun_name) import_asm = @@ -465,18 +473,18 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] <> parens ( vcat [ text (show l) - | l <- - [ ".section .custom_section.ghc_wasm_jsffi,\"\",@\n", - ".asciz \"" ++ import_name ++ "\"\n", - ".asciz \"" - ++ ( case safety of - PlayRisky -> "(" - _ -> "async (" - ) - ++ intercalate "," ["$" ++ show i | i <- [1 .. length arg_tys]] - ++ ")\"\n", - ".asciz " ++ show js_src ++ "\n" - ] + | l <- + [ ".section .custom_section.ghc_wasm_jsffi,\"\",@\n", + ".asciz \"" ++ import_name ++ "\"\n", + ".asciz \"" + ++ ( case sync of + Sync -> "(" + Async -> "async (" + ) + ++ intercalate "," ["$" ++ show i | i <- [1 .. length arg_tys]] + ++ ")\"\n", + ".asciz " ++ show js_src ++ "\n" + ] ] ) <> semi @@ -488,8 +496,8 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] ( punctuate comma [ text k <> parens (doubleQuotes (text v)) - | (k, v) <- - [("import_module", "ghc_wasm_jsffi"), ("import_name", import_name)] + | (k, v) <- + [("import_module", "ghc_wasm_jsffi"), ("import_name", import_name)] ] ) ) @@ -501,7 +509,7 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] | otherwise = text ("Hs" ++ ffiType res_ty) import_arg_list = [ text ("Hs" ++ ffiType arg_ty) <+> char 'a' <> int i - | (i, arg_ty) <- zip [1 ..] arg_tys + | (i, arg_ty) <- zip [1 ..] arg_tys ] import_args = case import_arg_list of [] -> text "void" @@ -528,7 +536,7 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] ( punctuate comma [ cfun_make_arg arg_ty (char 'a' <> int n) - | (arg_ty, n) <- zip arg_tys [1 ..] + | (arg_ty, n) <- zip arg_tys [1 ..] ] ) ) @@ -554,7 +562,8 @@ Note [Desugaring JSFFI static export] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A JSFFI static export wraps a top-level Haskell binding as a wasm -module export that can be called in JavaScript as an async function: +module export that can be called in JavaScript as an async/sync +function: foreign export javascript "plus" (+) :: Int -> Int -> Int @@ -565,32 +574,27 @@ stub for a JSFFI export as well: __attribute__((export_name("plus"))) HsJSVal plus(HsInt a1, HsInt a2) { ... } +The generated C stub function would be exported as __exports.plus and +can be called in JavaScript. By default, it's exported as an async +function, so the C stub would always return an HsJSVal which +represents the result Promise; in case of a sync export (using "plus +sync" instead of "plus"), it returns the original result type. + +The C stub function body applies the function closure to arguments, +wrap it with a runIO/runNonIO top handler function, then schedules +Haskell computation to happen, then fetches the result. In case of an +async export, the top handler creates a JavaScript Promise that stands +for Haskell evaluation result, and the Promise will eventually be +resolved with the result or rejected with an exception. That Promise +is what we return in the C stub function. See +Note [Async JSFFI scheduler] for detailed explanation. + At link time, you need to pass -optl-Wl,--export=plus,--export=... to specify your entrypoint function symbols as roots of wasm-ld link-time garbage collection. As for the auto-generated exports when desugaring the JSFFI dynamic exports, they will be transitively included as well due to the export_name attribute. -For each JSFFI static export, we create an internal worker function -which takes the same arguments as the exported Haskell binding, but -always returns (IO JSVal). Its RHS simply applies the arguments to the -original binding, then applies a runIO/runNonIO top handler function -to the result. The top handler creates a JavaScript Promise that -stands for Haskell evaluation result, schedules Haskell computation to -happen, and the Promise will eventually be resolved with the result or -rejected with an exception. That Promise is what we return in the C -stub function. See Note [Async JSFFI scheduler] for detailed -explanation. - -There's nothing else to explain about the C stub function body; just -like C FFI exports, it calls rts_mk* to box the arguments, rts_apply -to apply them to the worker function, evaluates the result, then -unboxes the resulting Promise using rts_getJSVal and returns it. - -Now, in JavaScript, once the wasm instance is initialized, you can -directly call these exports and await them, as if they're real -JavaScript async functions. - -} dsWasmJSExport :: @@ -598,108 +602,140 @@ dsWasmJSExport :: Coercion -> CLabelString -> DsM (CHeader, CStub, String, [Id], [Binding]) -dsWasmJSExport fn_id co ext_name = do - work_uniq <- newUnique +dsWasmJSExport fn_id co str = dsWasmJSExport' sync (Just fn_id) co ext_name + where + (sync, ext_name) = case words $ unpackFS str of + [ext_name] -> (Async, ext_name) + [ext_name, "sync"] -> (Sync, ext_name) + _ -> panic "dsWasmJSExport: unrecognized label string" + +dsWasmJSExport' :: + Synchronicity -> + Maybe Id -> + Coercion -> + String -> + DsM (CHeader, CStub, String, [Id], [Binding]) +dsWasmJSExport' sync m_fn_id co ext_name = do let ty = coercionRKind co - (tvs, fun_ty) = tcSplitForAllInvisTyVars ty + (_, fun_ty) = tcSplitForAllInvisTyVars ty (arg_tys, orig_res_ty) = tcSplitFunTys fun_ty (res_ty, is_io) = case tcSplitIOType_maybe orig_res_ty of Just (_, res_ty) -> (res_ty, True) Nothing -> (orig_res_ty, False) - (_, res_ty_args) = splitTyConApp res_ty res_ty_str = ffiType res_ty - args <- newSysLocalsDs arg_tys + top_handler_mod = case sync of + Sync -> "GHC.Internal.TopHandler" + Async -> "GHC.Internal.Wasm.Prim.Exports" + top_handler_name + | is_io = "runIO" + | otherwise = "runNonIO" + -- In case of sync export, we use the normal C FFI tophandler + -- functions. They would call flushStdHandles in case of uncaught + -- exception but not in normal cases, but we want flushStdHandles to + -- be called so that there are less run-time surprises for users, + -- and that's what our tophandler functions already do. + -- + -- So for each sync export, we first wrap the computation with a C + -- FFI tophandler, and then sequence it with flushStdHandles using + -- (<*) :: IO a -> IO b -> IO a. But it's trickier to call (<*) + -- using RTS API given type class dictionary is involved, so we'll + -- just use finally. + finally_id <- + lookupGhcInternalVarId + "GHC.Internal.Control.Exception.Base" + "finally" + flushStdHandles_id <- + lookupGhcInternalVarId + "GHC.Internal.TopHandler" + "flushStdHandles" promiseRes_id <- - lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" $ "js_promiseResolve" ++ res_ty_str - runIO_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "runIO" - runNonIO_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "runNonIO" - let work_id = - mkExportedVanillaId - ( mkExternalName - work_uniq - (nameModule $ getName fn_id) - (mkVarOcc $ "jsffi_" ++ occNameString (getOccName fn_id)) - generatedSrcSpan - ) - (exprType work_rhs) - work_rhs = - mkCoreLams (tvs ++ args) - $ mkApps - (Var $ if is_io then runIO_id else runNonIO_id) - [ Type res_ty, - mkApps (Var promiseRes_id) $ map Type res_ty_args, - mkApps (Cast (Var fn_id) co) - $ map (Type . mkTyVarTy) tvs - ++ map Var args - ] - work_closure = ppr work_id <> text "_closure" - work_closure_decl = text "extern StgClosure" <+> work_closure <> semi + lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" + $ "js_promiseResolve" + ++ res_ty_str + top_handler_id <- lookupGhcInternalVarId top_handler_mod top_handler_name + let ppr_closure c = ppr c <> text "_closure" + mk_extern_closure_decl c = + text "extern StgClosure" <+> ppr_closure c <> semi + gc_root_closures = maybeToList m_fn_id ++ case sync of + -- In case of C FFI top handlers, they are already declared in + -- RtsAPI.h and registered as GC roots in initBuiltinGcRoots. + -- flushStdHandles is already registered but somehow the C + -- stub can't access its declaration, won't hurt to declare it + -- again here. + Sync -> [finally_id, flushStdHandles_id] + Async -> [top_handler_id, promiseRes_id] + extern_closure_decls = vcat $ map mk_extern_closure_decl gc_root_closures cstub_attr = text "__attribute__" <> parens - (parens $ text "export_name" <> parens (doubleQuotes $ ftext ext_name)) + (parens $ text "export_name" <> parens (doubleQuotes $ text ext_name)) cstub_arg_list = [ text ("Hs" ++ ffiType (scaledThing arg_ty)) <+> char 'a' <> int i - | (i, arg_ty) <- zip [1 ..] arg_tys + | (i, arg_ty) <- zip [1 ..] arg_tys ] cstub_args = case cstub_arg_list of [] -> text "void" _ -> hsep $ punctuate comma cstub_arg_list - cstub_proto = text "HsJSVal" <+> ftext ext_name <> parens cstub_args + cstub_proto + | Sync <- sync, + res_ty `eqType` unitTy = + text "void" <+> text ext_name <> parens cstub_args + | Sync <- sync = + text ("Hs" ++ res_ty_str) <+> text ext_name <> parens cstub_args + | Async <- sync = + text "HsJSVal" <+> text ext_name <> parens cstub_args + c_closure c = char '&' <> ppr_closure c + c_call fn args = text fn <> parens (hsep $ punctuate comma args) + c_rts_apply = + Data.List.foldl1' $ \fn arg -> c_call "rts_apply" [text "cap", fn, arg] + apply_top_handler expr = case sync of + Sync -> + c_rts_apply + [ c_closure finally_id, + c_rts_apply [c_closure top_handler_id, expr], + c_closure flushStdHandles_id + ] + Async -> + c_rts_apply [c_closure top_handler_id, c_closure promiseRes_id, expr] + cstub_ret + | Sync <- sync, res_ty `eqType` unitTy = empty + | Sync <- sync = text $ "return rts_get" ++ res_ty_str ++ "(ret);" + | Async <- sync = text "return rts_getJSVal(ret);" + (cstub_target, real_args) + | Just fn_id <- m_fn_id = (c_closure fn_id, zip [1 ..] arg_tys) + | otherwise = (text "(HaskellObj)deRefStablePtr(a1)", zip [2 ..] $ tail arg_tys) cstub_body = vcat [ lbrace, text "Capability *cap = rts_lock();", text "HaskellObj ret;", - -- rts_evalLazyIO is fine, the top handler always returns - -- an evaluated result - text "rts_evalLazyIO" - <> parens - ( hsep - $ punctuate - comma - [ text "&cap", - foldl' - ( \acc (i, arg_ty) -> - text "rts_apply" - <> parens - ( hsep - $ punctuate - comma - [ text "cap", - acc, - text ("rts_mk" ++ ffiType (scaledThing arg_ty)) - <> parens - (hsep $ punctuate comma [text "cap", char 'a' <> int i]) - ] - ) - ) - (char '&' <> work_closure) - $ zip [1 ..] arg_tys, - text "&ret" - ] - ) + c_call + "rts_inCall" + [ text "&cap", + apply_top_handler + $ c_rts_apply + $ cstub_target + : [ c_call + ("rts_mk" ++ ffiType (scaledThing arg_ty)) + [text "cap", char 'a' <> int i] + | (i, arg_ty) <- real_args + ], + text "&ret" + ] <> semi, - text "rts_checkSchedStatus" - <> parens (doubleQuotes (ftext ext_name) <> comma <> text "cap") + c_call "rts_checkSchedStatus" [doubleQuotes (text ext_name), text "cap"] <> semi, text "rts_unlock(cap);", - text "return rts_getJSVal(ret);", + cstub_ret, rbrace ] cstub = commonCDecls - $+$ work_closure_decl + $+$ extern_closure_decls $+$ cstub_attr $+$ cstub_proto $+$ cstub_body - pure - ( CHeader commonCDecls, - CStub cstub [] [], - "", - [work_id], - [(work_id, work_rhs)] - ) + pure (CHeader commonCDecls, CStub cstub [] [], "", gc_root_closures, []) lookupGhcInternalVarId :: FastString -> String -> DsM Id lookupGhcInternalVarId m v = do ===================================== compiler/GHC/Settings/IO.hs ===================================== @@ -168,6 +168,7 @@ initSettings top_dir = do lc_prog <- getSetting "LLVM llc command" lo_prog <- getSetting "LLVM opt command" las_prog <- getSetting "LLVM llvm-as command" + las_args <- map Option . unescapeArgs <$> getSetting "LLVM llvm-as flags" let iserv_prog = libexec "ghc-iserv" @@ -225,7 +226,7 @@ initSettings top_dir = do , toolSettings_pgm_ranlib = ranlib_path , toolSettings_pgm_lo = (lo_prog,[]) , toolSettings_pgm_lc = (lc_prog,[]) - , toolSettings_pgm_las = (las_prog, []) + , toolSettings_pgm_las = (las_prog, las_args) , toolSettings_pgm_i = iserv_prog , toolSettings_opt_L = [] , toolSettings_opt_P = [] ===================================== compiler/GHC/SysTools/Tasks.hs ===================================== @@ -7,7 +7,26 @@ -- (c) The GHC Team 2017 -- ----------------------------------------------------------------------------- -module GHC.SysTools.Tasks where +module GHC.SysTools.Tasks + ( runUnlit + , SourceCodePreprocessor(..) + , runSourceCodePreprocessor + , runPp + , runCc + , askLd + , runAs + , runLlvmOpt + , runLlvmLlc + , runLlvmAs + , runEmscripten + , figureLlvmVersion + , runMergeObjects + , runAr + , askOtool + , runInstallNameTool + , runRanlib + , runWindres + ) where import GHC.Prelude import GHC.ForeignSrcLang ===================================== compiler/GHC/Tc/Gen/Foreign.hs ===================================== @@ -78,7 +78,7 @@ import GHC.Data.Bag import GHC.Driver.Hooks import qualified GHC.LanguageExtensions as LangExt -import Control.Monad ( zipWithM ) +import Control.Monad ( when, zipWithM ) import Control.Monad.Trans.Writer.CPS ( WriterT, runWriterT, tell ) import Control.Monad.Trans.Class @@ -444,7 +444,7 @@ tcFExport d = pprPanic "tcFExport" (ppr d) tcCheckFEType :: Type -> ForeignExport GhcRn -> TcM (ForeignExport GhcTc) tcCheckFEType sig_ty edecl@(CExport src (L l (CExportStatic esrc str cconv))) = do checkCg (Left edecl) backendValidityOfCExport - checkTc (isCLabelString str) (TcRnInvalidCIdentifier str) + when (cconv /= JavaScriptCallConv) $ checkTc (isCLabelString str) (TcRnInvalidCIdentifier str) cconv' <- checkCConv (Left edecl) cconv checkForeignArgs isFFIExternalTy arg_tys checkForeignRes nonIOok noCheckSafe isFFIExportResultTy res_ty ===================================== distrib/configure.ac.in ===================================== @@ -214,6 +214,13 @@ FIND_LLVM_PROG([LLVMAS], [clang], [$LlvmMinVersion], [$LlvmMaxVersion]) LlvmAsCmd="$LLVMAS" AC_SUBST([LlvmAsCmd]) +dnl We know that `clang` supports `--target` and it is necessary to pass it +dnl lest we see #25793. +if test -z "$LlvmAsFlags" ; then + LlvmAsFlags="--target=$LlvmTarget" +fi +AC_SUBST([LlvmAsFlags]) + dnl ** Check gcc version and flags we need to pass it ** FP_GCC_VERSION FP_GCC_SUPPORTS_NO_PIE ===================================== docs/users_guide/wasm.rst ===================================== @@ -231,15 +231,15 @@ There are two kinds of JSFFI imports: synchronous/asynchronous imports. ``unsafe`` indicates synchronous imports, which has the following caveats: -- The calling thread as well as the entire runtime blocks on waiting - for the import result. -- If the JavaScript code throws, the runtime crashes with the same - error. A JavaScript exception cannot be handled as a Haskell - exception here, so you need to use a JavaScript ``catch`` explicitly - shall the need arise. -- Like ``unsafe`` C imports, re-entrance is not supported, the imported - foreign code must not call into Haskell again. Doing so would result - in a runtime panic. +- The calling thread as well as the entire runtime blocks on waiting for + the import result. +- If the JavaScript code throws, the runtime crashes with the same + error. A JavaScript exception cannot be handled as a Haskell exception + here, so you need to use a JavaScript ``catch`` explicitly shall the + need arise. +- Unlike ``unsafe`` C imports, re-entrance is actually supported, the + imported JavaScript code can call into Haskell again, provided that + Haskell function is exported as a synchronous one. When a JSFFI import is marked as ``safe`` / ``interruptible`` or lacks safety annotation, then it’s treated as an asynchronous import. The @@ -274,14 +274,12 @@ runtime, and resumed when the ``Promise`` actually resolves or rejects. Compared to synchronous JSFFI imports, asynchronous JSFFI imports have the following notable pros/cons: -- Waiting for the result only blocks a single Haskell thread, other - threads can still make progress and garbage collection may still - happen. -- If the ``Promise`` rejects, Haskell code can catch JavaScript errors - as ``JSException``\ s. -- Re-entrance is supported. The JavaScript code may call into Haskell - again and vice versa. -- Of course, it has higher overhead than synchronous JSFFI imports. +- Waiting for the result only blocks a single Haskell thread, other + threads can still make progress and garbage collection may still + happen. +- If the ``Promise`` rejects, Haskell code can catch JavaScript errors + as ``JSException``\ s. +- It has higher overhead than synchronous JSFFI imports. Using thunks to encapsulate ``Promise`` result allows cheaper concurrency without even needing to fork Haskell threads just for @@ -345,12 +343,17 @@ wrapper, and as long as the wasm instance is properly initialized, you can call ``await instance.exports.my_fib(10)`` to invoke the exported Haskell function and get the result. -Unlike JSFFI imports which have synchronous/asynchronous flavors, JSFFI -exports are always asynchronous. Calling them always return a -``Promise`` in JavaScript that needs to be ``await``\ ed for the real -result. If the Haskell function throws, the ``Promise`` is rejected with -a ``WebAssembly.RuntimeError``, and the ``message`` field contains a -JavaScript string of the Haskell exception. +JSFFI exports are asynchronous by default. Calling an async export +return a ``Promise`` in JavaScript that needs to be ``await``\ ed for +the real result. If the Haskell function throws, the ``Promise`` is +rejected with a ``WebAssembly.RuntimeError``, and the ``message`` field +contains a JavaScript string of the Haskell exception. + +Additionally, sync exports are also supported by using ``"my_fib sync"`` +instead of ``"my_fib"``. With ``sync`` added alongside export function +name, the JavaScript function would return the result synchronously. For +the time being, sync exports don’t support propagating uncaught Haskell +exception to a JavaScript exception at the call site yet. Above is the static flavor of JSFFI exports. It’s also possible to export a dynamically created Haskell function closure as a JavaScript @@ -366,8 +369,9 @@ function and obtain its ``JSVal``: This is also much like ``foreign import ccall "wrapper"``, which wraps a Haskell function closure as a C function pointer. Note that ``unsafe`` / ``safe`` annotation is ignored here, since the ``JSVal`` that represent -the exported function is always returned synchronously, but it is always -an asynchronous JavaScript function, just like static JSFFI exports. +the exported function is always returned synchronously. Likewise, you +can use ``"wrapper sync"`` instead of ``"wrapper"`` to indicate the +returned JavaScript function is sync instead of async. The ``JSVal`` callbacks created by dynamic JSFFI exports can be passed to the rest of JavaScript world to be invoked later. But wait, didn’t we ===================================== hadrian/bindist/Makefile ===================================== @@ -131,6 +131,7 @@ lib/settings : config.mk @echo ',("LLVM llc command", "$(SettingsLlcCommand)")' >> $@ @echo ',("LLVM opt command", "$(SettingsOptCommand)")' >> $@ @echo ',("LLVM llvm-as command", "$(SettingsLlvmAsCommand)")' >> $@ + @echo ',("LLVM llvm-as flags", "$(SettingsLlvmAsFlags)")' >> $@ @echo ',("Use inplace MinGW toolchain", "$(SettingsUseDistroMINGW)")' >> $@ @echo @echo ',("target RTS linker only supports shared libraries", "$(TargetRTSLinkerOnlySupportsSharedLibs)")' >> $@ ===================================== hadrian/cfg/system.config.in ===================================== @@ -85,6 +85,7 @@ settings-install_name_tool-command = @SettingsInstallNameToolCommand@ settings-llc-command = @SettingsLlcCommand@ settings-opt-command = @SettingsOptCommand@ settings-llvm-as-command = @SettingsLlvmAsCommand@ +settings-llvm-as-flags = @SettingsLlvmAsFlags@ settings-use-distro-mingw = @SettingsUseDistroMINGW@ target-has-libm = @TargetHasLibm@ ===================================== hadrian/src/Oracles/Setting.hs ===================================== @@ -91,6 +91,7 @@ data ToolchainSetting | ToolchainSetting_LlcCommand | ToolchainSetting_OptCommand | ToolchainSetting_LlvmAsCommand + | ToolchainSetting_LlvmAsFlags | ToolchainSetting_DistroMinGW -- | Look up the value of a 'Setting' in @cfg/system.config@, tracking the @@ -144,6 +145,7 @@ settingsFileSetting key = lookupSystemConfig $ case key of ToolchainSetting_LlcCommand -> "settings-llc-command" ToolchainSetting_OptCommand -> "settings-opt-command" ToolchainSetting_LlvmAsCommand -> "settings-llvm-as-command" + ToolchainSetting_LlvmAsFlags -> "settings-llvm-as-flags" ToolchainSetting_DistroMinGW -> "settings-use-distro-mingw" -- ROMES:TODO: This option doesn't seem to be in ghc-toolchain yet. It corresponds to EnableDistroToolchain -- | An expression that looks up the value of a 'Setting' in @cfg/system.config@, ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -528,6 +528,7 @@ generateSettings settingsFile = do , ("LLVM llc command", expr $ settingsFileSetting ToolchainSetting_LlcCommand) , ("LLVM opt command", expr $ settingsFileSetting ToolchainSetting_OptCommand) , ("LLVM llvm-as command", expr $ settingsFileSetting ToolchainSetting_LlvmAsCommand) + , ("LLVM llvm-as flags", expr $ settingsFileSetting ToolchainSetting_LlvmAsFlags) , ("Use inplace MinGW toolchain", expr $ settingsFileSetting ToolchainSetting_DistroMinGW) , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs) ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -79,9 +79,9 @@ filled is generated via raiseJSException. -} -stg_blockPromise :: JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r -stg_blockPromise p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> - case stg_jsffi_check (unsafeCoerce# $ toException WouldBlockException) s0 of +stg_blockPromise :: String -> JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r +stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> + case stg_jsffi_check (unsafeCoerce# $ toException $ WouldBlockException err_msg) s0 of (# s1 #) -> case myThreadId# s1 of (# s2, tso #) -> case makeStablePtr# tso s2 of (# s3, sp #) -> ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -139,8 +139,8 @@ foreign import javascript unsafe "`${$1.stack ? $1.stack : $1}`" instance Exception JSException -data WouldBlockException - = WouldBlockException +newtype WouldBlockException + = WouldBlockException String deriving (Show) instance Exception WouldBlockException ===================================== m4/fp_settings.m4 ===================================== @@ -89,6 +89,7 @@ AC_DEFUN([FP_SETTINGS], SettingsLlcCommand="$LlcCmd" SettingsOptCommand="$OptCmd" SettingsLlvmAsCommand="$LlvmAsCmd" + SettingsLlvmAsFlags="$LlvmAsCmd" if test "$EnableDistroToolchain" = "YES"; then # If the user specified --enable-distro-toolchain then we just use the @@ -131,6 +132,7 @@ AC_DEFUN([FP_SETTINGS], SUBST_TOOLDIR([SettingsLlcCommand]) SUBST_TOOLDIR([SettingsOptCommand]) SUBST_TOOLDIR([SettingsLlvmAsCommand]) + SUBST_TOOLDIR([SettingsLlvmAsFlags]) fi # Mac-only tools @@ -171,5 +173,6 @@ AC_DEFUN([FP_SETTINGS], AC_SUBST(SettingsLlcCommand) AC_SUBST(SettingsOptCommand) AC_SUBST(SettingsLlvmAsCommand) + AC_SUBST(SettingsLlvmAsFlags) AC_SUBST(SettingsUseDistroMINGW) ]) ===================================== rts/include/RtsAPI.h ===================================== @@ -587,15 +587,15 @@ void rts_done (void); // the base package itself. // #if defined(COMPILING_WINDOWS_DLL) && !defined(COMPILING_GHC_INTERNAL_PACKAGE) -__declspec(dllimport) extern StgWord ghczminternal_GHCziInternalziTopHandler_runIO_closure[]; -__declspec(dllimport) extern StgWord ghczminternal_GHCziInternalziTopHandler_runNonIO_closure[]; +__declspec(dllimport) extern StgClosure ghczminternal_GHCziInternalziTopHandler_runIO_closure; +__declspec(dllimport) extern StgClosure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure; #else -extern StgWord ghczminternal_GHCziInternalziTopHandler_runIO_closure[]; -extern StgWord ghczminternal_GHCziInternalziTopHandler_runNonIO_closure[]; +extern StgClosure ghczminternal_GHCziInternalziTopHandler_runIO_closure; +extern StgClosure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure; #endif -#define runIO_closure ghczminternal_GHCziInternalziTopHandler_runIO_closure -#define runNonIO_closure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure +#define runIO_closure DLL_IMPORT_DATA_REF(ghczminternal_GHCziInternalziTopHandler_runIO_closure) +#define runNonIO_closure DLL_IMPORT_DATA_REF(ghczminternal_GHCziInternalziTopHandler_runNonIO_closure) /* ------------------------------------------------------------------------ */ ===================================== testsuite/tests/jsffi/jsffigc.hs ===================================== @@ -10,17 +10,16 @@ import System.Mem type BinOp a = a -> a -> a -foreign import javascript "wrapper" +foreign import javascript "wrapper sync" js_from_hs :: BinOp Int -> IO JSVal --- This must be safe since we intend to call back into Haskell again. -foreign import javascript safe "dynamic" +foreign import javascript unsafe "dynamic" js_to_hs :: JSVal -> BinOp Int foreign import javascript "wrapper" js_mk_cont :: IO () -> IO JSVal -foreign export javascript "testDynExportFree" +foreign export javascript "testDynExportFree sync" testDynExportFree :: Int -> Int -> Int -> IO () -- JSVal uses Weak# under the hood for garbage collection support, ===================================== testsuite/tests/jsffi/jsffigc.mjs ===================================== @@ -8,7 +8,7 @@ async function reallyGC() { } export default async (__exports) => { - await __exports.testDynExportFree(114, 514, 1919810); + __exports.testDynExportFree(114, 514, 1919810); const cont = await __exports.testDynExportGC(114, 514, 1919810); await reallyGC(); ===================================== testsuite/tests/jsffi/jsffisleep.hs ===================================== @@ -20,8 +20,8 @@ foreign export ccall "testWouldBlock" -- non-main exports in C FFI. In JSFFI, it's always done automatically -- for every export though. testWouldBlock :: IO () -testWouldBlock = catch (threadDelay 1000000) $ \WouldBlockException -> do - print WouldBlockException +testWouldBlock = catch (threadDelay 1000000) $ \(WouldBlockException err) -> do + print $ WouldBlockException err flushStdHandles foreign export javascript "testLazySleep" ===================================== testsuite/tests/jsffi/jsffisleep.stdout ===================================== @@ -1,4 +1,4 @@ -WouldBlockException +WouldBlockException "new Promise(res => setTimeout(res, $1 / 1000))" zzzzzzz i sleep Left thread killed ===================================== testsuite/tests/jsffi/textconv.hs ===================================== @@ -45,7 +45,7 @@ textToJSString (Text (ByteArray ba#) (I# off#) (I# len#)) = unsafeDupablePerform (# s1, mba# #) -> case copyByteArray# ba# off# mba# 0# len# s1 of s2 -> keepAlive# mba# s2 $ unIO $ js_to_str (Ptr (mutableByteArrayContents# mba#)) $ I# len# -foreign export javascript "main" +foreign export javascript "main sync" main :: IO () main :: IO () ===================================== testsuite/tests/jsffi/textconv.mjs ===================================== @@ -1,3 +1,3 @@ -export default async (__exports) => { - await __exports.main(); +export default (__exports) => { + __exports.main(); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/75248fe7b32dbf61228e17731cf47a66adbdde78...3add7dc2927050afdefa75f44228a3d4e62d706d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/75248fe7b32dbf61228e17731cf47a66adbdde78...3add7dc2927050afdefa75f44228a3d4e62d706d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/f9392aad/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 11:20:59 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 03 Mar 2025 06:20:59 -0500 Subject: [Git][ghc/ghc][wip/mi_top_env_serialise] 5 commits: Do not deallocate stack for jump/switch table jumps Message-ID: <67c5909b88461_1f81a015c750717a6@gitlab.mail> Matthew Pickering pushed to branch wip/mi_top_env_serialise at Glasgow Haskell Compiler / GHC Commits: a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - d65b3e87 by Matthew Pickering at 2025-03-03T11:20:35+00:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 3f3648db by Matthew Pickering at 2025-03-03T11:20:35+00:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 113 changed files: - compiler/GHC.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - ghc/GHCi/UI.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/02860e424473722a4a8922cae80a2ef49a6a98bf...3f3648db1937e97752b0010e2a5871a5a4391b41 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/02860e424473722a4a8922cae80a2ef49a6a98bf...3f3648db1937e97752b0010e2a5871a5a4391b41 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/1c2aaffd/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 11:48:01 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 03 Mar 2025 06:48:01 -0500 Subject: [Git][ghc/ghc][wip/mi_top_env_serialise] Apply 2 suggestion(s) to 2 file(s) Message-ID: <67c596f12e2c9_1f81a04b4e70774f4@gitlab.mail> Matthew Pickering pushed to branch wip/mi_top_env_serialise at Glasgow Haskell Compiler / GHC Commits: 1af21fd6 by Matthew Pickering at 2025-03-03T11:47:58+00:00 Apply 2 suggestion(s) to 2 file(s) Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - 2 changed files: - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Types/PkgQual.hs Changes: ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -152,9 +152,10 @@ instance Binary ImpIfaceList where 1 -> do env <- get bh return (ImpIfaceExplicit env) - _ -> do + 2 -> do ns <- get @[Name] bh return (ImpIfaceEverythingBut ns) + _ -> fail "instance Binary ImpIfaceList: Invalid tag" -- | A binding top-level 'Name' in an interface file (e.g. the name of an -- 'IfaceDecl'). ===================================== compiler/GHC/Types/PkgQual.hs ===================================== @@ -54,7 +54,7 @@ instance Binary PkgQual where 0 -> return NoPkgQual 1 -> do u <- get bh return (ThisPkg u) - _ -> do u <- get bh + 2 -> do u <- get bh return (OtherPkg u) - + _ -> fail "instance Binary PkgQual: Invalid tag" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1af21fd68dce20985cdb6701cfeb926a8f631884 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1af21fd68dce20985cdb6701cfeb926a8f631884 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/0e708347/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 11:51:56 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 03 Mar 2025 06:51:56 -0500 Subject: [Git][ghc/ghc][wip/mi_top_env_serialise] 5 commits: compiler: Add export list to GHC.SysTools.Tasks Message-ID: <67c597dc924d6_1f81a025344c8099c@gitlab.mail> Matthew Pickering pushed to branch wip/mi_top_env_serialise at Glasgow Haskell Compiler / GHC Commits: 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - edef8db7 by Matthew Pickering at 2025-03-03T11:51:31+00:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - a5de39de by Matthew Pickering at 2025-03-03T11:51:31+00:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 26 changed files: - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModIface.hs - distrib/configure.ac.in - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - m4/fp_settings.m4 - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T Changes: ===================================== compiler/GHC/Cmm/Opt.hs ===================================== @@ -63,18 +63,23 @@ cmmMachOpFoldM _ (MO_VF_Broadcast lg _w) exprs = [CmmLit l] -> Just $! CmmLit (CmmVec $ replicate lg l) _ -> Nothing cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] - = Just $! case op of - MO_S_Neg _ -> CmmLit (CmmInt (narrowS rep (-x)) rep) - MO_Not _ -> CmmLit (CmmInt (complement x) rep) + = case op of + MO_S_Neg _ -> Just $! CmmLit (CmmInt (narrowS rep (-x)) rep) + MO_Not _ -> Just $! CmmLit (CmmInt (complement x) rep) -- these are interesting: we must first narrow to the -- "from" type, in order to truncate to the correct size. -- The final narrow/widen to the destination type -- is implicit in the CmmLit. - MO_SF_Round _frm to -> CmmLit (CmmFloat (fromInteger x) to) - MO_SS_Conv from to -> CmmLit (CmmInt (narrowS from x) to) - MO_UU_Conv from to -> CmmLit (CmmInt (narrowU from x) to) - MO_XX_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + MO_SF_Round _frm to -> Just $! CmmLit (CmmFloat (fromInteger x) to) + MO_SS_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) + MO_UU_Conv from to -> Just $! CmmLit (CmmInt (narrowU from x) to) + MO_XX_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) + + -- Not as simply as it seems, since CmmFloat uses Rational, so skipping those + -- for now ... + MO_WF_Bitcast _w -> Nothing + MO_FW_Bitcast _w -> Nothing _ -> panic $ "cmmMachOpFoldM: unknown unary op: " ++ show op -- Eliminate shifts that are wider than the shiftee ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -47,7 +47,6 @@ import GHC.Core.RoughMap ( RoughMatchTc(..) ) import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env -import GHC.Driver.Backend import GHC.Driver.DynFlags import GHC.Driver.Plugins @@ -342,7 +341,7 @@ mkIface_ hsc_env trust_info = setSafeMode safe_mode annotations = map mkIfaceAnnotation anns icomplete_matches = map mkIfaceCompleteMatch complete_matches - !rdrs = maybeGlobalRdrEnv rdr_env + !rdrs = mkIfaceTopEnv rdr_env emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag @@ -395,15 +394,11 @@ mkIface_ hsc_env -- Desugar.addExportFlagsAndRules). The mi_top_env field is used -- by GHCi to decide whether the module has its full top-level -- scope available. (#5534) - maybeGlobalRdrEnv :: GlobalRdrEnv -> Maybe IfaceTopEnv - maybeGlobalRdrEnv rdr_env - | backendWantsGlobalBindings (backend dflags) - = Just $! let !exports = forceGlobalRdrEnv (globalRdrEnvLocal rdr_env) - !imports = mkIfaceImports import_decls - in IfaceTopEnv exports imports - -- See Note [Forcing GREInfo] in GHC.Types.GREInfo. - | otherwise - = Nothing + mkIfaceTopEnv :: GlobalRdrEnv -> IfaceTopEnv + mkIfaceTopEnv rdr_env + = let !exports = sortAvails $ gresToAvailInfo $ globalRdrEnvElts $ globalRdrEnvLocal rdr_env + !imports = mkIfaceImports import_decls + in IfaceTopEnv exports imports ifFamInstTcName = ifFamInstFam @@ -515,8 +510,8 @@ mkIfaceImports :: [ImportUserSpec] -> [IfaceImport] mkIfaceImports = map go where go (ImpUserSpec decl ImpUserAll) = IfaceImport decl ImpIfaceAll - go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env)) - go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns) + go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (sortAvails env)) + go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut (nameSetElemsStable ns)) mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -26,7 +26,8 @@ module GHC.Iface.Syntax ( IfaceCompleteMatch(..), IfaceLFInfo(..), IfaceTopBndrInfo(..), IfaceImport(..), - ImpIfaceList(..), + ifImpModule, + ImpIfaceList(..), IfaceExport, -- * Binding names IfaceTopBndr, @@ -69,6 +70,7 @@ import GHC.Types.Name.Set import GHC.Types.Name.Reader import GHC.Types.CostCentre import GHC.Types.Literal +import GHC.Types.Avail import GHC.Types.ForeignCall import GHC.Types.Annotations( AnnPayload, AnnTarget ) import GHC.Types.Basic @@ -112,12 +114,48 @@ infixl 3 &&& ************************************************************************ -} +type IfaceExport = AvailInfo + data IfaceImport = IfaceImport ImpDeclSpec ImpIfaceList data ImpIfaceList = ImpIfaceAll -- ^ no user import list - | ImpIfaceExplicit !IfGlobalRdrEnv - | ImpIfaceEverythingBut !NameSet + | ImpIfaceExplicit !DetOrdAvails + | ImpIfaceEverythingBut ![Name] + + +-- | Extract the imported module from an IfaceImport +ifImpModule :: IfaceImport -> Module +ifImpModule (IfaceImport declSpec _) = is_mod declSpec + +instance Binary IfaceImport where + put_ bh (IfaceImport declSpec ifaceList) = do + put_ bh declSpec + put_ bh ifaceList + get bh = do + declSpec <- get bh + ifaceList <- get bh + return (IfaceImport declSpec ifaceList) + +instance Binary ImpIfaceList where + put_ bh ImpIfaceAll = putByte bh 0 + put_ bh (ImpIfaceExplicit env) = do + putByte bh 1 + put_ bh env + put_ bh (ImpIfaceEverythingBut ns) = do + putByte bh 2 + put_ @[Name] bh ns + get bh = do + tag <- getByte bh + case tag of + 0 -> return ImpIfaceAll + 1 -> do + env <- get bh + return (ImpIfaceExplicit env) + 2 -> do + ns <- get @[Name] bh + return (ImpIfaceEverythingBut ns) + _ -> fail "instance Binary ImpIfaceList: Invalid tag" -- | A binding top-level 'Name' in an interface file (e.g. the name of an -- 'IfaceDecl'). ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -104,6 +104,7 @@ import GHC.Types.SourceText import GHC.Types.Basic hiding ( SuccessFlag(..) ) import GHC.Types.CompleteMatch import GHC.Types.SrcLoc +import GHC.Types.Avail import GHC.Types.TypeEnv import GHC.Types.Unique.FM import GHC.Types.Unique.DSet ( mkUniqDSet ) @@ -114,7 +115,7 @@ import GHC.Types.Literal import GHC.Types.Var as Var import GHC.Types.Var.Set import GHC.Types.Name -import GHC.Types.Name.Reader +import GHC.Types.Name.Set import GHC.Types.Name.Env import GHC.Types.DefaultEnv ( ClassDefaults(..), defaultEnv ) import GHC.Types.Id @@ -2242,9 +2243,7 @@ hydrateCgBreakInfo CgBreakInfo{..} = do -- | This function is only used to construct the environment for GHCi, -- so we make up fake locations -tcIfaceImport :: HscEnv -> IfaceImport -> ImportUserSpec -tcIfaceImport _ (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll -tcIfaceImport _ (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut ns) -tcIfaceImport hsc_env (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (hydrateGlobalRdrEnv get_GRE_info gre)) - where - get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm +tcIfaceImport :: IfaceImport -> ImportUserSpec +tcIfaceImport (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll +tcIfaceImport (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut (mkNameSet ns)) +tcIfaceImport (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (getDetOrdAvails gre)) ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -2015,6 +2015,8 @@ lookupGREInfo hsc_env nm -- and looks up the TyThing in the type environment. -- -- See Note [Retrieving the GREInfo from interfaces] in GHC.Types.GREInfo. + -- Note: This function is very similar to 'tcIfaceGlobal', it would be better to + -- use that if possible. = case nameModule_maybe nm of Nothing -> UnboundGRE Just mod -> ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -1189,7 +1189,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) (gres, imp_user_list) = case want_hiding of Exactly -> let gre_env = mkGlobalRdrEnv $ concatMap (gresFromIE decl_spec) items2 - in (gre_env, ImpUserExplicit gre_env) + in (gre_env, ImpUserExplicit (gresToAvailInfo $ globalRdrEnvElts $ gre_env)) EverythingBut -> let hidden_names = mkNameSet $ concatMap (map greName . snd) items2 in (importsFromIface hsc_env iface decl_spec (Just hidden_names), ImpUserEverythingBut hidden_names) ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -53,7 +53,7 @@ import GHC.Driver.DynFlags import GHC.Driver.Ppr import GHC.Driver.Config -import GHC.Rename.Names (importsFromIface) +import GHC.Rename.Names (importsFromIface, gresFromAvails) import GHC.Runtime.Eval.Types import GHC.Runtime.Interpreter as GHCi @@ -113,6 +113,7 @@ import GHC.Types.TyThing import GHC.Types.Breakpoint import GHC.Types.Unique.Map +import GHC.Types.Avail import GHC.Unit import GHC.Unit.Module.Graph import GHC.Unit.Module.ModIface @@ -122,7 +123,7 @@ import GHC.Unit.Home.PackageTable import GHC.Tc.Module ( runTcInteractive, tcRnType, loadUnqualIfaces ) import GHC.Tc.Solver (simplifyWantedsTcM) -import GHC.Tc.Utils.Env (tcGetInstEnvs, lookupGlobal) +import GHC.Tc.Utils.Env (tcGetInstEnvs) import GHC.Tc.Utils.Instantiate (instDFunType) import GHC.Tc.Utils.Monad import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) @@ -848,21 +849,25 @@ mkTopLevEnv hsc_env modl Nothing -> pure $ Left "not a home module" Just details -> case mi_top_env (hm_iface details) of - Nothing -> pure $ Left "not interpreted" - Just (IfaceTopEnv exports imports) -> do + (IfaceTopEnv exports imports) -> do imports_env <- runInteractiveHsc hsc_env $ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv) $ forM imports $ \iface_import -> do - let ImpUserSpec spec details = tcIfaceImport hsc_env iface_import + let ImpUserSpec spec details = tcIfaceImport iface_import iface <- loadSrcInterface (text "imported by GHCi") (moduleName $ is_mod spec) (is_isboot spec) (is_pkg_qual spec) pure $ case details of ImpUserAll -> importsFromIface hsc_env iface spec Nothing ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns) - ImpUserExplicit x -> x - let get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm - let exports_env = hydrateGlobalRdrEnv get_GRE_info exports + ImpUserExplicit x -> + -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y). + -- It is only used for error messages. It seems dubious even to add an import context to these GREs as + -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that + -- the test case produce the same output as before. + let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } } + in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x + let exports_env = mkGlobalRdrEnv $ gresFromAvails hsc_env Nothing (getDetOrdAvails exports) pure $ Right $ plusGlobalRdrEnv imports_env exports_env where hpt = hsc_HPT hsc_env @@ -880,8 +885,8 @@ moduleIsInterpreted :: GhcMonad m => Module -> m Bool moduleIsInterpreted modl = withSession $ \h -> if notHomeModule (hsc_home_unit h) modl then return False - else liftIO (lookupHpt (hsc_HPT h) (moduleName modl)) >>= \case - Just details -> return (isJust (mi_top_env (hm_iface details))) + else liftIO (HUG.lookupHugByModule modl (hsc_HUG h)) >>= \case + Just hmi -> return (isJust $ homeModInfoByteCode hmi) _not_a_home_module -> return False -- | Looks up an identifier in the current interactive context (for :info) ===================================== compiler/GHC/Settings/IO.hs ===================================== @@ -168,6 +168,7 @@ initSettings top_dir = do lc_prog <- getSetting "LLVM llc command" lo_prog <- getSetting "LLVM opt command" las_prog <- getSetting "LLVM llvm-as command" + las_args <- map Option . unescapeArgs <$> getSetting "LLVM llvm-as flags" let iserv_prog = libexec "ghc-iserv" @@ -225,7 +226,7 @@ initSettings top_dir = do , toolSettings_pgm_ranlib = ranlib_path , toolSettings_pgm_lo = (lo_prog,[]) , toolSettings_pgm_lc = (lc_prog,[]) - , toolSettings_pgm_las = (las_prog, []) + , toolSettings_pgm_las = (las_prog, las_args) , toolSettings_pgm_i = iserv_prog , toolSettings_opt_L = [] , toolSettings_opt_P = [] ===================================== compiler/GHC/SysTools/Tasks.hs ===================================== @@ -7,7 +7,26 @@ -- (c) The GHC Team 2017 -- ----------------------------------------------------------------------------- -module GHC.SysTools.Tasks where +module GHC.SysTools.Tasks + ( runUnlit + , SourceCodePreprocessor(..) + , runSourceCodePreprocessor + , runPp + , runCc + , askLd + , runAs + , runLlvmOpt + , runLlvmLlc + , runLlvmAs + , runEmscripten + , figureLlvmVersion + , runMergeObjects + , runAr + , askOtool + , runInstallNameTool + , runRanlib + , runWindres + ) where import GHC.Prelude import GHC.ForeignSrcLang ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -124,7 +124,7 @@ import GHC.Serialized import GHC.Unit.Finder import GHC.Unit.Module import GHC.Unit.Module.ModIface -import GHC.Unit.Module.Deps +import GHC.Iface.Syntax import GHC.Utils.Misc import GHC.Utils.Panic as Panic @@ -2887,16 +2887,12 @@ reifyModule (TH.Module (TH.PkgName pkgString) (TH.ModName mString)) = do reifyFromIface reifMod = do iface <- loadInterfaceForModule (text "reifying module from TH for" <+> ppr reifMod) reifMod - let usages = [modToTHMod m | usage <- mi_usages iface, - Just m <- [usageToModule (moduleUnit reifMod) usage] ] + let IfaceTopEnv _ imports = mi_top_env iface + -- Convert IfaceImport to module names + usages = [modToTHMod (ifImpModule imp) | imp <- imports] return $ TH.ModuleInfo usages - usageToModule :: Unit -> Usage -> Maybe Module - usageToModule _ (UsageFile {}) = Nothing - usageToModule this_pkg (UsageHomeModule { usg_mod_name = mn }) = Just $ mkModule this_pkg mn - usageToModule _ (UsagePackageModule { usg_mod = m }) = Just m - usageToModule _ (UsageMergedRequirement { usg_mod = m }) = Just m - usageToModule this_pkg (UsageHomeModuleInterface { usg_mod_name = mn }) = Just $ mkModule this_pkg mn + ------------------------------ mkThAppTs :: TH.Type -> [TH.Type] -> TH.Type ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -206,7 +206,7 @@ data ImportUserSpec data ImpUserList = ImpUserAll -- ^ no user import list - | ImpUserExplicit !GlobalRdrEnv + | ImpUserExplicit ![AvailInfo] | ImpUserEverythingBut !NameSet -- | A 'NameShape' is a substitution on 'Name's that can be used ===================================== compiler/GHC/Types/Avail.hs ===================================== @@ -22,7 +22,8 @@ module GHC.Types.Avail ( filterAvails, nubAvails, sortAvails, - DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails) + DetOrdAvails(DetOrdAvails, getDetOrdAvails, DefinitelyDeterministicAvails), + emptyDetOrdAvails ) where import GHC.Prelude @@ -74,7 +75,7 @@ type Avails = [AvailInfo] -- We guarantee a deterministic order by either using the order explicitly -- given by the user (e.g. in an explicit constructor export list) or instead -- by sorting the avails with 'sortAvails'. -newtype DetOrdAvails = DefinitelyDeterministicAvails Avails +newtype DetOrdAvails = DefinitelyDeterministicAvails { getDetOrdAvails :: Avails } deriving newtype (Binary, Outputable, NFData) -- | It's always safe to match on 'DetOrdAvails' @@ -245,3 +246,7 @@ instance Binary AvailInfo where instance NFData AvailInfo where rnf (Avail n) = rnf n rnf (AvailTC a b) = rnf a `seq` rnf b + +-- | Create an empty DetOrdAvails +emptyDetOrdAvails :: DetOrdAvails +emptyDetOrdAvails = DefinitelyDeterministicAvails [] ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -133,6 +133,7 @@ import GHC.Unit.Module import GHC.Utils.Misc as Utils import GHC.Utils.Outputable import GHC.Utils.Panic +import GHC.Utils.Binary import Control.DeepSeq import Control.Monad ( guard ) @@ -1946,6 +1947,22 @@ data ImpDeclSpec instance NFData ImpDeclSpec where rnf = rwhnf -- Already strict in all fields +instance Binary ImpDeclSpec where + put_ bh (ImpDeclSpec mod as pkg_qual qual _dloc isboot) = do + put_ bh mod + put_ bh as + put_ bh pkg_qual + put_ bh qual + put_ bh isboot + + get bh = do + mod <- get bh + as <- get bh + pkg_qual <- get bh + qual <- get bh + isboot <- get bh + return (ImpDeclSpec mod as pkg_qual qual noSrcSpan isboot) + -- | Import Item Specification -- -- Describes import info a particular Name ===================================== compiler/GHC/Types/PkgQual.hs ===================================== @@ -6,6 +6,7 @@ module GHC.Types.PkgQual where import GHC.Prelude import GHC.Types.SourceText import GHC.Unit.Types +import GHC.Utils.Binary import GHC.Utils.Outputable import Data.Data @@ -38,4 +39,22 @@ instance Outputable PkgQual where ThisPkg u -> doubleQuotes (ppr u) OtherPkg u -> doubleQuotes (ppr u) +instance Binary PkgQual where + put_ bh NoPkgQual = putByte bh 0 + put_ bh (ThisPkg u) = do + putByte bh 1 + put_ bh u + put_ bh (OtherPkg u) = do + putByte bh 2 + put_ bh u + + get bh = do + tag <- getByte bh + case tag of + 0 -> return NoPkgQual + 1 -> do u <- get bh + return (ThisPkg u) + 2 -> do u <- get bh + return (OtherPkg u) + _ -> fail "instance Binary PkgQual: Invalid tag" ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -111,7 +111,6 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name -import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -299,7 +298,7 @@ data ModIface_ (phase :: ModIfacePhase) mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: !(Maybe IfaceTopEnv), + mi_top_env_ :: IfaceTopEnv, -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which @@ -365,13 +364,23 @@ data ModIface_ (phase :: ModIfacePhase) -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !IfGlobalRdrEnv -- ^ all top level things in this module, including unexported stuff + { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where rnf (IfaceTopEnv a b) = rnf a `seq` rnf b +instance Binary IfaceTopEnv where + put_ bh (IfaceTopEnv exports imports) = do + put_ bh exports + put_ bh imports + get bh = do + exports <- get bh + imports <- get bh + return (IfaceTopEnv exports imports) + + {- Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -479,6 +488,7 @@ instance Binary ModIface where mi_trust_ = trust, mi_trust_pkg_ = trust_pkg, mi_complete_matches_ = complete_matches, + mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header @@ -526,6 +536,7 @@ instance Binary ModIface where put_ bh trust put_ bh trust_pkg put_ bh complete_matches + lazyPut bh top_env lazyPutMaybe bh docs get bh = do @@ -560,6 +571,7 @@ instance Binary ModIface where trust <- get bh trust_pkg <- get bh complete_matches <- get bh + top_env <- lazyGet bh docs <- lazyGetMaybe bh return (PrivateModIface { mi_module_ = mod, @@ -582,7 +594,6 @@ instance Binary ModIface where mi_decls_ = decls, mi_extra_decls_ = extra_decls, mi_foreign_ = foreign_, - mi_top_env_ = Nothing, mi_defaults_ = defaults, mi_insts_ = insts, mi_fam_insts_ = fam_insts, @@ -593,6 +604,7 @@ instance Binary ModIface where -- And build the cached values mi_complete_matches_ = complete_matches, mi_docs_ = docs, + mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read mi_final_exts_ = ModIfaceBackend { @@ -613,8 +625,6 @@ instance Binary ModIface where }}) --- | The original names declared of a certain module that are exported -type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod @@ -638,7 +648,7 @@ emptyPartialModIface mod mi_decls_ = [], mi_extra_decls_ = Nothing, mi_foreign_ = emptyIfaceForeign, - mi_top_env_ = Nothing, + mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , mi_hpc_ = False, mi_trust_ = noIfaceTrustInfo, mi_trust_pkg_ = False, @@ -817,8 +827,7 @@ addSourceFingerprint val iface = iface { mi_src_hash_ = val } -- the in-memory byte array buffer 'mi_hi_bytes'. restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase restoreFromOldModIface old new = new - { mi_top_env_ = mi_top_env_ old - , mi_hsc_src_ = mi_hsc_src_ old + { mi_hsc_src_ = mi_hsc_src_ old , mi_src_hash_ = mi_src_hash_ old } @@ -879,7 +888,7 @@ set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } -set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase @@ -996,7 +1005,7 @@ pattern ModIface :: [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> ModIface_ phase ===================================== distrib/configure.ac.in ===================================== @@ -214,6 +214,13 @@ FIND_LLVM_PROG([LLVMAS], [clang], [$LlvmMinVersion], [$LlvmMaxVersion]) LlvmAsCmd="$LLVMAS" AC_SUBST([LlvmAsCmd]) +dnl We know that `clang` supports `--target` and it is necessary to pass it +dnl lest we see #25793. +if test -z "$LlvmAsFlags" ; then + LlvmAsFlags="--target=$LlvmTarget" +fi +AC_SUBST([LlvmAsFlags]) + dnl ** Check gcc version and flags we need to pass it ** FP_GCC_VERSION FP_GCC_SUPPORTS_NO_PIE ===================================== hadrian/bindist/Makefile ===================================== @@ -131,6 +131,7 @@ lib/settings : config.mk @echo ',("LLVM llc command", "$(SettingsLlcCommand)")' >> $@ @echo ',("LLVM opt command", "$(SettingsOptCommand)")' >> $@ @echo ',("LLVM llvm-as command", "$(SettingsLlvmAsCommand)")' >> $@ + @echo ',("LLVM llvm-as flags", "$(SettingsLlvmAsFlags)")' >> $@ @echo ',("Use inplace MinGW toolchain", "$(SettingsUseDistroMINGW)")' >> $@ @echo @echo ',("target RTS linker only supports shared libraries", "$(TargetRTSLinkerOnlySupportsSharedLibs)")' >> $@ ===================================== hadrian/cfg/system.config.in ===================================== @@ -85,6 +85,7 @@ settings-install_name_tool-command = @SettingsInstallNameToolCommand@ settings-llc-command = @SettingsLlcCommand@ settings-opt-command = @SettingsOptCommand@ settings-llvm-as-command = @SettingsLlvmAsCommand@ +settings-llvm-as-flags = @SettingsLlvmAsFlags@ settings-use-distro-mingw = @SettingsUseDistroMINGW@ target-has-libm = @TargetHasLibm@ ===================================== hadrian/src/Oracles/Setting.hs ===================================== @@ -91,6 +91,7 @@ data ToolchainSetting | ToolchainSetting_LlcCommand | ToolchainSetting_OptCommand | ToolchainSetting_LlvmAsCommand + | ToolchainSetting_LlvmAsFlags | ToolchainSetting_DistroMinGW -- | Look up the value of a 'Setting' in @cfg/system.config@, tracking the @@ -144,6 +145,7 @@ settingsFileSetting key = lookupSystemConfig $ case key of ToolchainSetting_LlcCommand -> "settings-llc-command" ToolchainSetting_OptCommand -> "settings-opt-command" ToolchainSetting_LlvmAsCommand -> "settings-llvm-as-command" + ToolchainSetting_LlvmAsFlags -> "settings-llvm-as-flags" ToolchainSetting_DistroMinGW -> "settings-use-distro-mingw" -- ROMES:TODO: This option doesn't seem to be in ghc-toolchain yet. It corresponds to EnableDistroToolchain -- | An expression that looks up the value of a 'Setting' in @cfg/system.config@, ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -528,6 +528,7 @@ generateSettings settingsFile = do , ("LLVM llc command", expr $ settingsFileSetting ToolchainSetting_LlcCommand) , ("LLVM opt command", expr $ settingsFileSetting ToolchainSetting_OptCommand) , ("LLVM llvm-as command", expr $ settingsFileSetting ToolchainSetting_LlvmAsCommand) + , ("LLVM llvm-as flags", expr $ settingsFileSetting ToolchainSetting_LlvmAsFlags) , ("Use inplace MinGW toolchain", expr $ settingsFileSetting ToolchainSetting_DistroMinGW) , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs) ===================================== m4/fp_settings.m4 ===================================== @@ -89,6 +89,7 @@ AC_DEFUN([FP_SETTINGS], SettingsLlcCommand="$LlcCmd" SettingsOptCommand="$OptCmd" SettingsLlvmAsCommand="$LlvmAsCmd" + SettingsLlvmAsFlags="$LlvmAsCmd" if test "$EnableDistroToolchain" = "YES"; then # If the user specified --enable-distro-toolchain then we just use the @@ -131,6 +132,7 @@ AC_DEFUN([FP_SETTINGS], SUBST_TOOLDIR([SettingsLlcCommand]) SUBST_TOOLDIR([SettingsOptCommand]) SUBST_TOOLDIR([SettingsLlvmAsCommand]) + SUBST_TOOLDIR([SettingsLlvmAsFlags]) fi # Mac-only tools @@ -171,5 +173,6 @@ AC_DEFUN([FP_SETTINGS], AC_SUBST(SettingsLlcCommand) AC_SUBST(SettingsOptCommand) AC_SUBST(SettingsLlvmAsCommand) + AC_SUBST(SettingsLlvmAsFlags) AC_SUBST(SettingsUseDistroMINGW) ]) ===================================== testsuite/tests/ghci/should_run/Makefile ===================================== @@ -7,3 +7,9 @@ T3171: echo "do Control.Concurrent.threadDelay 3000000; putStrLn \"threadDelay was not interrupted\"" | \ "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) & \ sleep 2; kill -INT $$!; wait + +TopEnvIface: + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface + # Second compilation starts from interface files, but still can print "a" + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface + ===================================== testsuite/tests/ghci/should_run/TopEnvIface.hs ===================================== @@ -0,0 +1,4 @@ +module TopEnvIface where + +import TopEnvIface2 + ===================================== testsuite/tests/ghci/should_run/TopEnvIface.stdout ===================================== @@ -0,0 +1,8 @@ +[1 of 2] Compiling TopEnvIface2 ( TopEnvIface2.hs, interpreted ) +[2 of 2] Compiling TopEnvIface ( TopEnvIface.hs, interpreted ) +Ok, two modules loaded. +"I should be printed twice" +Leaving GHCi. +Ok, two modules loaded. +"I should be printed twice" +Leaving GHCi. ===================================== testsuite/tests/ghci/should_run/TopEnvIface2.hs ===================================== @@ -0,0 +1,3 @@ +module TopEnvIface2 where + +a = "I should be printed twice" ===================================== testsuite/tests/ghci/should_run/all.T ===================================== @@ -96,3 +96,4 @@ test('LargeBCO', [extra_files(['LargeBCO_A.hs']), req_interp, extra_hc_opts("-O test('T24115', just_ghci + [extra_run_opts("-e ':add T24115.hs'")], ghci_script, ['T24115.script']) test('T10920', [only_ways(ghci_ways), extra_files(['LocalPrelude/Prelude.hs'])], ghci_script, ['T10920.script']) +test('TopEnvIface', [only_ways(ghci_ways)], makefile_test, []) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1af21fd68dce20985cdb6701cfeb926a8f631884...a5de39dec43ad4fb91234235ca7a22c9ea3c9d0c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1af21fd68dce20985cdb6701cfeb926a8f631884...a5de39dec43ad4fb91234235ca7a22c9ea3c9d0c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/4028e6fe/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 14:40:41 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 03 Mar 2025 09:40:41 -0500 Subject: [Git][ghc/ghc][wip/strict-level] 74 commits: compiler: Always load GHC.Data.FastString optimised into GHCi Message-ID: <67c5bf699101e_23db021594b040a6@gitlab.mail> Ben Gamari pushed to branch wip/strict-level at Glasgow Haskell Compiler / GHC Commits: 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 28a2d3a7 by Ben Gamari at 2025-03-03T09:37:53-05:00 SetLevels: Make Level strict There is no benefit to collecting thunks for (+1) operations. - - - - - 5cd7d404 by Ben Gamari at 2025-03-03T09:39:25-05:00 SetLevels: Track binding context In preparation to use this information to provide more context-sensitive naming for generated `lvl_` identifiers as propsed in #25802. - - - - - aa009886 by Ben Gamari at 2025-03-03T09:39:25-05:00 SetLevels: Name `lvl` binders according to context In general we should strive to maintain some amount of information about the provenance of generated bindings. Addresses #25802. - - - - - 301 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - ghc/GHCi/UI.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Parser.hs - libffi-tarballs - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/System/Timeout.hs - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/Interpreter.h - rts/RtsMain.c - rts/StgCRunAsm.S - rts/linker/MachO.c - testsuite/driver/testlib.py - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/T25177.stderr - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci/should_run/T21052.stdout - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod185.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Transform.hs - − utils/deriveConstants/Makefile - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30dabb0c7a0a79b68aeb7f315f75e9f55ef7aba2...aa009886182ee82920019d97743b360860d192fe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30dabb0c7a0a79b68aeb7f315f75e9f55ef7aba2...aa009886182ee82920019d97743b360860d192fe You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/369b76de/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 14:41:37 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 03 Mar 2025 09:41:37 -0500 Subject: [Git][ghc/ghc][wip/hadrian-test-env] hadrian: Refactor handling of test suite environment Message-ID: <67c5bfa1e5c7_23db0217ff204235@gitlab.mail> Ben Gamari pushed to branch wip/hadrian-test-env at Glasgow Haskell Compiler / GHC Commits: c3c41f55 by Ben Gamari at 2025-03-03T09:23:47-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 1 changed file: - hadrian/src/Rules/Test.hs Changes: ===================================== hadrian/src/Rules/Test.hs ===================================== @@ -1,8 +1,6 @@ {-# OPTIONS_GHC -Wno-unused-top-binds #-} module Rules.Test (testRules) where -import System.Environment - import Base import CommandLine import Expression @@ -171,7 +169,6 @@ testRules = do root -/- timeoutPath %> \_ -> timeoutProgBuilder "test" ~> do - args <- userSetting defaultTestArgs let testCompilerArg = testCompiler args let stg = fromMaybe Stage2 $ stageOf testCompilerArg @@ -185,92 +182,98 @@ testRules = do let ok_to_build = filter (isOkToBuild args) extra_targets putVerbose $ " | ExtraTargets: " ++ intercalate ", " extra_targets putVerbose $ " | ExtraTargets (ok-to-build): " ++ intercalate ", " ok_to_build - need ok_to_build - - -- Prepare Ghc configuration file for input compiler. - need [root -/- timeoutPath] - - cross <- flag CrossCompiling - - -- get relative path for the given program in the given stage - let relative_path_stage s p = programPath =<< programContext s p - let make_absolute rel_path = do - abs_path <- liftIO (makeAbsolute rel_path) - fixAbsolutePathOnWindows abs_path - - rel_ghc_pkg <- relative_path_stage Stage1 ghcPkg - rel_hsc2hs <- relative_path_stage Stage1 hsc2hs - rel_hp2ps <- relative_path_stage Stage1 hp2ps - rel_haddock <- relative_path_stage (Stage0 InTreeLibs) haddock - rel_hpc <- relative_path_stage (Stage0 InTreeLibs) hpc - rel_runghc <- relative_path_stage (Stage0 InTreeLibs) runGhc + need $ ok_to_build ++ [root -/- timeoutPath] -- force stage0 program building for cross - when cross $ need [rel_hpc, rel_haddock, rel_runghc] - - prog_ghc_pkg <- make_absolute rel_ghc_pkg - prog_hsc2hs <- make_absolute rel_hsc2hs - prog_hp2ps <- make_absolute rel_hp2ps - prog_haddock <- make_absolute rel_haddock - prog_hpc <- make_absolute rel_hpc - prog_runghc <- make_absolute rel_runghc - - ghcPath <- getCompilerPath testCompilerArg - - makePath <- builderPath $ Make "" - top <- topDirectory - ghcFlags <- runTestGhcFlags - let ghciFlags = ghcFlags ++ unwords - [ "--interactive", "-v0", "-ignore-dot-ghci" - , "-fno-ghci-history", "-fprint-error-index-links=never" - ] - ccPath <- queryTargetTarget (Toolchain.prgPath . Toolchain.ccProgram . Toolchain.tgtCCompiler) - ccFlags <- queryTargetTarget (unwords . Toolchain.prgFlags . Toolchain.ccProgram . Toolchain.tgtCCompiler) - - pythonPath <- builderPath Python + cross <- flag CrossCompiling + when cross $ mapM (relativePathStage (Stage0 InTreeLibs)) [hpc, haddock, runGhc] >>= need -- Set environment variables for test's Makefile. - -- TODO: Ideally we would define all those env vars in 'env', so that - -- Shake can keep track of them, but it is not as easy as it seems - -- to get that to work. - liftIO $ do - -- Many of those env vars are used by Makefiles in the - -- test infrastructure, or from tests or their - -- Makefiles. - setEnv "MAKE" makePath - setEnv "PYTHON" pythonPath - setEnv "TEST_HC" ghcPath - setEnv "TEST_HC_OPTS" ghcFlags - setEnv "TEST_HC_OPTS_INTERACTIVE" ghciFlags - setEnv "TEST_CC" ccPath - setEnv "TEST_CC_OPTS" ccFlags - - when cross $ do - setEnv "GHC_PKG" prog_ghc_pkg - setEnv "HSC2HS" prog_hsc2hs - setEnv "HP2PS_ABS" prog_hp2ps - setEnv "HPC" prog_hpc - setEnv "HADDOCK" prog_haddock - setEnv "RUNGHC" prog_runghc - - setEnv "CHECK_PPR" (top -/- root -/- checkPprProgPath) - setEnv "CHECK_EXACT" (top -/- root -/- checkExactProgPath) - setEnv "DUMP_DECLS" (top -/- root -/- dumpDeclsProgPath) - setEnv "COUNT_DEPS" (top -/- root -/- countDepsProgPath) - setEnv "LINT_NOTES" (top -/- root -/- noteLinterProgPath) - setEnv "LINT_CODES" (top -/- root -/- codeLinterProgPath) - setEnv "LINT_WHITESPACE" (top -/- root -/- whitespaceLinterProgPath) - - -- This lets us bypass the need to generate a config - -- through Make, which happens in testsuite/mk/boilerplate.mk - -- which is in turn included by all test 'Makefile's. - setEnv "ghc_config_mk" (top -/- root -/- ghcConfigPath) - + env <- testEnv -- Execute the test target. -- We override the verbosity setting to make sure the user can see -- the test output: https://gitlab.haskell.org/ghc/ghc/issues/15951. - withVerbosity Diagnostic $ buildWithCmdOptions [] $ test_target RunTest + withVerbosity Diagnostic $ buildWithCmdOptions [AddEnv k v | (k,v) <- env] $ test_target RunTest + +testEnv :: Action [(String, String)] +testEnv = do + cross <- flag CrossCompiling + makePath <- builderPath $ Make "" + prog_ghc_pkg <- absolutePathStage Stage1 ghcPkg + prog_hsc2hs <- absolutePathStage Stage1 hsc2hs + prog_hp2ps <- absolutePathStage Stage1 hp2ps + prog_haddock <- absolutePathStage (Stage0 InTreeLibs) haddock + prog_hpc <- absolutePathStage (Stage0 InTreeLibs) hpc + prog_runghc <- absolutePathStage (Stage0 InTreeLibs) runGhc + + root <- buildRoot + args <- userSetting defaultTestArgs + let testCompilerArg = testCompiler args + ghcPath <- getCompilerPath testCompilerArg + + top <- topDirectory + pythonPath <- builderPath Python + ccPath <- queryTargetTarget (Toolchain.prgPath . Toolchain.ccProgram . Toolchain.tgtCCompiler) + ccFlags <- queryTargetTarget (unwords . Toolchain.prgFlags . Toolchain.ccProgram . Toolchain.tgtCCompiler) + ghcFlags <- runTestGhcFlags + let ghciFlags = ghcFlags ++ unwords + [ "--interactive", "-v0", "-ignore-dot-ghci" + , "-fno-ghci-history", "-fprint-error-index-links=never" + ] + + -- Many of those env vars are used by Makefiles in the + -- test infrastructure, or from tests or their + -- Makefiles. + return $ + [ "MAKE" .= makePath + , "PYTHON" .= pythonPath + , "TEST_HC" .= ghcPath + , "TEST_HC_OPTS" .= ghcFlags + , "TEST_HC_OPTS_INTERACTIVE" .= ghciFlags + , "TEST_CC" .= ccPath + , "TEST_CC_OPTS" .= ccFlags + , "CHECK_PPR" .= (top -/- root -/- checkPprProgPath) + , "CHECK_EXACT" .= (top -/- root -/- checkExactProgPath) + , "DUMP_DECLS" .= (top -/- root -/- dumpDeclsProgPath) + , "COUNT_DEPS" .= (top -/- root -/- countDepsProgPath) + , "LINT_NOTES" .= (top -/- root -/- noteLinterProgPath) + , "LINT_CODES" .= (top -/- root -/- codeLinterProgPath) + , "LINT_WHITESPACE" .= (top -/- root -/- whitespaceLinterProgPath) + -- This lets us bypass the need to generate a config + -- through Make, which happens in testsuite/mk/boilerplate.mk + -- which is in turn included by all test 'Makefile's. + , "ghc_config_mk" .= (top -/- root -/- ghcConfigPath) + ] ++ + if_ cross + [ "GHC_PKG" .= prog_ghc_pkg + , "HSC2HS" .= prog_hsc2hs + , "HP2PS_ABS" .= prog_hp2ps + , "HPC" .= prog_hpc + , "HADDOCK" .= prog_haddock + , "RUNGHC" .= prog_runghc + ] + where + if_ :: Bool -> [a] -> [a] + if_ True xs = xs + if_ False _ = [] + + (.=) = (,) + +needProgramStage :: Stage -> Package -> Action () +needProgramStage s p = relativePathStage s p >>= need . (:[]) + +-- | Get relative path for the given program in the given stage. +relativePathStage :: Stage -> Package -> Action FilePath +relativePathStage s p = programPath =<< programContext s p + +absolutePathStage :: Stage -> Package -> Action FilePath +absolutePathStage s p = + relativePathStage s p >>= make_absolute + where + make_absolute rel_path = do + abs_path <- liftIO (makeAbsolute rel_path) + fixAbsolutePathOnWindows abs_path -- | Given a test compiler and a hadrian dependency (target), check if we -- can build the target with the compiler View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c3c41f558569fe815dffccd80de633bcaddbd578 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c3c41f558569fe815dffccd80de633bcaddbd578 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/c2380efc/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 14:42:13 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 03 Mar 2025 09:42:13 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/backports-9.10 Message-ID: <67c5bfc5df6f1_23db022d0d986954@gitlab.mail> Ben Gamari deleted branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/464ac273/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 3 14:42:16 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 03 Mar 2025 09:42:16 -0500 Subject: [Git][ghc/ghc][ghc-9.10] ghc-prim: Bump version to 0.12 Message-ID: <67c5bfc8e4130_23db02184d187185@gitlab.mail> Ben Gamari pushed to branch ghc-9.10 at Glasgow Haskell Compiler / GHC Commits: 9968ac07 by Ben Gamari at 2025-02-28T11:40:56-05:00 ghc-prim: Bump version to 0.12 Requires bump of `text` submodule due to upstream bound. Addresses #25550. - - - - - 9 changed files: - ghc/ghc-bin.cabal.in - libraries/ghc-bignum/ghc-bignum.cabal - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/ghci.cabal.in - libraries/text Changes: ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -57,7 +57,7 @@ Executable ghc -- NB: this is never built by the bootstrapping GHC+libraries Build-depends: deepseq >= 1.4 && < 1.6, - ghc-prim >= 0.5.0 && < 0.12, + ghc-prim >= 0.5.0 && < 0.13, ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, ===================================== libraries/ghc-bignum/ghc-bignum.cabal ===================================== @@ -77,7 +77,7 @@ library ForeignFunctionInterface build-depends: - ghc-prim >= 0.5.1.0 && < 0.12 + ghc-prim >= 0.5.1.0 && < 0.13 hs-source-dirs: src/ include-dirs: include/ ===================================== libraries/ghc-compact/ghc-compact.cabal ===================================== @@ -39,7 +39,7 @@ library UnboxedTuples CPP - build-depends: ghc-prim >= 0.5.3 && < 0.12, + build-depends: ghc-prim >= 0.5.3 && < 0.14, base >= 4.9.0 && < 4.21, bytestring >= 0.10.6.0 && <0.13 ghc-options: -Wall ===================================== libraries/ghc-experimental/ghc-experimental.cabal.in ===================================== @@ -39,7 +39,7 @@ library other-extensions: build-depends: base ^>=4.20, ghc-internal == @ProjectVersionForLib at .*, - ghc-prim >= 0.11 && < 0.12 + ghc-prim >= 0.11 && < 0.13 hs-source-dirs: src default-language: Haskell2010 ghc-options: -this-unit-id ghc-experimental ===================================== libraries/ghc-heap/ghc-heap.cabal.in ===================================== @@ -23,7 +23,7 @@ library default-language: Haskell2010 build-depends: base >= 4.9.0 && < 5.0 - , ghc-prim > 0.2 && < 0.12 + , ghc-prim > 0.2 && < 0.13 , rts == 1.0.* , containers >= 0.6.2.1 && < 0.8 ===================================== libraries/ghc-internal/ghc-internal.cabal.in ===================================== @@ -89,7 +89,7 @@ Library build-depends: rts == 1.0.*, - ghc-prim >= 0.11 && < 0.12, + ghc-prim >= 0.11 && < 0.13, ghc-bignum >= 1.0 && < 2.0 exposed-modules: ===================================== libraries/ghc-prim/ghc-prim.cabal ===================================== @@ -1,6 +1,6 @@ cabal-version: 2.2 name: ghc-prim -version: 0.11.0 +version: 0.12.0 -- NOTE: Don't forget to update ./changelog.md license: BSD-3-Clause license-file: LICENSE ===================================== libraries/ghci/ghci.cabal.in ===================================== @@ -76,7 +76,7 @@ library rts, array == 0.5.*, base >= 4.8 && < 4.21, - ghc-prim >= 0.5.0 && < 0.12, + ghc-prim >= 0.5.0 && < 0.13, binary == 0.8.*, bytestring >= 0.10 && < 0.13, containers >= 0.5 && < 0.8, ===================================== libraries/text ===================================== @@ -1 +1 @@ -Subproject commit ee0a8f8b9a4bd3fdad23e9ac0db56e7f08ce35cd +Subproject commit 991b7e34efacc44a8a8b60e28ae737c45bc5942e View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9968ac074d4d55f8611e241a089dea5b4ce9303b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9968ac074d4d55f8611e241a089dea5b4ce9303b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/19c1f4f0/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 15:24:44 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Mar 2025 10:24:44 -0500 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] Adapt locations for do-blocks Message-ID: <67c5c9bc631a_23db026e5ac8125c4@gitlab.mail> Simon Peyton Jones pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 0753130c by Simon Peyton Jones at 2025-03-03T15:23:33+00:00 Adapt locations for do-blocks - - - - - 1 changed file: - compiler/GHC/Tc/Gen/Do.hs Changes: ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -255,9 +255,10 @@ mk_failable_expr doFlav lpat expr@(L _exprloc _) fail_op = else wrapGenSpan <$> mk_fail_block doFlav lpat expr fail_op } --- makes the fail block with a given fail_op mk_fail_block :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) +-- (mk_fail_block (L ploc pat) rhs fail_op) makes +-- \x. case x of { (L ploc pat) -> rhs; _ -> fail_op "pattern match failure..." } mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = do dflags <- getDynFlags return $ HsLam noAnn LamCases $ mkMatchGroup (doExpansionOrigin doFlav) -- \ @@ -267,11 +268,11 @@ mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = where fail_alt_case :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> LMatch GhcRn (LHsExpr GhcRn) fail_alt_case dflags pat fail_op = genHsCaseAltDoExp doFlav (L ploc $ WildPat noExtField) $ - L ploc (fail_op_expr dflags pat fail_op) + L generatedLoc (fail_op_expr dflags pat fail_op) fail_op_expr :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> HsExpr GhcRn fail_op_expr dflags pat fail_op - = mkExpandedPatRn pat doFlav $ + = mkExpandedPatRn pat doFlav $ xxx get rid of this! genHsApp fail_op (mk_fail_msg_expr dflags pat) mk_fail_msg_expr :: DynFlags -> LPat GhcRn -> LHsExpr GhcRn View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0753130cda9a59b573942f06868a1b89da20a0b3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0753130cda9a59b573942f06868a1b89da20a0b3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/34368ee6/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 16:27:53 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Mar 2025 11:27:53 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: compiler: Add export list to GHC.SysTools.Tasks Message-ID: <67c5d889c630e_26d8392b8edc8525b@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 6eb2f15b by John Ericson at 2025-03-03T11:27:29-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - 89f1a624 by Rodrigo Mesquita at 2025-03-03T11:27:30-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 3ac82226 by Rodrigo Mesquita at 2025-03-03T11:27:30-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - 14 changed files: - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/SysTools/Tasks.hs - distrib/configure.ac.in - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - m4/fp_settings.m4 Changes: ===================================== compiler/GHC/Cmm/Opt.hs ===================================== @@ -63,18 +63,23 @@ cmmMachOpFoldM _ (MO_VF_Broadcast lg _w) exprs = [CmmLit l] -> Just $! CmmLit (CmmVec $ replicate lg l) _ -> Nothing cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] - = Just $! case op of - MO_S_Neg _ -> CmmLit (CmmInt (narrowS rep (-x)) rep) - MO_Not _ -> CmmLit (CmmInt (complement x) rep) + = case op of + MO_S_Neg _ -> Just $! CmmLit (CmmInt (narrowS rep (-x)) rep) + MO_Not _ -> Just $! CmmLit (CmmInt (complement x) rep) -- these are interesting: we must first narrow to the -- "from" type, in order to truncate to the correct size. -- The final narrow/widen to the destination type -- is implicit in the CmmLit. - MO_SF_Round _frm to -> CmmLit (CmmFloat (fromInteger x) to) - MO_SS_Conv from to -> CmmLit (CmmInt (narrowS from x) to) - MO_UU_Conv from to -> CmmLit (CmmInt (narrowU from x) to) - MO_XX_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + MO_SF_Round _frm to -> Just $! CmmLit (CmmFloat (fromInteger x) to) + MO_SS_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) + MO_UU_Conv from to -> Just $! CmmLit (CmmInt (narrowU from x) to) + MO_XX_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) + + -- Not as simply as it seems, since CmmFloat uses Rational, so skipping those + -- for now ... + MO_WF_Bitcast _w -> Nothing + MO_FW_Bitcast _w -> Nothing _ -> panic $ "cmmMachOpFoldM: unknown unary op: " ++ show op -- Eliminate shifts that are wider than the shiftee ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -18,7 +18,7 @@ module GHC.Runtime.Eval ( abandon, abandonAll, getResumeContext, getHistorySpan, - getModBreaks, + getModBreaks, readModBreaks, getHistoryModule, setupBreakpoint, back, forward, @@ -130,14 +130,12 @@ import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) import GHC.IfaceToCore import Control.Monad -import Control.Monad.Catch as MC import Data.Array import Data.Dynamic import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.List (find,intercalate) import Data.List.NonEmpty (NonEmpty) -import System.Directory import Unsafe.Coerce ( unsafeCoerce ) import qualified GHC.Unit.Home.Graph as HUG @@ -156,9 +154,8 @@ getHistoryModule = ibi_tick_mod . historyBreakpointId getHistorySpan :: HscEnv -> History -> IO SrcSpan getHistorySpan hsc_env hist = do let ibi = historyBreakpointId hist - HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) >>= pure . \case - Just hmi -> modBreaks_locs (getModBreaks hmi) ! ibi_tick_index ibi - _ -> panic "getHistorySpan" + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi {- | Finds the enclosing top level function name -} -- ToDo: a better way to do this would be to keep hold of the decl_path computed @@ -166,9 +163,8 @@ getHistorySpan hsc_env hist = do -- for each tick. findEnclosingDecls :: HscEnv -> InternalBreakpointId -> IO [String] findEnclosingDecls hsc_env ibi = do - hmi <- expectJust <$> HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) - return $ - modBreaks_decls (getModBreaks hmi) ! ibi_tick_index ibi + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_decls brks ! ibi_tick_index ibi -- | Update fixity environment in the current interactive context. updateFixityEnv :: GhcMonad m => FixityEnv -> m () @@ -232,10 +228,9 @@ execStmt' stmt stmt_text ExecOptions{..} = do updateFixityEnv fix_env status <- - withVirtualCWD $ - liftIO $ do - let eval_opts = initEvalOpts idflags' (isStep execSingleStep) - evalStmt interp eval_opts (execWrap hval) + liftIO $ do + let eval_opts = initEvalOpts idflags' (enableGhcStepMode execSingleStep) + evalStmt interp eval_opts (execWrap hval) let ic = hsc_IC hsc_env bindings = (ic_tythings ic, ic_gre_cache ic) @@ -282,38 +277,17 @@ them. The relevant predicate is OccName.isDerivedOccName. See #11051 for more background and examples. -} -withVirtualCWD :: GhcMonad m => m a -> m a -withVirtualCWD m = do - hsc_env <- getSession - - -- a virtual CWD is only necessary when we're running interpreted code in - -- the same process as the compiler. - case interpInstance <$> hsc_interp hsc_env of - Just (ExternalInterp {}) -> m - _ -> do - let ic = hsc_IC hsc_env - let set_cwd = do - dir <- liftIO $ getCurrentDirectory - case ic_cwd ic of - Just dir -> liftIO $ setCurrentDirectory dir - Nothing -> return () - return dir - - reset_cwd orig_dir = do - virt_dir <- liftIO $ getCurrentDirectory - hsc_env <- getSession - let old_IC = hsc_IC hsc_env - setSession hsc_env{ hsc_IC = old_IC{ ic_cwd = Just virt_dir } } - liftIO $ setCurrentDirectory orig_dir - - MC.bracket set_cwd reset_cwd $ \_ -> m - parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) parseImportDecl expr = withSession $ \hsc_env -> liftIO $ hscImport hsc_env expr emptyHistory :: Int -> BoundedList History emptyHistory size = nilBL size +-- | Turn an 'EvalStatus_' result from interpreting Haskell into a GHCi 'ExecResult'. +-- +-- This function is responsible for resuming execution at an intermediate +-- breakpoint if we don't care about that breakpoint (e.g. if using :steplocal +-- or :stepmodule, rather than :step, we only care about certain breakpoints). handleRunStatus :: GhcMonad m => SingleStep -> String -> ResumeBindings @@ -322,92 +296,107 @@ handleRunStatus :: GhcMonad m -> BoundedList History -> m ExecResult -handleRunStatus step expr bindings final_ids status history0 - | RunAndLogSteps <- step = tracing - | otherwise = not_tracing - where - tracing - | EvalBreak apStack_ref (Just eval_break) resume_ctxt _ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - let dflags = hsc_dflags hsc_env - ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break - hmi <- liftIO $ expectJust <$> - lookupHpt (hsc_HPT hsc_env) (moduleName (ibi_tick_mod ibi)) - let breaks = getModBreaks hmi - - b <- liftIO $ - breakpointStatus interp (modBreaks_flags breaks) (ibi_tick_index ibi) - if b - then not_tracing - -- This breakpoint is explicitly enabled; we want to stop - -- instead of just logging it. - else do - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi - let !history' = history1 `consBL` history0 - -- history is strict, otherwise our BoundedList is pointless. - fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - let eval_opts = initEvalOpts dflags True - status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv - handleRunStatus RunAndLogSteps expr bindings final_ids - status history' - | otherwise - = not_tracing - - not_tracing - -- Hit a breakpoint - | EvalBreak apStack_ref maybe_break resume_ctxt ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - ibi <- case maybe_break of - Nothing -> pure Nothing - Just break -> fmap Just $ liftIO $ - evalBreakpointToId (hsc_HPT hsc_env) break - (hsc_env1, names, span, decl) <- liftIO $ - bindLocalsAtBreakpoint hsc_env apStack_fhv ibi - let - resume = Resume - { resumeStmt = expr - , resumeContext = resume_ctxt_fhv - , resumeBindings = bindings - , resumeFinalIds = final_ids - , resumeApStack = apStack_fhv - , resumeBreakpointId = ibi - , resumeSpan = span - , resumeHistory = toListBL history0 - , resumeDecl = decl - , resumeCCS = ccs - , resumeHistoryIx = 0 - } - hsc_env2 = pushResume hsc_env1 resume - - setSession hsc_env2 - return (ExecBreak names ibi) +handleRunStatus step expr bindings final_ids status history0 = do + hsc_env <- getSession + let + interp = hscInterp hsc_env + dflags = hsc_dflags hsc_env + case status of -- Completed successfully - | EvalComplete allocs (EvalSuccess hvals) <- status - = do hsc_env <- getSession - let final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids - final_names = map getName final_ids - interp = hscInterp hsc_env - liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) - hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} - setSession hsc_env' - return (ExecComplete (Right final_names) allocs) + EvalComplete allocs (EvalSuccess hvals) -> do + let + final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids + final_names = map getName final_ids + liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) + hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} + setSession hsc_env' + return (ExecComplete (Right final_names) allocs) -- Completed with an exception - | EvalComplete alloc (EvalException e) <- status - = return (ExecComplete (Left (fromSerializableException e)) alloc) - + EvalComplete alloc (EvalException e) -> + return (ExecComplete (Left (fromSerializableException e)) alloc) + + -- Nothing case: we stopped when an exception was raised, not at a breakpoint. + EvalBreak apStack_ref Nothing resume_ctxt ccs -> do + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + let span = mkGeneralSrcSpan (fsLit "<unknown>") + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span Nothing + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Nothing + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = "<exception thrown>" + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + + setSession hsc_env2 + return (ExecBreak names Nothing) + + -- Just case: we stopped at a breakpoint + EvalBreak apStack_ref (Just eval_break) resume_ctxt ccs -> do + ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break + tick_brks <- liftIO $ readModBreaks hsc_env (ibi_tick_mod ibi) + let + span = modBreaks_locs tick_brks ! ibi_tick_index ibi + decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi + + b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi) + + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + + -- This breakpoint is explicitly enabled; we want to stop + -- instead of just logging it. + if b || breakHere step span then do + -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break. + -- Specifically, for :steplocal or :stepmodule, don't return control + -- and simply resume execution from here until we hit a breakpoint we do want to stop at. + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Just ibi + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = decl + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + setSession hsc_env2 + return (ExecBreak names (Just ibi)) + else do + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) + status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv + history <- if not tracing then pure history0 else do + history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi + let !history' = history1 `consBL` history0 + -- history is strict, otherwise our BoundedList is pointless. + return history' + handleRunStatus step expr bindings final_ids status history + where + tracing | RunAndLogSteps <- step = True + | otherwise = False -resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> Maybe Int +resumeExec :: GhcMonad m => SingleStep -> Maybe Int -> m ExecResult -resumeExec canLogSpan step mbCnt +resumeExec step mbCnt = do hsc_env <- getSession let ic = hsc_IC hsc_env @@ -445,42 +434,41 @@ resumeExec canLogSpan step mbCnt , resumeBreakpointId = mb_brkpt , resumeSpan = span , resumeHistory = hist } -> - withVirtualCWD $ do + do -- When the user specified a break ignore count, set it -- in the interpreter case (mb_brkpt, mbCnt) of (Just brkpt, Just cnt) -> setupBreakpoint hsc_env (toBreakpointId brkpt) cnt _ -> return () - let eval_opts = initEvalOpts dflags (isStep step) + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv let prevHistoryLst = fromListBL 50 hist hist' = case mb_brkpt of Nothing -> pure prevHistoryLst Just bi - | not $ canLogSpan span -> pure prevHistoryLst - | otherwise -> do + | breakHere step span -> do hist1 <- liftIO (mkHistory hsc_env apStack bi) return $ hist1 `consBL` fromListBL 50 hist + | otherwise -> pure prevHistoryLst handleRunStatus step expr bindings final_ids status =<< hist' setupBreakpoint :: GhcMonad m => HscEnv -> BreakpointId -> Int -> m () -- #19157 setupBreakpoint hsc_env bi cnt = do let modl = bi_tick_mod bi - modBreaks <- getModBreaks . expectJust <$> - liftIO (lookupHpt (hsc_HPT hsc_env) (moduleName modl)) + modBreaks <- liftIO $ readModBreaks hsc_env modl let breakarray = modBreaks_flags modBreaks interp = hscInterp hsc_env _ <- liftIO $ GHCi.storeBreakpoint interp breakarray (bi_tick_index bi) cnt pure () -back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) back n = moveHist (+n) -forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) forward n = moveHist (subtract n) -moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan, String) +moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan) moveHist fn = do hsc_env <- getSession case ic_resume (hsc_IC hsc_env) of @@ -498,15 +486,20 @@ moveHist fn = do let update_ic apStack mb_info = do - (hsc_env1, names, span, decl) <- - liftIO $ bindLocalsAtBreakpoint hsc_env apStack mb_info + span <- case mb_info of + Nothing -> return $ mkGeneralSrcSpan (fsLit "<unknown>") + Just ibi -> liftIO $ do + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi + (hsc_env1, names) <- + liftIO $ bindLocalsAtBreakpoint hsc_env apStack span mb_info let ic = hsc_IC hsc_env1 r' = r { resumeHistoryIx = new_ix } ic' = ic { ic_resume = r':rs } setSession hsc_env1{ hsc_IC = ic' } - return (names, new_ix, span, decl) + return (names, new_ix, span) -- careful: we want apStack to be the AP_STACK itself, not a thunk -- around it, hence the cases are carefully constructed below to @@ -527,19 +520,25 @@ moveHist fn = do result_fs :: FastString result_fs = fsLit "_result" +-- | Read the 'ModBreaks' of the given home 'Module' from the 'HomeUnitGraph'. +readModBreaks :: HscEnv -> Module -> IO ModBreaks +readModBreaks hsc_env mod = + getModBreaks . expectJust <$> + HUG.lookupHugByModule mod (hsc_HUG hsc_env) + bindLocalsAtBreakpoint :: HscEnv -> ForeignHValue + -> SrcSpan -> Maybe InternalBreakpointId - -> IO (HscEnv, [Name], SrcSpan, String) + -> IO (HscEnv, [Name]) -- Nothing case: we stopped when an exception was raised, not at a -- breakpoint. We have no location information or local variables to -- bind, all we can do is bind a local variable to the exception -- value. -bindLocalsAtBreakpoint hsc_env apStack Nothing = do +bindLocalsAtBreakpoint hsc_env apStack span Nothing = do let exn_occ = mkVarOccFS (fsLit "_exception") - span = mkGeneralSrcSpan (fsLit "<unknown>") exn_name <- newInteractiveBinder hsc_env exn_occ span let e_fs = fsLit "e" @@ -552,32 +551,21 @@ bindLocalsAtBreakpoint hsc_env apStack Nothing = do interp = hscInterp hsc_env -- Loader.extendLoadedEnv interp [(exn_name, apStack)] - return (hsc_env{ hsc_IC = ictxt1 }, [exn_name], span, "<exception thrown>") + return (hsc_env{ hsc_IC = ictxt1 }, [exn_name]) -- Just case: we stopped at a breakpoint, we have information about the location -- of the breakpoint and the free variables of the expression. -bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do - let - interp = hscInterp hsc_env - - info_mod = ibi_info_mod ibi - info_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName info_mod) - let - info_brks = getModBreaks info_hmi - info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) - - tick_mod = ibi_tick_mod ibi - tick_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName tick_mod) - let - tick_brks = getModBreaks tick_hmi - occs = modBreaks_vars tick_brks ! ibi_tick_index ibi - span = modBreaks_locs tick_brks ! ibi_tick_index ibi - decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi +bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do + info_brks <- readModBreaks hsc_env (ibi_info_mod ibi) + tick_brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + let info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) + interp = hscInterp hsc_env + occs = modBreaks_vars tick_brks ! ibi_tick_index ibi -- Rehydrate to understand the breakpoint info relative to the current environment. -- This design is critical to preventing leaks (#22530) (mbVars, result_ty) <- initIfaceLoad hsc_env - $ initIfaceLcl info_mod (text "debugger") NotBoot + $ initIfaceLcl (ibi_info_mod ibi) (text "debugger") NotBoot $ hydrateCgBreakInfo info let @@ -624,7 +612,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do Loader.extendLoadedEnv interp (zip names fhvs) when result_ok $ Loader.extendLoadedEnv interp [(result_name, apStack_fhv)] hsc_env1 <- rttiEnvironment hsc_env{ hsc_IC = ictxt1 } - return (hsc_env1, if result_ok then result_name:names else names, span, decl) + return (hsc_env1, if result_ok then result_name:names else names) where -- We need a fresh Unique for each Id we bind, because the linker -- state is single-threaded and otherwise we'd spam old bindings ===================================== compiler/GHC/Runtime/Eval/Types.hs ===================================== @@ -9,7 +9,8 @@ module GHC.Runtime.Eval.Types ( Resume(..), ResumeBindings, IcGlobalRdrEnv(..), History(..), ExecResult(..), - SingleStep(..), isStep, ExecOptions(..) + SingleStep(..), enableGhcStepMode, breakHere, + ExecOptions(..) ) where import GHC.Prelude @@ -35,21 +36,59 @@ data ExecOptions , execWrap :: ForeignHValue -> EvalExpr ForeignHValue } +-- | What kind of stepping are we doing? data SingleStep = RunToCompletion - | SingleStep + + -- | :trace [expr] | RunAndLogSteps -isStep :: SingleStep -> Bool -isStep RunToCompletion = False -isStep _ = True + -- | :step [expr] + | SingleStep + + -- | :steplocal [expr] + | LocalStep + { breakAt :: SrcSpan } + + -- | :stepmodule [expr] + | ModuleStep + { breakAt :: SrcSpan } + +-- | Whether this 'SingleStep' mode requires instructing the interpreter to +-- step at every breakpoint. +enableGhcStepMode :: SingleStep -> Bool +enableGhcStepMode RunToCompletion = False +enableGhcStepMode _ = True + +-- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return +-- @True@ if based on the step-mode alone we should stop at this breakpoint. +-- +-- In particular, this will always be @False@ for @'RunToCompletion'@ and +-- @'RunAndLogSteps'@. We'd need further information e.g. about the user +-- breakpoints to determine whether to break in those modes. +breakHere :: SingleStep -> SrcSpan -> Bool +breakHere step break_span = case step of + RunToCompletion -> False + RunAndLogSteps -> False + SingleStep -> True + LocalStep span -> break_span `isSubspanOf` span + ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span data ExecResult + + -- | Execution is complete = ExecComplete { execResult :: Either SomeException [Name] , execAllocation :: Word64 } - | ExecBreak + + -- | Execution stopped at a breakpoint. + -- + -- Note: `ExecBreak` is only returned by `handleRunStatus` when GHCi should + -- definitely stop at this breakpoint. GHCi is /not/ responsible for + -- subsequently deciding whether to really stop here. + -- `ExecBreak` always means GHCi breaks. + | ExecBreak { breakNames :: [Name] , breakPointId :: Maybe InternalBreakpointId } ===================================== compiler/GHC/Settings/IO.hs ===================================== @@ -168,6 +168,7 @@ initSettings top_dir = do lc_prog <- getSetting "LLVM llc command" lo_prog <- getSetting "LLVM opt command" las_prog <- getSetting "LLVM llvm-as command" + las_args <- map Option . unescapeArgs <$> getSetting "LLVM llvm-as flags" let iserv_prog = libexec "ghc-iserv" @@ -225,7 +226,7 @@ initSettings top_dir = do , toolSettings_pgm_ranlib = ranlib_path , toolSettings_pgm_lo = (lo_prog,[]) , toolSettings_pgm_lc = (lc_prog,[]) - , toolSettings_pgm_las = (las_prog, []) + , toolSettings_pgm_las = (las_prog, las_args) , toolSettings_pgm_i = iserv_prog , toolSettings_opt_L = [] , toolSettings_opt_P = [] ===================================== compiler/GHC/SysTools/Tasks.hs ===================================== @@ -7,7 +7,26 @@ -- (c) The GHC Team 2017 -- ----------------------------------------------------------------------------- -module GHC.SysTools.Tasks where +module GHC.SysTools.Tasks + ( runUnlit + , SourceCodePreprocessor(..) + , runSourceCodePreprocessor + , runPp + , runCc + , askLd + , runAs + , runLlvmOpt + , runLlvmLlc + , runLlvmAs + , runEmscripten + , figureLlvmVersion + , runMergeObjects + , runAr + , askOtool + , runInstallNameTool + , runRanlib + , runWindres + ) where import GHC.Prelude import GHC.ForeignSrcLang ===================================== distrib/configure.ac.in ===================================== @@ -214,6 +214,13 @@ FIND_LLVM_PROG([LLVMAS], [clang], [$LlvmMinVersion], [$LlvmMaxVersion]) LlvmAsCmd="$LLVMAS" AC_SUBST([LlvmAsCmd]) +dnl We know that `clang` supports `--target` and it is necessary to pass it +dnl lest we see #25793. +if test -z "$LlvmAsFlags" ; then + LlvmAsFlags="--target=$LlvmTarget" +fi +AC_SUBST([LlvmAsFlags]) + dnl ** Check gcc version and flags we need to pass it ** FP_GCC_VERSION FP_GCC_SUPPORTS_NO_PIE ===================================== ghc/GHCi/UI.hs ===================================== @@ -1310,7 +1310,7 @@ runStmt input step = do m_result <- GhciMonad.runStmt stmt input step case m_result of Nothing -> return Nothing - Just result -> Just <$> afterRunStmt (const True) result + Just result -> Just <$> afterRunStmt step result -- `x = y` (a declaration) should be treated as `let x = y` (a statement). -- The reason is because GHCi wasn't designed to support `x = y`, but then @@ -1342,7 +1342,7 @@ runStmt input step = do _ <- liftIO $ tryIO $ hFlushAll stdin m_result <- GhciMonad.runDecls' decls forM m_result $ \result -> - afterRunStmt (const True) (GHC.ExecComplete (Right result) 0) + afterRunStmt step (GHC.ExecComplete (Right result) 0) mk_stmt :: SrcSpan -> HsBind GhcPs -> GhciLStmt GhcPs mk_stmt loc bind = @@ -1359,9 +1359,9 @@ runStmt input step = do modStr = moduleNameString $ moduleName $ icInteractiveModule $ ic -- | Clean up the GHCi environment after a statement has run -afterRunStmt :: GhciMonad m - => (SrcSpan -> Bool) -> GHC.ExecResult -> m GHC.ExecResult -afterRunStmt step_here run_result = do +afterRunStmt :: GhciMonad m => SingleStep {-^ Type of step we took just before -} + -> GHC.ExecResult -> m GHC.ExecResult +afterRunStmt step run_result = do resumes <- GHC.getResumeContext case run_result of GHC.ExecComplete{..} -> @@ -1372,9 +1372,7 @@ afterRunStmt step_here run_result = do when show_types $ printTypeOfNames names GHC.ExecBreak names mb_info | first_resume : _ <- resumes - , isNothing mb_info || - step_here (GHC.resumeSpan first_resume) -> do - mb_id_loc <- toBreakIdAndLocation mb_info + -> do mb_id_loc <- toBreakIdAndLocation mb_info let bCmd = maybe "" ( \(_,l) -> onBreakCmd l ) mb_id_loc if (null bCmd) then printStoppedAtBreakInfo first_resume names @@ -1383,8 +1381,9 @@ afterRunStmt step_here run_result = do st <- getGHCiState enqueueCommands [stop st] return () - | otherwise -> resume step_here GHC.SingleStep Nothing >>= - afterRunStmt step_here >> return () + + | otherwise -> resume step Nothing >>= + afterRunStmt step >> return () flushInterpBuffers withSignalHandlers $ do @@ -3810,7 +3809,7 @@ forceCmd = pprintClosureCommand False True stepCmd :: GhciMonad m => String -> m () stepCmd arg = withSandboxOnly ":step" $ step arg where - step [] = doContinue (const True) GHC.SingleStep + step [] = doContinue GHC.SingleStep step expression = runStmt expression GHC.SingleStep >> return () stepLocalCmd :: GhciMonad m => String -> m () @@ -3829,7 +3828,7 @@ stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg Just loc -> do md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule current_toplevel_decl <- enclosingTickSpan md loc - doContinue (`isSubspanOf` RealSrcSpan current_toplevel_decl Strict.Nothing) GHC.SingleStep + doContinue (GHC.LocalStep (RealSrcSpan current_toplevel_decl Strict.Nothing)) stepModuleCmd :: GhciMonad m => String -> m () stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg @@ -3840,9 +3839,7 @@ stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg mb_span <- getCurrentBreakSpan case mb_span of Nothing -> stepCmd [] - Just pan -> do - let f some_span = srcSpanFileName_maybe pan == srcSpanFileName_maybe some_span - doContinue f GHC.SingleStep + Just pan -> doContinue (GHC.ModuleStep pan) -- | Returns the span of the largest tick containing the srcspan given enclosingTickSpan :: GhciMonad m => Module -> SrcSpan -> m RealSrcSpan @@ -3863,14 +3860,14 @@ traceCmd :: GhciMonad m => String -> m () traceCmd arg = withSandboxOnly ":trace" $ tr arg where - tr [] = doContinue (const True) GHC.RunAndLogSteps + tr [] = doContinue GHC.RunAndLogSteps tr expression = runStmt expression GHC.RunAndLogSteps >> return () continueCmd :: GhciMonad m => String -> m () -- #19157 continueCmd argLine = withSandboxOnly ":continue" $ case contSwitch (words argLine) of Left sdoc -> printForUser sdoc - Right mbCnt -> doContinue' (const True) GHC.RunToCompletion mbCnt + Right mbCnt -> doContinue' GHC.RunToCompletion mbCnt where contSwitch :: [String] -> Either SDoc (Maybe Int) contSwitch [ ] = Right Nothing @@ -3878,13 +3875,13 @@ continueCmd argLine = withSandboxOnly ":continue" $ contSwitch _ = Left $ text "After ':continue' only one ignore count is allowed" -doContinue :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> m () -doContinue pre step = doContinue' pre step Nothing +doContinue :: GhciMonad m => SingleStep -> m () +doContinue step = doContinue' step Nothing -doContinue' :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m () -doContinue' pre step mbCnt= do - runResult <- resume pre step mbCnt - _ <- afterRunStmt pre runResult +doContinue' :: GhciMonad m => SingleStep -> Maybe Int -> m () +doContinue' step mbCnt= do + runResult <- resume step mbCnt + _ <- afterRunStmt step runResult return () abandonCmd :: GhciMonad m => String -> m () @@ -4036,7 +4033,7 @@ backCmd arg | otherwise = liftIO $ putStrLn "Syntax: :back [num]" where back num = withSandboxOnly ":back" $ do - (names, _, pan, _) <- GHC.back num + (names, _, pan) <- GHC.back num printForUser $ text "Logged breakpoint at" <+> ppr pan printTypeOfNames names -- run the command set with ":set stop <cmd>" @@ -4050,7 +4047,7 @@ forwardCmd arg | otherwise = liftIO $ putStrLn "Syntax: :forward [num]" where forward num = withSandboxOnly ":forward" $ do - (names, ix, pan, _) <- GHC.forward num + (names, ix, pan) <- GHC.forward num printForUser $ (if (ix == 0) then text "Stopped at" else text "Logged breakpoint at") <+> ppr pan ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -401,14 +401,14 @@ runDecls' decls = do return Nothing) (Just <$> GHC.runParsedDecls decls) -resume :: GhciMonad m => (SrcSpan -> Bool) -> GHC.SingleStep -> Maybe Int -> m GHC.ExecResult -resume canLogSpan step mbIgnoreCnt = do +resume :: GhciMonad m => GHC.SingleStep -> Maybe Int -> m GHC.ExecResult +resume step mbIgnoreCnt = do st <- getGHCiState reifyGHCi $ \x -> withProgName (progname st) $ withArgs (args st) $ reflectGHCi x $ do - GHC.resumeExec canLogSpan step mbIgnoreCnt + GHC.resumeExec step mbIgnoreCnt -- -------------------------------------------------------------------------- -- timing & statistics ===================================== hadrian/bindist/Makefile ===================================== @@ -131,6 +131,7 @@ lib/settings : config.mk @echo ',("LLVM llc command", "$(SettingsLlcCommand)")' >> $@ @echo ',("LLVM opt command", "$(SettingsOptCommand)")' >> $@ @echo ',("LLVM llvm-as command", "$(SettingsLlvmAsCommand)")' >> $@ + @echo ',("LLVM llvm-as flags", "$(SettingsLlvmAsFlags)")' >> $@ @echo ',("Use inplace MinGW toolchain", "$(SettingsUseDistroMINGW)")' >> $@ @echo @echo ',("target RTS linker only supports shared libraries", "$(TargetRTSLinkerOnlySupportsSharedLibs)")' >> $@ ===================================== hadrian/cfg/system.config.in ===================================== @@ -85,6 +85,7 @@ settings-install_name_tool-command = @SettingsInstallNameToolCommand@ settings-llc-command = @SettingsLlcCommand@ settings-opt-command = @SettingsOptCommand@ settings-llvm-as-command = @SettingsLlvmAsCommand@ +settings-llvm-as-flags = @SettingsLlvmAsFlags@ settings-use-distro-mingw = @SettingsUseDistroMINGW@ target-has-libm = @TargetHasLibm@ ===================================== hadrian/src/Oracles/Setting.hs ===================================== @@ -91,6 +91,7 @@ data ToolchainSetting | ToolchainSetting_LlcCommand | ToolchainSetting_OptCommand | ToolchainSetting_LlvmAsCommand + | ToolchainSetting_LlvmAsFlags | ToolchainSetting_DistroMinGW -- | Look up the value of a 'Setting' in @cfg/system.config@, tracking the @@ -144,6 +145,7 @@ settingsFileSetting key = lookupSystemConfig $ case key of ToolchainSetting_LlcCommand -> "settings-llc-command" ToolchainSetting_OptCommand -> "settings-opt-command" ToolchainSetting_LlvmAsCommand -> "settings-llvm-as-command" + ToolchainSetting_LlvmAsFlags -> "settings-llvm-as-flags" ToolchainSetting_DistroMinGW -> "settings-use-distro-mingw" -- ROMES:TODO: This option doesn't seem to be in ghc-toolchain yet. It corresponds to EnableDistroToolchain -- | An expression that looks up the value of a 'Setting' in @cfg/system.config@, ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -528,6 +528,7 @@ generateSettings settingsFile = do , ("LLVM llc command", expr $ settingsFileSetting ToolchainSetting_LlcCommand) , ("LLVM opt command", expr $ settingsFileSetting ToolchainSetting_OptCommand) , ("LLVM llvm-as command", expr $ settingsFileSetting ToolchainSetting_LlvmAsCommand) + , ("LLVM llvm-as flags", expr $ settingsFileSetting ToolchainSetting_LlvmAsFlags) , ("Use inplace MinGW toolchain", expr $ settingsFileSetting ToolchainSetting_DistroMinGW) , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs) ===================================== libraries/ghc-internal/src/GHC/Internal/Pack.hs ===================================== @@ -12,95 +12,20 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- ⚠Warning: Starting @base-4.18@, this module is being deprecated. --- See https://gitlab.haskell.org/ghc/ghc/-/issues/21461 for more information. --- --- --- --- This module provides a small set of low-level functions for packing --- and unpacking a chunk of bytes. Used by code emitted by the compiler --- plus the prelude libraries. --- --- The programmer level view of packed strings is provided by a GHC --- system library PackedString. +-- This function is just used by `rts_mkString` -- ----------------------------------------------------------------------------- module GHC.Internal.Pack ( - -- (**) - emitted by compiler. - - packCString#, unpackCString, - unpackCString#, - unpackNBytes#, - unpackFoldrCString#, -- (**) - unpackAppendCString#, -- (**) ) where import GHC.Internal.Base -import GHC.Internal.List ( length ) -import GHC.Internal.ST import GHC.Internal.Ptr -data ByteArray ix = ByteArray ix ix ByteArray# -data MutableByteArray s ix = MutableByteArray ix ix (MutableByteArray# s) - unpackCString :: Ptr a -> [Char] unpackCString a@(Ptr addr) | a == nullPtr = [] | otherwise = unpackCString# addr - -packCString# :: [Char] -> ByteArray# -packCString# str = case (packString str) of { ByteArray _ _ bytes -> bytes } - -packString :: [Char] -> ByteArray Int -packString str = runST (packStringST str) - -packStringST :: [Char] -> ST s (ByteArray Int) -packStringST str = - let len = length str in - packNBytesST len str - -packNBytesST :: Int -> [Char] -> ST s (ByteArray Int) -packNBytesST (I# length#) str = - {- - allocate an array that will hold the string - (not forgetting the NUL byte at the end) - -} - new_ps_array (length# +# 1#) >>= \ ch_array -> - -- fill in packed string from "str" - fill_in ch_array 0# str >> - -- freeze the puppy: - freeze_ps_array ch_array length# - where - fill_in :: MutableByteArray s Int -> Int# -> [Char] -> ST s () - fill_in arr_in# idx [] = - write_ps_array arr_in# idx (chr# 0#) >> - return () - - fill_in arr_in# idx (C# c : cs) = - write_ps_array arr_in# idx c >> - fill_in arr_in# (idx +# 1#) cs - --- (Very :-) ``Specialised'' versions of some CharArray things... - -new_ps_array :: Int# -> ST s (MutableByteArray s Int) -write_ps_array :: MutableByteArray s Int -> Int# -> Char# -> ST s () -freeze_ps_array :: MutableByteArray s Int -> Int# -> ST s (ByteArray Int) - -new_ps_array size = ST $ \ s -> - case (newByteArray# size s) of { (# s2#, barr# #) -> - (# s2#, MutableByteArray bot bot barr# #) } - where - bot = errorWithoutStackTrace "new_ps_array" - -write_ps_array (MutableByteArray _ _ barr#) n ch = ST $ \ s# -> - case writeCharArray# barr# n ch s# of { s2# -> - (# s2#, () #) } - --- same as unsafeFreezeByteArray -freeze_ps_array (MutableByteArray _ _ arr#) len# = ST $ \ s# -> - case unsafeFreezeByteArray# arr# s# of { (# s2#, frozen# #) -> - (# s2#, ByteArray 0 (I# len#) frozen# #) } ===================================== m4/fp_settings.m4 ===================================== @@ -89,6 +89,7 @@ AC_DEFUN([FP_SETTINGS], SettingsLlcCommand="$LlcCmd" SettingsOptCommand="$OptCmd" SettingsLlvmAsCommand="$LlvmAsCmd" + SettingsLlvmAsFlags="$LlvmAsCmd" if test "$EnableDistroToolchain" = "YES"; then # If the user specified --enable-distro-toolchain then we just use the @@ -131,6 +132,7 @@ AC_DEFUN([FP_SETTINGS], SUBST_TOOLDIR([SettingsLlcCommand]) SUBST_TOOLDIR([SettingsOptCommand]) SUBST_TOOLDIR([SettingsLlvmAsCommand]) + SUBST_TOOLDIR([SettingsLlvmAsFlags]) fi # Mac-only tools @@ -171,5 +173,6 @@ AC_DEFUN([FP_SETTINGS], AC_SUBST(SettingsLlcCommand) AC_SUBST(SettingsOptCommand) AC_SUBST(SettingsLlvmAsCommand) + AC_SUBST(SettingsLlvmAsFlags) AC_SUBST(SettingsUseDistroMINGW) ]) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8bb9dd201cdb21ce925577a4823ef40e0665af5a...3ac8222607ba91e0de2eb22577b3c491d20b818b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8bb9dd201cdb21ce925577a4823ef40e0665af5a...3ac8222607ba91e0de2eb22577b3c491d20b818b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/5825e483/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 16:52:00 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 03 Mar 2025 11:52:00 -0500 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] 58 commits: Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. Message-ID: <67c5de30e10e4_277dc5c7d0845062@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - ffc711d2 by Apoorv Ingle at 2025-03-02T21:51:12-06:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail - - - - - a148416f by Apoorv Ingle at 2025-03-02T21:51:24-06:00 simplify data structures. remove doTcApp and applicative stmt fail blocks do not refer stmts - - - - - ee343350 by Simon Peyton Jones at 2025-03-02T21:52:21-06:00 - Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed. - Make `tcExpr` take a `Maybe HsThingRn` which will be passed on to tcApp and used by splitHsApps to determine a more accurate `AppCtx` - `tcXExpr` is less hacky now - - - - - cbfe38c6 by Apoorv Ingle at 2025-03-02T21:52:29-06:00 remove HsExprRn from VAExpansion - - - - - adefa726 by Apoorv Ingle at 2025-03-02T21:52:29-06:00 Revert "remove HsExprRn from VAExpansion" This reverts commit 9648167a936a329d3876de71235f476e5836ddf8. - - - - - a45a4891 by Apoorv Ingle at 2025-03-02T21:52:29-06:00 do not look through HsExpansion applications - - - - - 0dbe4b10 by Apoorv Ingle at 2025-03-03T10:42:03-06:00 kill OrigPat and remove HsThingRn From VAExpansion - - - - - 287 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.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/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - ghc/GHCi/UI.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Parser.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/linker/MachO.c - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/T16135.hs - − testsuite/tests/ado/T16135.stderr - + testsuite/tests/ado/T24406.hs - testsuite/tests/ado/ado002.stderr - testsuite/tests/ado/ado003.stderr - testsuite/tests/ado/ado004.stderr - testsuite/tests/ado/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/determinism/determ021/determ021.stdout - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break029.script - testsuite/tests/ghci.debugger/scripts/break029.stdout - testsuite/tests/hiefile/should_run/T23540.stdout - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod185.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/all.T - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Transform.hs - − utils/deriveConstants/Makefile - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0753130cda9a59b573942f06868a1b89da20a0b3...0dbe4b10a497adf3592f4be034bf7cb52bcf2110 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0753130cda9a59b573942f06868a1b89da20a0b3...0dbe4b10a497adf3592f4be034bf7cb52bcf2110 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/3ed91bcb/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 16:54:25 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 03 Mar 2025 11:54:25 -0500 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] 3 commits: - Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed. Message-ID: <67c5dec138ec6_277dc5c5cc445316@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: f5c7773f by Simon Peyton Jones at 2025-03-03T10:53:45-06:00 - Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed. - Make `tcExpr` take a `Maybe HsThingRn` which will be passed on to tcApp and used by splitHsApps to determine a more accurate `AppCtx` - `tcXExpr` is less hacky now This reverts commit 9648167a936a329d3876de71235f476e5836ddf8. - - - - - 141bbcbb by Apoorv Ingle at 2025-03-03T10:54:00-06:00 do not look through HsExpansion applications - - - - - 1229a9f1 by Apoorv Ingle at 2025-03-03T10:54:00-06:00 kill OrigPat and remove HsThingRn From VAExpansion - - - - - 9 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Types/Origin.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -530,26 +530,21 @@ type instance XXExpr GhcTc = XXExprGhcTc -- See Note [Handling overloaded and rebindable constructs] in `GHC.Rename.Expr` data HsThingRn = OrigExpr (HsExpr GhcRn) -- ^ The source, user written, expression | OrigStmt (ExprLStmt GhcRn) HsDoFlavour -- ^ which kind of do-block did this statement come from - | OrigPat (LPat GhcRn) -- ^ The source, user written, pattern - HsDoFlavour -- ^ which kind of do-block did this statement come from -isHsThingRnExpr, isHsThingRnStmt, isHsThingRnPat :: HsThingRn -> Bool +isHsThingRnExpr, isHsThingRnStmt :: HsThingRn -> Bool isHsThingRnExpr (OrigExpr{}) = True isHsThingRnExpr _ = False isHsThingRnStmt (OrigStmt{}) = True isHsThingRnStmt _ = False -isHsThingRnPat (OrigPat{}) = True -isHsThingRnPat _ = False - data XXExprGhcRn = ExpandedThingRn { xrn_orig :: HsThingRn -- The original source thing to be used for error messages , xrn_expanded :: HsExpr GhcRn -- The compiler generated expanded thing } | PopErrCtxt -- A hint for typechecker to pop - {-# UNPACK #-} !(LHsExpr GhcRn) -- the top of the error context stack + {-# UNPACK #-} !(HsExpr GhcRn) -- the top of the error context stack -- Does not presist post renaming phase -- See Part 3. of Note [Expanding HsDo with XXExprGhcRn] -- in `GHC.Tc.Gen.Do` @@ -558,15 +553,6 @@ data XXExprGhcRn -- Note [Record selectors in the AST] - --- | Wrap a located expression with a `PopErrCtxt` -mkPopErrCtxtExpr :: LHsExpr GhcRn -> HsExpr GhcRn -mkPopErrCtxtExpr a = XExpr (PopErrCtxt a) - --- | Wrap a located expression with a PopSrcExpr with an appropriate location -mkPopErrCtxtExprAt :: SrcSpanAnnA -> LHsExpr GhcRn -> LHsExpr GhcRn -mkPopErrCtxtExprAt loc a = L loc $ mkPopErrCtxtExpr a - -- | Build an expression using the extension constructor `XExpr`, -- and the two components of the expansion: original expression and -- expanded expressions. @@ -588,30 +574,6 @@ mkExpandedStmt mkExpandedStmt oStmt flav eExpr = XExpr (ExpandedThingRn { xrn_orig = OrigStmt oStmt flav , xrn_expanded = eExpr }) -mkExpandedPatRn - :: LPat GhcRn -- ^ source pattern - -> HsDoFlavour -- ^ source statement do flavour - -> HsExpr GhcRn -- ^ expanded expression - -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedPatRn oPat flav eExpr = XExpr (ExpandedThingRn { xrn_orig = OrigPat oPat flav - , xrn_expanded = eExpr }) - --- | Build an expression using the extension constructor `XExpr`, --- and the two components of the expansion: original do stmt and --- expanded expression and associate it with a provided location -mkExpandedStmtAt - :: Bool -- ^ Wrap this expansion with a pop? - -> SrcSpanAnnA -- ^ Location for the expansion expression - -> ExprLStmt GhcRn -- ^ source statement - -> HsDoFlavour -- ^ the flavour of the statement - -> HsExpr GhcRn -- ^ expanded expression - -> LHsExpr GhcRn -- ^ suitably wrapped located 'XXExprGhcRn' -mkExpandedStmtAt addPop loc oStmt flav eExpr - | addPop - = mkPopErrCtxtExprAt loc (L loc $ mkExpandedStmt oStmt flav eExpr) - | otherwise - = L loc $ mkExpandedStmt oStmt flav eExpr - data XXExprGhcTc = WrapExpr -- Type and evidence application and abstractions HsWrapper (HsExpr GhcTc) @@ -664,6 +626,12 @@ mkExpandedStmtTc -> HsExpr GhcTc -- ^ suitably wrapped 'XXExprGhcRn' mkExpandedStmtTc oStmt flav eExpr = XExpr (ExpandedThingTc (OrigStmt oStmt flav) eExpr) +mkExpandedTc + :: HsThingRn -- ^ source do statement + -> HsExpr GhcTc -- ^ expanded typechecked expression + -> HsExpr GhcTc -- ^ suitably wrapped 'XXExprGhcRn' +mkExpandedTc o e = XExpr (ExpandedThingTc o e) + {- ********************************************************************* * * Pretty-printing expressions @@ -918,7 +886,6 @@ instance Outputable HsThingRn where = case thing of OrigExpr x -> ppr_builder "<OrigExpr>:" x OrigStmt x _ -> ppr_builder "<OrigStmt>:" x - OrigPat x _ -> ifPprDebug (braces (text "<OrigPat>:" <+> parens (ppr x))) (ppr x) where ppr_builder prefix x = ifPprDebug (braces (text prefix <+> parens (ppr x))) (ppr x) instance Outputable XXExprGhcRn where @@ -966,7 +933,7 @@ ppr_infix_expr _ = Nothing ppr_infix_expr_rn :: XXExprGhcRn -> Maybe SDoc ppr_infix_expr_rn (ExpandedThingRn thing _) = ppr_infix_hs_expansion thing -ppr_infix_expr_rn (PopErrCtxt (L _ a)) = ppr_infix_expr a +ppr_infix_expr_rn (PopErrCtxt a) = ppr_infix_expr a ppr_infix_expr_rn (HsRecSelRn f) = Just (pprInfixOcc f) ppr_infix_expr_tc :: XXExprGhcTc -> Maybe SDoc @@ -1083,7 +1050,7 @@ hsExprNeedsParens prec = go go_x_rn :: XXExprGhcRn -> Bool go_x_rn (ExpandedThingRn thing _ ) = hsExpandedNeedsParens thing - go_x_rn (PopErrCtxt (L _ a)) = hsExprNeedsParens prec a + go_x_rn (PopErrCtxt a) = hsExprNeedsParens prec a go_x_rn (HsRecSelRn{}) = False hsExpandedNeedsParens :: HsThingRn -> Bool @@ -1135,9 +1102,9 @@ isAtomicHsExpr (XExpr x) go_x_tc (HsRecSelTc{}) = True go_x_rn :: XXExprGhcRn -> Bool - go_x_rn (ExpandedThingRn thing _) = isAtomicExpandedThingRn thing - go_x_rn (PopErrCtxt (L _ a)) = isAtomicHsExpr a - go_x_rn (HsRecSelRn{}) = True + go_x_rn (ExpandedThingRn thing _) = isAtomicExpandedThingRn thing + go_x_rn (PopErrCtxt a) = isAtomicHsExpr a + go_x_rn (HsRecSelRn{}) = True isAtomicExpandedThingRn :: HsThingRn -> Bool isAtomicExpandedThingRn (OrigExpr e) = isAtomicHsExpr e ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -1716,7 +1716,7 @@ repE e@(XExpr (ExpandedThingRn o x)) | otherwise = notHandled (ThExpressionForm e) -repE (XExpr (PopErrCtxt (L _ e))) = repE e +repE (XExpr (PopErrCtxt e)) = repE e repE (XExpr (HsRecSelRn (FieldOcc _ (L _ x)))) = repE (HsVar noExtField (noLocA x)) repE e@(HsPragE _ (HsPragSCC {}) _) = notHandled (ThCostCentres e) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -2267,7 +2267,7 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do -- Need 'pureAName' and not 'returnMName' here, so that it requires -- 'Applicative' and not 'Monad' whenever possible (until #20540 is fixed). (pure_name, _) <- lookupQualifiedDoName (HsDoStmt ctxt) pureAName - let expr = noLocA (HsApp noExtField (noLocA ret) tup) + let expr = noLocA (genHsApps pure_name [tup]) return (expr, emptyFVs) return ( ApplicativeArgMany { xarg_app_arg_many = noExtField ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -181,7 +181,7 @@ tcInferSigma inst (L loc rn_expr) do { (fun@(rn_fun,fun_ctxt), rn_args) <- splitHsApps rn_expr ; do_ql <- wantQuickLook rn_fun ; (tc_fun, fun_sigma) <- tcInferAppHead fun - ; (inst_args, app_res_sigma) <- tcInstFun do_ql inst (tc_fun, fun_ctxt) fun_sigma rn_args + ; (inst_args, app_res_sigma) <- tcInstFun do_ql inst (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args ; _ <- tcValArgs do_ql inst_args ; return app_res_sigma } @@ -409,7 +409,7 @@ tcApp rn_expr exp_res_ty ; (inst_args, app_res_rho) <- setQLInstLevel do_ql $ -- See (TCAPP1) and (TCAPP2) in -- Note [tcApp: typechecking applications] - tcInstFun do_ql True tc_head fun_sigma rn_args + tcInstFun do_ql True (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args ; case do_ql of NoQL -> do { traceTc "tcApp:NoQL" (ppr rn_fun $$ ppr app_res_rho) @@ -418,6 +418,7 @@ tcApp rn_expr exp_res_ty -- See Note [Unify with expected type before typechecking arguments] ; res_wrap <- checkResultTy rn_expr tc_head inst_args app_res_rho exp_res_ty + -- Step 4.2: typecheck the arguments ; tc_args <- tcValArgs NoQL inst_args -- Step 4.3: wrap up @@ -513,7 +514,7 @@ checkResultTy rn_expr (tc_fun, fun_ctxt) inst_args app_res_rho (Check res_ty) -- Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr perhaps_add_res_ty_ctxt thing_inside | insideExpansion fun_ctxt - = addHeadCtxt fun_ctxt thing_inside + = thing_inside | otherwise = addFunResCtxt tc_fun inst_args app_res_rho (mkCheckExpType res_ty) $ thing_inside @@ -539,12 +540,7 @@ tcValArg do_ql (EValArg { ea_ctxt = ctxt , ea_arg = larg@(L arg_loc arg) , ea_arg_ty = sc_arg_ty }) = addArgCtxt ctxt larg $ - do { traceTc "tcValArg" $ - vcat [ ppr ctxt - , text "arg type:" <+> ppr sc_arg_ty - , text "arg:" <+> ppr larg ] - - -- Crucial step: expose QL results before checking exp_arg_ty + do { -- Crucial step: expose QL results before checking exp_arg_ty -- So far as the paper is concerned, this step applies -- the poly-substitution Theta, learned by QL, so that we -- "see" the polymorphism in that argument type. E.g. @@ -553,14 +549,21 @@ tcValArg do_ql (EValArg { ea_ctxt = ctxt -- Then Theta = [p :-> forall a. a->a], and we want -- to check 'e' with expected type (forall a. a->a) -- See Note [Instantiation variables are short lived] - ; Scaled mult exp_arg_ty <- case do_ql of + Scaled mult exp_arg_ty <- case do_ql of DoQL -> liftZonkM $ zonkScaledTcType sc_arg_ty NoQL -> return sc_arg_ty + ; traceTc "tcValArg {" $ + vcat [ text "ctxt:" <+> ppr ctxt + , text "sigma_type" <+> ppr (mkCheckExpType exp_arg_ty) + , text "arg:" <+> ppr larg + ] + -- Now check the argument ; arg' <- tcScalingUsage mult $ tcPolyExpr arg (mkCheckExpType exp_arg_ty) - + ; traceTc "tcValArg" $ vcat [ ppr arg' + , text "}" ] ; return (EValArg { ea_ctxt = ctxt , ea_arg = L arg_loc arg' , ea_arg_ty = noExtField }) } @@ -640,26 +643,21 @@ tcInstFun :: QLFlag -- in tcInferSigma, which is used only to implement :type -- Otherwise we do eager instantiation; in Fig 5 of the paper -- |-inst returns a rho-type - -> (HsExpr GhcTc, AppCtxt) + -> (HsExpr GhcTc, HsExpr GhcRn, AppCtxt) -> TcSigmaType -> [HsExprArg 'TcpRn] -> TcM ( [HsExprArg 'TcpInst] , TcSigmaType ) -- This crucial function implements the |-inst judgement in Fig 4, plus the -- modification in Fig 5, of the QL paper: -- "A quick look at impredicativity" (ICFP'20). -tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args +tcInstFun do_ql inst_final (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args = do { traceTc "tcInstFun" (vcat [ text "tc_fun" <+> ppr tc_fun , text "fun_sigma" <+> ppr fun_sigma - , text "fun_ctxt" <+> ppr fun_ctxt , text "args:" <+> ppr rn_args , text "do_ql" <+> ppr do_ql ]) ; go 1 [] fun_sigma rn_args } where - fun_orig = case fun_ctxt of - VAExpansion (OrigStmt{}) _ _ -> DoOrigin - VAExpansion (OrigPat pat _) _ _ -> DoPatOrigin pat - VAExpansion (OrigExpr e) _ _ -> exprCtOrigin e - VACall e _ _ -> exprCtOrigin e + fun_orig = exprCtOrigin rn_fun -- These are the type variables which must be instantiated to concrete -- types. See Note [Representation-polymorphic Ids with no binding] @@ -821,9 +819,7 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args -- Rule IARG from Fig 4 of the QL paper: go1 pos acc fun_ty (EValArg { ea_arg = arg, ea_ctxt = ctxt } : rest_args) - = do { let herald = case fun_ctxt of - VAExpansion (OrigStmt{}) _ _ -> ExpectedFunTySyntaxOp DoOrigin tc_fun - _ -> ExpectedFunTyArg (HsExprTcThing tc_fun) (unLoc arg) + = do { let herald = ExpectedFunTyArg (HsExprTcThing tc_fun) (unLoc arg) ; (wrap, arg_ty, res_ty) <- -- NB: matchActualFunTy does the rep-poly check. -- For example, suppose we have f :: forall r (a::TYPE r). a -> Int @@ -880,7 +876,7 @@ looks_like_type_arg _ = False addArgCtxt :: AppCtxt -> LHsExpr GhcRn -> TcM a -> TcM a --- There are four cases: +-- There are 3 cases: -- 1. In the normal case, we add an informative context -- "In the third argument of f, namely blah" -- 2. If we are deep inside generated code (`isGeneratedCode` is `True`) @@ -889,42 +885,21 @@ addArgCtxt :: AppCtxt -> LHsExpr GhcRn -- "In the expression: arg" -- Unless the arg is also a generated thing, in which case do nothing. -- See Note [Rebindable syntax and XXExprGhcRn] in GHC.Hs.Expr --- 3. We are in an expanded `do`-block's non-bind statement --- we simply add the statement context --- "In the statement of the `do`-block .." --- 4. We are in an expanded do block's bind statement --- a. Then either we are typechecking the first argument of the bind which is user located --- so we set the location to be that of the argument --- b. Or, we are typechecking the second argument which would be a generated lambda --- so we set the location to be whatever the location in the context is +-- 3. We are in an expanded `do`-block statement +-- Do nothing as we have already added the error +-- context in GHC.Tc.Do.tcXExpr -- See Note [Expanding HsDo with XXExprGhcRn] in GHC.Tc.Gen.Do --- For future: we need a cleaner way of doing this bit of adding the right error context. --- There is a delicate dance of looking at source locations and reconstructing --- whether the piece of code is a `do`-expanded code or some other expanded code. addArgCtxt ctxt (L arg_loc arg) thing_inside = do { in_generated_code <- inGeneratedCode + ; traceTc "addArgCtxt" (vcat [ text "generated:" <+> ppr in_generated_code + , text "arg: " <+> ppr arg + , text "arg_loc" <+> ppr arg_loc]) ; case ctxt of VACall fun arg_no _ | not in_generated_code -> do setSrcSpanA arg_loc $ addErrCtxt (FunAppCtxt (FunAppCtxtExpr fun arg) arg_no) $ thing_inside - VAExpansion (OrigStmt (L _ stmt@(BindStmt {})) flav) _ loc - | isGeneratedSrcSpan (locA arg_loc) -- This arg is the second argument to generated (>>=) - -> setSrcSpan loc $ - addStmtCtxt stmt flav $ - thing_inside - | otherwise -- This arg is the first argument to generated (>>=) - -> setSrcSpanA arg_loc $ - addStmtCtxt stmt flav $ - thing_inside - VAExpansion (OrigStmt (L _ (XStmtLR (ApplicativeStmt{}))) _) _ _ - -> thing_inside - VAExpansion (OrigStmt (L loc stmt) flav) _ _ - -> setSrcSpanA loc $ - addStmtCtxt stmt flav $ - thing_inside - _ -> setSrcSpanA arg_loc $ addExprCtxt arg $ -- Auto-suppressed if arg_loc is generated thing_inside } @@ -1761,7 +1736,7 @@ quickLookArg1 ctxt larg@(L _ arg) sc_arg_ty@(Scaled _ orig_arg_rho) ; do_ql <- wantQuickLook rn_fun ; ((inst_args, app_res_rho), wanted) <- captureConstraints $ - tcInstFun do_ql True tc_head fun_sigma rn_args + tcInstFun do_ql True (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args -- We must capture type-class and equality constraints here, but -- not equality constraints. See (QLA6) in Note [Quick Look at -- value arguments] ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -45,58 +45,56 @@ import Data.List ((\\)) * * ************************************************************************ -} - -- | Expand the `do`-statments into expressions right after renaming -- so that they can be typechecked. -- See Note [Expanding HsDo with XXExprGhcRn] below for `HsDo` specific commentary -- and Note [Handling overloaded and rebindable constructs] for high level commentary expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (HsExpr GhcRn) -expandDoStmts doFlav stmts = unLoc <$> expand_do_stmts False doFlav stmts +expandDoStmts doFlav stmts = expand_do_stmts doFlav stmts -- | The main work horse for expanding do block statements into applications of binds and thens -- See Note [Expanding HsDo with XXExprGhcRn] -expand_do_stmts :: Bool -> HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) +expand_do_stmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (HsExpr GhcRn) -expand_do_stmts _ ListComp _ = +expand_do_stmts ListComp _ = pprPanic "expand_do_stmts: impossible happened. ListComp" empty -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty - -expand_do_stmts _ _ (stmt@(L _ (TransStmt {})):_) = +expand_do_stmts _ (stmt@(L _ (TransStmt {})):_) = pprPanic "expand_do_stmts: TransStmt" $ ppr stmt -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ _ (stmt@(L _ (ParStmt {})):_) = +expand_do_stmts _ (stmt@(L _ (ParStmt {})):_) = pprPanic "expand_do_stmts: ParStmt" $ ppr stmt -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))] +expand_do_stmts _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty + +expand_do_stmts flav [stmt@(L _loc (LastStmt _ (L body_loc body) _ ret_expr))] -- See Note [Expanding HsDo with XXExprGhcRn] Equation (5) below -- last statement of a list comprehension, needs to explicitly return it -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt` | NoSyntaxExprRn <- ret_expr -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt - = return $ mkExpandedStmtAt addPop loc stmt flav body - + = return $ mkExpandedStmt stmt flav body | SyntaxExprRn ret <- ret_expr -- -- ------------------------------------------------ -- return e ~~> return e -- to make T18324 work = do let expansion = genHsApp ret (L body_loc body) - return $ mkExpandedStmtAt addPop loc stmt flav expansion + return $ mkExpandedStmt stmt flav expansion -expand_do_stmts addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) = +expand_do_stmts doFlavour (stmt@(L _ (LetStmt _ bs)) : lstmts) = -- See Note [Expanding HsDo with XXExprGhcRn] Equation (3) below -- stmts ~~> stmts' -- ------------------------------------------------ -- let x = e ; stmts ~~> let x = e in stmts' - do expand_stmts <- expand_do_stmts True doFlavour lstmts - let expansion = genHsLet bs expand_stmts - return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion + do expand_stmts_expr <- expand_do_stmts doFlavour lstmts + let expansion = genHsLet bs (genPopErrCtxtExpr expand_stmts_expr) + return $ mkExpandedStmt stmt doFlavour expansion -expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) +expand_do_stmts doFlavour (stmt@(L _loc (BindStmt xbsrn pat e)): lstmts) | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn , fail_op <- xbsrn_failOp xbsrn -- See Note [Expanding HsDo with XXExprGhcRn] Equation (2) below @@ -105,29 +103,29 @@ expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) -- _ -> fail "Pattern match failure .." -- ------------------------------------------------------- -- pat <- e ; stmts ~~> (>>=) e f - = do expand_stmts <- expand_do_stmts True doFlavour lstmts - failable_expr <- mk_failable_expr False doFlavour pat expand_stmts fail_op + = do expand_stmts_expr <- expand_do_stmts doFlavour lstmts + failable_expr <- mk_failable_expr doFlavour pat (genPopErrCtxtExpr expand_stmts_expr) fail_op let expansion = genHsExpApps bind_op -- (>>=) [ e , failable_expr ] - return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion + return $ mkExpandedStmt stmt doFlavour expansion | otherwise = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr stmt) -expand_do_stmts addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) = +expand_do_stmts doFlavour (stmt@(L _loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) = -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr -- See Note [Expanding HsDo with XXExprGhcRn] Equation (1) below -- stmts ~~> stmts' -- ---------------------------------------------- -- e ; stmts ~~> (>>) e stmts' - do expand_stmts_expr <- expand_do_stmts True doFlavour lstmts + do expand_stmts_expr <- expand_do_stmts doFlavour lstmts let expansion = genHsExpApps then_op -- (>>) - [ e - , expand_stmts_expr ] - return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion + [ e + , genPopErrCtxtExpr $ expand_stmts_expr ] + return $ mkExpandedStmt stmt doFlavour expansion -expand_do_stmts _ doFlavour +expand_do_stmts doFlavour ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts , recS_later_ids = later_ids -- forward referenced local ids , recS_rec_ids = local_ids -- ids referenced outside of the rec block @@ -147,14 +145,14 @@ expand_do_stmts _ doFlavour -- -> do { rec_stmts -- ; return (local_only_ids ++ later_ids) } )) -- (\ [ local_only_ids ++ later_ids ] -> stmts') - do expand_stmts <- expand_do_stmts True doFlavour lstmts + do expand_stmts_expr <- expand_do_stmts doFlavour lstmts -- NB: No need to wrap the expansion with an ExpandedStmt -- as we want to flatten the rec block statements into its parent do block anyway - return $ mkHsApps (wrapGenSpan bind_fun) -- (>>=) - [ (wrapGenSpan mfix_fun) `mkHsApp` mfix_expr -- (mfix (do block)) - , genHsLamDoExp doFlavour [ mkBigLHsVarPatTup all_ids ] -- (\ x -> - expand_stmts -- stmts') - ] + return $ unLoc (mkHsApps (wrapGenSpan bind_fun) -- (>>=) + [ (wrapGenSpan mfix_fun) `mkHsApp` mfix_expr -- (mfix (do block)) + , genHsLamDoExp doFlavour [ mkBigLHsVarPatTup all_ids ] -- (\ x -> + (wrapGenSpan expand_stmts_expr) -- stmts') + ]) where local_only_ids = local_ids \\ later_ids -- get unique local rec ids; -- local rec ids and later ids can overlap @@ -175,7 +173,7 @@ expand_do_stmts _ doFlavour -- NB: LazyPat because we do not want to eagerly evaluate the pattern -- and potentially loop forever -expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) = +expand_do_stmts doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) = -- See Note [Applicative BodyStmt] -- -- stmts ~~> stmts' @@ -185,13 +183,13 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join) -- Very similar to HsToCore.Expr.dsDo -- args are [(<$>, e1), (<*>, e2), .., ] - do { xexpr <- expand_do_stmts False doFlavour lstmts + do { xexpr <- expand_do_stmts doFlavour lstmts -- extracts pats and arg bodies (rhss) from args ; (pats_can_fail, rhss) <- unzip <$> mapM (do_arg . snd) args -- add blocks for failable patterns - ; body_with_fails <- foldrM match_args xexpr pats_can_fail + ; body_with_fails <- foldrM match_args (wrapGenSpan xexpr) pats_can_fail -- builds (((body <$> e1) <*> e2) ...) ; let expand_ado_expr = foldl mk_apps body_with_fails (zip (map fst args) rhss) @@ -205,7 +203,7 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join) , text "lstmts:" <+> ppr lstmts , text "mb_join:" <+> ppr mb_join , text "expansion:" <+> ppr final_expr]) - ; return final_expr + ; return $ unLoc final_expr } where @@ -214,7 +212,7 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join) { xarg_app_arg_one = mb_fail_op , app_arg_pattern = pat , arg_expr = (L rhs_loc rhs) }) = - do let xx_expr = mkExpandedStmtAt addPop (noAnnSrcSpan generatedSrcSpan) stmt doFlavour rhs + do let xx_expr = mkExpandedStmtAt rhs_loc stmt doFlavour rhs traceTc "do_arg" (text "OneArg" <+> vcat [ppr pat, ppr xx_expr]) return ((pat, mb_fail_op) , xx_expr) @@ -223,13 +221,14 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join) , final_expr = ret@(L ret_loc _) , bv_pattern = pat , stmt_context = ctxt }) = - do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts addPop ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret]) - ; traceTc "do_arg" (text "ManyArg" <+> ppr addPop <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr]) + do { xx_expr <- expand_do_stmts ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret] + ; traceTc "do_arg" (text "ManyArg" + <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr]) ; return ((pat, Nothing) - , xx_expr) } + , wrapGenSpan xx_expr) } - match_args :: (LPat GhcRn, FailOperator GhcRn) -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn) - match_args (pat, fail_op) body = mk_failable_expr addPop doFlavour pat body fail_op + match_args :: (LPat GhcRn, FailOperator GhcRn) -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn) + match_args (pat, fail_op) body = mk_failable_expr doFlavour pat body fail_op mk_apps :: LHsExpr GhcRn -> (SyntaxExprRn, LHsExpr GhcRn) -> LHsExpr GhcRn mk_apps l_expr (op, r_expr) = @@ -237,31 +236,28 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join) SyntaxExprRn op -> wrapGenSpan $ genHsExpApps op [ l_expr, r_expr ] NoSyntaxExprRn -> pprPanic "expand_do_stmts applicative op:" (ppr op) -expand_do_stmts _ _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts) +expand_do_stmts _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts) -- checks the pattern `pat` for irrefutability which decides if we need to wrap it with a fail block -mk_failable_expr :: Bool -> HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn) -mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op = +mk_failable_expr :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn) +mk_failable_expr doFlav lpat expr@(L _exprloc _) fail_op = do { is_strict <- xoptM LangExt.Strict ; hscEnv <- getTopEnv ; rdrEnv <- getGlobalRdrEnv ; comps <- getCompleteMatchesTcM ; let irrf_pat = isIrrefutableHsPat is_strict (irrefutableConLikeRn hscEnv rdrEnv comps) lpat - ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat + ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr lpat , text "isIrrefutable:" <+> ppr irrf_pat ]) - ; let xexpr | addPop = mkPopErrCtxtExprAt exprloc expr - | otherwise = expr ; if irrf_pat -- don't wrap with fail block if -- the pattern is irrefutable - then case pat of - (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] xexpr - _ -> return $ genHsLamDoExp doFlav [lpat] xexpr - - else L loc <$> mk_fail_block doFlav lpat expr fail_op + then return $ genHsLamDoExp doFlav [lpat] expr + else wrapGenSpan <$> mk_fail_block doFlav lpat expr fail_op } --- makes the fail block with a given fail_op +-- | Makes the fail block with a given fail_op +-- mk_fail_block pat rhs fail builds +-- \x. case x of {pat -> rhs; _ -> fail "Pattern match failure..."} mk_fail_block :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = @@ -273,12 +269,11 @@ mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = where fail_alt_case :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> LMatch GhcRn (LHsExpr GhcRn) fail_alt_case dflags pat fail_op = genHsCaseAltDoExp doFlav (L ploc $ WildPat noExtField) $ - L ploc (fail_op_expr dflags pat fail_op) + wrapGenSpan (fail_op_expr dflags pat fail_op) fail_op_expr :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> HsExpr GhcRn fail_op_expr dflags pat fail_op - = mkExpandedPatRn pat doFlav $ - genHsApp fail_op (mk_fail_msg_expr dflags pat) + = genHsApp fail_op (mk_fail_msg_expr dflags pat) mk_fail_msg_expr :: DynFlags -> LPat GhcRn -> LHsExpr GhcRn mk_fail_msg_expr dflags pat @@ -341,10 +336,10 @@ They capture the essence of statement expansions as implemented in `expand_do_st (2) DO〠p <- e; ss 】 = if p is irrefutable then ‹ExpansionStmt (p <- e)› - (>>=) s (‹PopExprCtxt›(\ p -> DO〠ss 】)) + (>>=) s ((\ p -> ‹PopExprCtxt› DO〠ss 】)) else ‹ExpansionStmt (p <- e)› - (>>=) s (‹PopExprCtxt›(\case p -> DO〠ss 】 - _ -> fail "pattern p failure")) + (>>=) s ((\case p -> ‹PopExprCtxt› DO〠ss 】 + _ -> fail "pattern p failure")) (3) DO〠let x = e; ss 】 = ‹ExpansionStmt (let x = e)› (let x = e in (‹PopErrCtxt›DO〠ss 】)) @@ -561,3 +556,23 @@ It stores the original statement (with location) and the expanded expression We hence use a tag `GenReason` in `Ghc.Tc.Origin`. When typechecking a `HsLam` in `Tc.Gen.Expr.tcExpr` the `match_ctxt` is set to a `StmtCtxt` if `GenOrigin` is a `DoExpansionOrigin`. -} + + +-- | Wrap a located expression with a `PopErrCtxt` +mkPopErrCtxtExpr :: HsExpr GhcRn -> HsExpr GhcRn +mkPopErrCtxtExpr a = XExpr (PopErrCtxt a) + +genPopErrCtxtExpr :: HsExpr GhcRn -> LHsExpr GhcRn +genPopErrCtxtExpr a = wrapGenSpan $ mkPopErrCtxtExpr a + +-- | Build an expression using the extension constructor `XExpr`, +-- and the two components of the expansion: original do stmt and +-- expanded expression and associate it with a provided location +mkExpandedStmtAt + :: SrcSpanAnnA + -> ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour -- ^ the flavour of the statement + -> HsExpr GhcRn -- ^ expanded expression + -> LHsExpr GhcRn -- ^ suitably wrapped located 'XXExprGhcRn' +mkExpandedStmtAt loc oStmt flav eExpr + = L loc $ mkExpandedStmt oStmt flav eExpr ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -739,33 +739,19 @@ tcExpr (SectionR {}) ty = pprPanic "tcExpr:SectionR" (ppr ty) tcXExpr :: XXExprGhcRn -> ExpRhoType -> TcM (HsExpr GhcTc) -tcXExpr (PopErrCtxt (L loc e)) res_ty +tcXExpr (PopErrCtxt e) res_ty = popErrCtxt $ -- See Part 3 of Note [Expanding HsDo with XXExprGhcRn] in `GHC.Tc.Gen.Do` - setSrcSpanA loc $ tcExpr e res_ty -tcXExpr xe@(ExpandedThingRn o e') res_ty - | OrigStmt ls@(L loc s) flav <- o - , HsLet x binds e <- e' - = do { (binds', e') <- setSrcSpanA loc $ - addStmtCtxt s flav $ - tcLocalBinds binds $ - tcMonoExprNC e res_ty -- NB: Do not call tcMonoExpr here as it adds - -- a duplicate error context - ; return $ mkExpandedStmtTc ls flav (HsLet x binds' e') - } - - | OrigStmt s@(L loc LastStmt{}) flav <- o - = setSrcSpanA loc $ - addStmtCtxt (unLoc s) flav $ - mkExpandedStmtTc s flav <$> tcApp e' res_ty - - | OrigStmt ls@(L loc _) flav <- o - = setSrcSpanA loc $ - mkExpandedStmtTc ls flav <$> tcApp (XExpr xe) res_ty +tcXExpr (ExpandedThingRn o e) res_ty + = addThingCtxt o $ + mkExpandedTc o <$> -- necessary for breakpoints + tcExpr e res_ty +-- For record selection, etc tcXExpr xe res_ty = tcApp (XExpr xe) res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -28,7 +28,7 @@ module GHC.Tc.Gen.Head , nonBidirectionalErr , pprArgInst - , addHeadCtxt, addExprCtxt, addStmtCtxt, addFunResCtxt ) where + , addHeadCtxt, addThingCtxt, addExprCtxt, addStmtCtxt, addFunResCtxt ) where import {-# SOURCE #-} GHC.Tc.Gen.Expr( tcExpr, tcCheckPolyExprNC, tcPolyLExprSig ) import {-# SOURCE #-} GHC.Tc.Gen.Splice( getUntypedSpliceBody ) @@ -210,9 +210,6 @@ data EWrap = EPar AppCtxt data AppCtxt = VAExpansion - HsThingRn - SrcSpan - SrcSpan | VACall (HsExpr GhcRn) Int -- In the third argument of function f @@ -248,19 +245,19 @@ a second time. -} appCtxtLoc :: AppCtxt -> SrcSpan -appCtxtLoc (VAExpansion _ l _) = l +appCtxtLoc VAExpansion = generatedSrcSpan appCtxtLoc (VACall _ _ l) = l insideExpansion :: AppCtxt -> Bool insideExpansion (VAExpansion {}) = True -insideExpansion (VACall _ _ src) = isGeneratedSrcSpan src +insideExpansion (VACall _ _ loc) = isGeneratedSrcSpan loc instance Outputable QLFlag where ppr DoQL = text "DoQL" ppr NoQL = text "NoQL" instance Outputable AppCtxt where - ppr (VAExpansion e l _) = text "VAExpansion" <+> ppr e <+> ppr l + ppr VAExpansion = text "VAExpansion" ppr (VACall f n l) = text "VACall" <+> int n <+> ppr f <+> ppr l type family XPass (p :: TcPass) where @@ -283,6 +280,7 @@ addArgWrap wrap args | isIdHsWrapper wrap = args | otherwise = EWrap (EHsWrap wrap) : args + splitHsApps :: HsExpr GhcRn -> TcM ( (HsExpr GhcRn, AppCtxt) -- Head , [HsExprArg 'TcpRn]) -- Args @@ -297,14 +295,14 @@ splitHsApps e = go e (top_ctxt 0 e) [] -- Always returns VACall fun n_val_args noSrcSpan -- to initialise the argument splitting in 'go' -- See Note [AppCtxt] - top_ctxt n (HsPar _ fun) = top_lctxt n fun + + top_ctxt n (HsPar _ fun) = top_lctxt n fun top_ctxt n (HsPragE _ _ fun) = top_lctxt n fun top_ctxt n (HsAppType _ fun _) = top_lctxt (n+1) fun top_ctxt n (HsApp _ fun _) = top_lctxt (n+1) fun - top_ctxt n (XExpr (ExpandedThingRn (OrigExpr fun) _)) - = VACall fun n noSrcSpan top_ctxt n other_fun = VACall other_fun n noSrcSpan + top_lctxt :: Int -> LHsExpr GhcRn -> AppCtxt top_lctxt n (L _ fun) = top_ctxt n fun go :: HsExpr GhcRn -> AppCtxt -> [HsExprArg 'TcpRn] @@ -325,11 +323,6 @@ splitHsApps e = go e (top_ctxt 0 e) [] HsUntypedSpliceExpr _ (L l _) -> set l ctxt -- l :: SrcAnn AnnListItem HsQuasiQuote _ _ (L l _) -> set l ctxt -- l :: SrcAnn NoEpAnns - -- See Note [Looking through ExpandedThingRn] - go (XExpr (ExpandedThingRn o e)) ctxt args - = go e (VAExpansion o (appCtxtLoc ctxt) (appCtxtLoc ctxt)) - (EWrap (EExpand o) : args) - -- See Note [Desugar OpApp in the typechecker] go e@(OpApp _ arg1 (L l op) arg2) _ args = pure ( (op, VACall op 0 (locA l)) @@ -344,11 +337,11 @@ splitHsApps e = go e (top_ctxt 0 e) [] set :: EpAnn ann -> AppCtxt -> AppCtxt set l (VACall f n _) = VACall f n (locA l) - set l (VAExpansion orig ol _) = VAExpansion orig ol (locA l) + set _ ctx = ctx dec :: EpAnn ann -> AppCtxt -> AppCtxt dec l (VACall f n _) = VACall f (n-1) (locA l) - dec l (VAExpansion orig ol _) = VAExpansion orig ol (locA l) + dec _ ctx = ctx -- | Rebuild an application: takes a type-checked application head -- expression together with arguments in the form of typechecked 'HsExprArg's @@ -377,15 +370,12 @@ rebuildHsApps (fun, ctxt) (arg : args) EWrap (EExpand orig) | OrigExpr oe <- orig -> rebuildHsApps (mkExpandedExprTc oe fun, ctxt) args - | otherwise - -> rebuildHsApps (fun, ctxt) args + | OrigStmt stmt flav <- orig + -> rebuildHsApps (mkExpandedStmtTc stmt flav fun, ctxt) args EWrap (EHsWrap wrap) -> rebuildHsApps (mkHsWrap wrap fun, ctxt) args where - lfun = L (noAnnSrcSpan $ appCtxtLoc' ctxt) fun - appCtxtLoc' (VAExpansion _ _ l) = l - appCtxtLoc' v = appCtxtLoc v - + lfun = L (noAnnSrcSpan $ appCtxtLoc ctxt) fun isHsValArg :: HsExprArg id -> Bool isHsValArg (EValArg {}) = True @@ -556,19 +546,7 @@ tcInferAppHead_maybe fun _ -> return Nothing addHeadCtxt :: AppCtxt -> TcM a -> TcM a -addHeadCtxt (VAExpansion (OrigStmt (L loc stmt) flav) _ _) thing_inside = - do setSrcSpanA loc $ - addStmtCtxt stmt flav - thing_inside -addHeadCtxt fun_ctxt thing_inside - | not (isGoodSrcSpan fun_loc) -- noSrcSpan => no arguments - = thing_inside -- => context is already set - | otherwise - = setSrcSpan fun_loc $ - do case fun_ctxt of - VAExpansion (OrigExpr orig) _ _ - -> addExprCtxt orig thing_inside - _ -> thing_inside +addHeadCtxt fun_ctxt thing_inside = setSrcSpan fun_loc thing_inside where fun_loc = appCtxtLoc fun_ctxt @@ -1247,16 +1225,25 @@ mis-match in the number of value arguments. * * ********************************************************************* -} -addStmtCtxt :: ExprStmt GhcRn -> TcRn a -> TcRn a -addStmtCtxt stmt = - addErrCtxt (StmtErrCtxt (HsDoStmt (DoExpr Nothing)) stmt) + +addStmtCtxt :: ExprStmt GhcRn -> HsDoFlavour -> TcRn a -> TcRn a +addStmtCtxt stmt flav = + addErrCtxt (StmtErrCtxt (HsDoStmt flav) stmt) + +addThingCtxt :: HsThingRn -> TcRn a -> TcRn a +addThingCtxt (OrigStmt (L loc stmt) flav) thing_inside = do + setSrcSpanA loc $ + addStmtCtxt stmt flav $ + setInGeneratedCode + thing_inside +addThingCtxt (OrigExpr e) thing_inside = addExprCtxt e thing_inside addExprCtxt :: HsExpr GhcRn -> TcRn a -> TcRn a addExprCtxt e thing_inside = case e of - HsUnboundVar {} -> thing_inside - _ -> addErrCtxt (ExprCtxt e) thing_inside - -- The HsUnboundVar special case addresses situations like + -- The HsUnboundVar special case addresses situations like -- f x = _ -- when we don't want to say "In the expression: _", -- because it is mentioned in the error message itself + HsUnboundVar {} -> thing_inside + _ -> addErrCtxt (ExprCtxt e) thing_inside ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -84,7 +84,7 @@ import GHC.Types.Basic( VisArity, isDoExpansionGenerated ) import qualified GHC.Data.List.NonEmpty as NE import Control.Monad -import qualified Data.List.NonEmpty as NE +import Data.List.NonEmpty (NonEmpty(..), toList) import Data.Maybe (mapMaybe) import qualified GHC.LanguageExtensions as LangExt @@ -350,12 +350,14 @@ tcDoStmts ListComp (L l stmts) res_ty tcDoStmts doExpr@(DoExpr _) ss@(L _ stmts) res_ty = do { expanded_expr <- expandDoStmts doExpr stmts -- Do expansion on the fly - ; mkExpandedExprTc (HsDo noExtField doExpr ss) <$> tcExpr expanded_expr res_ty + ; let orig = HsDo noExtField doExpr ss + ; mkExpandedExprTc orig <$> tcExpr expanded_expr res_ty } tcDoStmts mDoExpr@(MDoExpr _) ss@(L _ stmts) res_ty = do { expanded_expr <- expandDoStmts mDoExpr stmts -- Do expansion on the fly - ; mkExpandedExprTc (HsDo noExtField mDoExpr ss) <$> tcExpr expanded_expr res_ty } + ; let orig = HsDo noExtField mDoExpr ss + ; mkExpandedExprTc orig <$> tcExpr expanded_expr res_ty } tcDoStmts MonadComp (L l stmts) res_ty = do { stmts' <- tcStmts (HsDoStmt MonadComp) tcMcStmt stmts res_ty ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -757,7 +757,6 @@ exprCtOrigin (HsQual {}) = Shouldn'tHappenOrigin "constraint context" - exprCtOrigin (HsFunArr {}) = Shouldn'tHappenOrigin "function arrow" -- See Note [Types in terms] exprCtOrigin (XExpr (ExpandedThingRn thing _)) | OrigExpr a <- thing = exprCtOrigin a | OrigStmt _ _ <- thing = DoOrigin - | OrigPat p _ <- thing = DoPatOrigin p exprCtOrigin (XExpr (PopErrCtxt {})) = Shouldn'tHappenOrigin "PopErrCtxt" exprCtOrigin (XExpr (HsRecSelRn f)) = OccurrenceOfRecSel (foExt f) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0dbe4b10a497adf3592f4be034bf7cb52bcf2110...1229a9f18eb0805ca16fcf72cc75666d845e6805 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0dbe4b10a497adf3592f4be034bf7cb52bcf2110...1229a9f18eb0805ca16fcf72cc75666d845e6805 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/ac85c067/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 17:26:14 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Mon, 03 Mar 2025 12:26:14 -0500 Subject: [Git][ghc/ghc][wip/andreask/interpreter_primops] Flatten and expand subword instructions. Message-ID: <67c5e6368619d_277dc556c3e0512b2@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/interpreter_primops at Glasgow Haskell Compiler / GHC Commits: 6ed53c04 by Andreas Klebinger at 2025-03-03T18:03:08+01:00 Flatten and expand subword instructions. - - - - - 6 changed files: - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/StgToByteCode.hs - rts/Disassembler.c - rts/Interpreter.c - rts/include/rts/Bytecodes.h Changes: ===================================== compiler/GHC/ByteCode/Asm.hs ===================================== @@ -540,30 +540,113 @@ assembleI platform i = case i of emit bci_CCALL [wOp off, Op np, SmallOp i] PRIMCALL -> emit bci_PRIMCALL [] - OP_ADD -> emit bci_OP_ADD [] - OP_SUB -> emit bci_OP_SUB [] - OP_AND -> emit bci_OP_AND [] - OP_XOR -> emit bci_OP_XOR [] - OP_NOT -> emit bci_OP_NOT [] - OP_NEG -> emit bci_OP_NEG [] - OP_MUL -> emit bci_OP_MUL [] - OP_SHL -> emit bci_OP_SHL [] - OP_ASR -> emit bci_OP_ASR [] - OP_LSR -> emit bci_OP_LSR [] - - OP_NEQ -> emit bci_OP_NEQ [] - OP_EQ -> emit bci_OP_EQ [] - - OP_U_LT -> emit bci_OP_U_LT [] - OP_S_LT -> emit bci_OP_S_LT [] - OP_U_GE -> emit bci_OP_U_GE [] - OP_S_GE -> emit bci_OP_S_GE [] - OP_U_GT -> emit bci_OP_U_GT [] - OP_S_GT -> emit bci_OP_S_GT [] - OP_U_LE -> emit bci_OP_U_LE [] - OP_S_LE -> emit bci_OP_S_LE [] - - OP_SIZED_SUB rep -> emit (sizedInstr platform bci_OP_SIZED_SUB rep) [] + OP_ADD w -> case w of + W64 -> emit bci_OP_ADD_64 [] + W32 -> emit bci_OP_ADD_32 [] + W16 -> emit bci_OP_ADD_16 [] + W8 -> emit bci_OP_ADD_08 [] + OP_SUB w -> case w of + W64 -> emit bci_OP_SUB_64 [] + W32 -> emit bci_OP_SUB_32 [] + W16 -> emit bci_OP_SUB_16 [] + W8 -> emit bci_OP_SUB_08 [] + OP_AND w -> case w of + W64 -> emit bci_OP_AND_64 [] + W32 -> emit bci_OP_AND_32 [] + W16 -> emit bci_OP_AND_16 [] + W8 -> emit bci_OP_AND_08 [] + OP_XOR w -> case w of + W64 -> emit bci_OP_XOR_64 [] + W32 -> emit bci_OP_XOR_32 [] + W16 -> emit bci_OP_XOR_16 [] + W8 -> emit bci_OP_XOR_08 [] + OP_OR w -> case w of + W64 -> emit bci_OP_OR_64 [] + W32 -> emit bci_OP_OR_32 [] + W16 -> emit bci_OP_OR_16 [] + W8 -> emit bci_OP_OR_08 [] + OP_NOT w -> case w of + W64 -> emit bci_OP_NOT_64 [] + W32 -> emit bci_OP_NOT_32 [] + W16 -> emit bci_OP_NOT_16 [] + W8 -> emit bci_OP_NOT_08 [] + OP_NEG w -> case w of + W64 -> emit bci_OP_NEG_64 [] + W32 -> emit bci_OP_NEG_32 [] + W16 -> emit bci_OP_NEG_16 [] + W8 -> emit bci_OP_NEG_08 [] + OP_MUL w -> case w of + W64 -> emit bci_OP_MUL_64 [] + W32 -> emit bci_OP_MUL_32 [] + W16 -> emit bci_OP_MUL_16 [] + W8 -> emit bci_OP_MUL_08 [] + OP_SHL w -> case w of + W64 -> emit bci_OP_SHL_64 [] + W32 -> emit bci_OP_SHL_32 [] + W16 -> emit bci_OP_SHL_16 [] + W8 -> emit bci_OP_SHL_08 [] + OP_ASR w -> case w of + W64 -> emit bci_OP_ASR_64 [] + W32 -> emit bci_OP_ASR_32 [] + W16 -> emit bci_OP_ASR_16 [] + W8 -> emit bci_OP_ASR_08 [] + OP_LSR w -> case w of + W64 -> emit bci_OP_LSR_64 [] + W32 -> emit bci_OP_LSR_32 [] + W16 -> emit bci_OP_LSR_16 [] + W8 -> emit bci_OP_LSR_08 [] + + OP_NEQ w -> case w of + W64 -> emit bci_OP_NEQ_64 [] + W32 -> emit bci_OP_NEQ_32 [] + W16 -> emit bci_OP_NEQ_16 [] + W8 -> emit bci_OP_NEQ_08 [] + OP_EQ w -> case w of + W64 -> emit bci_OP_EQ_64 [] + W32 -> emit bci_OP_EQ_32 [] + W16 -> emit bci_OP_EQ_16 [] + W8 -> emit bci_OP_EQ_08 [] + + OP_U_LT w -> case w of + W64 -> emit bci_OP_U_LT_64 [] + W32 -> emit bci_OP_U_LT_32 [] + W16 -> emit bci_OP_U_LT_16 [] + W8 -> emit bci_OP_U_LT_08 [] + OP_S_LT w -> case w of + W64 -> emit bci_OP_S_LT_64 [] + W32 -> emit bci_OP_S_LT_32 [] + W16 -> emit bci_OP_S_LT_16 [] + W8 -> emit bci_OP_S_LT_08 [] + OP_U_GE w -> case w of + W64 -> emit bci_OP_U_GE_64 [] + W32 -> emit bci_OP_U_GE_32 [] + W16 -> emit bci_OP_U_GE_16 [] + W8 -> emit bci_OP_U_GE_08 [] + OP_S_GE w -> case w of + W64 -> emit bci_OP_S_GE_64 [] + W32 -> emit bci_OP_S_GE_32 [] + W16 -> emit bci_OP_S_GE_16 [] + W8 -> emit bci_OP_S_GE_08 [] + OP_U_GT w -> case w of + W64 -> emit bci_OP_U_GT_64 [] + W32 -> emit bci_OP_U_GT_32 [] + W16 -> emit bci_OP_U_GT_16 [] + W8 -> emit bci_OP_U_GT_08 [] + OP_S_GT w -> case w of + W64 -> emit bci_OP_S_GT_64 [] + W32 -> emit bci_OP_S_GT_32 [] + W16 -> emit bci_OP_S_GT_16 [] + W8 -> emit bci_OP_S_GT_08 [] + OP_U_LE w -> case w of + W64 -> emit bci_OP_U_LE_64 [] + W32 -> emit bci_OP_U_LE_32 [] + W16 -> emit bci_OP_U_LE_16 [] + W8 -> emit bci_OP_U_LE_08 [] + OP_S_LE w -> case w of + W64 -> emit bci_OP_S_LE_64 [] + W32 -> emit bci_OP_S_LE_32 [] + W16 -> emit bci_OP_S_LE_16 [] + W8 -> emit bci_OP_S_LE_08 [] BRK_FUN arr tick_mod tickx info_mod infox cc -> do p1 <- ptr (BCOPtrBreakArray arr) ===================================== compiler/GHC/ByteCode/Instr.hs ===================================== @@ -37,6 +37,7 @@ import GHC.Stg.Syntax import GHCi.BreakArray (BreakArray) import Language.Haskell.Syntax.Module.Name (ModuleName) import GHC.Types.RepType (PrimRep) +import GHC.Cmm.Type (Width) -- ---------------------------------------------------------------------------- -- Bytecode instructions @@ -215,34 +216,34 @@ data BCInstr | PRIMCALL - -- Primops - | OP_ADD - | OP_SUB - | OP_AND - | OP_XOR - | OP_MUL - | OP_SHL - | OP_ASR - | OP_LSR - - | OP_NOT - | OP_NEG - - | OP_NEQ - | OP_EQ - - | OP_U_LT - | OP_U_GE - | OP_U_GT - | OP_U_LE - - | OP_S_LT - | OP_S_GE - | OP_S_GT - | OP_S_LE - - | OP_SIZED_SUB PrimRep - + -- Primops - The actual interpreter instructions are flattened into 64/32/16/8 wide + -- instructions. But for generating code it's handy to have the width as argument + -- to avoid duplication. + | OP_ADD !Width + | OP_SUB !Width + | OP_AND !Width + | OP_XOR !Width + | OP_MUL !Width + | OP_SHL !Width + | OP_ASR !Width + | OP_LSR !Width + | OP_OR !Width + + | OP_NOT !Width + | OP_NEG !Width + + | OP_NEQ !Width + | OP_EQ !Width + + | OP_U_LT !Width + | OP_U_GE !Width + | OP_U_GT !Width + | OP_U_LE !Width + + | OP_S_LT !Width + | OP_S_GE !Width + | OP_S_GT !Width + | OP_S_LE !Width -- For doing magic ByteArray passing to foreign calls | SWIZZLE !WordOff -- to the ptr N words down the stack, @@ -424,30 +425,28 @@ instance Outputable BCInstr where _ -> empty) ppr PRIMCALL = text "PRIMCALL" - ppr OP_ADD = text "OP_ADD" - ppr OP_SUB = text "OP_SUB" - ppr OP_AND = text "OP_AND" - ppr OP_XOR = text "OP_XOR" - ppr OP_NOT = text "OP_NOT" - ppr OP_NEG = text "OP_NEG" - ppr OP_MUL = text "OP_MUL" - ppr OP_SHL = text "OP_SHL" - ppr OP_ASR = text "OP_ASR" - ppr OP_LSR = text "OP_LSR" - - ppr OP_EQ = text "OP_EQ" - ppr OP_NEQ = text "OP_NEQ" - ppr OP_S_LT = text "OP_S_LT" - ppr OP_S_GE = text "OP_S_GE" - ppr OP_S_GT = text "OP_S_GT" - ppr OP_S_LE = text "OP_S_LE" - ppr OP_U_LT = text "OP_U_LT" - ppr OP_U_GE = text "OP_U_GE" - ppr OP_U_GT = text "OP_U_GT" - ppr OP_U_LE = text "OP_U_LE" - - ppr (OP_SIZED_SUB rep) = text "OP_SIZED_SUB" <+> (ppr rep) - + ppr (OP_ADD w) = text "OP_ADD_" <> ppr w + ppr (OP_SUB w) = text "OP_SUB_" <> ppr w + ppr (OP_AND w) = text "OP_AND_" <> ppr w + ppr (OP_XOR w) = text "OP_XOR_" <> ppr w + ppr (OP_OR w) = text "OP_OR_" <> ppr w + ppr (OP_NOT w) = text "OP_NOT_" <> ppr w + ppr (OP_NEG w) = text "OP_NEG_" <> ppr w + ppr (OP_MUL w) = text "OP_MUL_" <> ppr w + ppr (OP_SHL w) = text "OP_SHL_" <> ppr w + ppr (OP_ASR w) = text "OP_ASR_" <> ppr w + ppr (OP_LSR w) = text "OP_LSR_" <> ppr w + + ppr (OP_EQ w) = text "OP_EQ_" <> ppr w + ppr (OP_NEQ w) = text "OP_NEQ_" <> ppr w + ppr (OP_S_LT w) = text "OP_S_LT_" <> ppr w + ppr (OP_S_GE w) = text "OP_S_GE_" <> ppr w + ppr (OP_S_GT w) = text "OP_S_GT_" <> ppr w + ppr (OP_S_LE w) = text "OP_S_LE_" <> ppr w + ppr (OP_U_LT w) = text "OP_U_LT_" <> ppr w + ppr (OP_U_GE w) = text "OP_U_GE_" <> ppr w + ppr (OP_U_GT w) = text "OP_U_GT_" <> ppr w + ppr (OP_U_LE w) = text "OP_U_LE_" <> ppr w ppr (SWIZZLE stkoff n) = text "SWIZZLE " <+> text "stkoff" <+> ppr stkoff <+> text "by" <+> ppr n @@ -561,6 +560,7 @@ bciStackUse OP_ADD{} = 0 -- We overestimate, it's -1 actually ... bciStackUse OP_SUB{} = 0 bciStackUse OP_AND{} = 0 bciStackUse OP_XOR{} = 0 +bciStackUse OP_OR{} = 0 bciStackUse OP_NOT{} = 0 bciStackUse OP_NEG{} = 0 bciStackUse OP_MUL{} = 0 @@ -579,8 +579,6 @@ bciStackUse OP_U_GT{} = 0 bciStackUse OP_U_LE{} = 0 bciStackUse OP_U_GE{} = 0 -bciStackUse OP_SIZED_SUB{} = 0 - bciStackUse SWIZZLE{} = 0 bciStackUse BRK_FUN{} = 0 ===================================== compiler/GHC/StgToByteCode.hs ===================================== @@ -60,6 +60,7 @@ import GHC.Utils.Exception (evaluate) import GHC.StgToCmm.Closure ( NonVoid(..), fromNonVoid, idPrimRepU, addIdReps, addArgReps, assertNonVoidIds, assertNonVoidStgArgs ) +import GHC.CmmToAsm.Config (platformWordWidth) import GHC.StgToCmm.Layout import GHC.Runtime.Heap.Layout hiding (WordOff, ByteOff, wordsToBytes) import GHC.Data.Bitmap @@ -850,12 +851,12 @@ doPrimOp op init_d s p args = Int64SubOp -> primOp OP_SUB Word64SubOp -> primOp OP_SUB - Int8SubOp -> primOp (OP_SIZED_SUB primArg1Width) - Word8SubOp -> primOp (OP_SIZED_SUB primArg1Width) - Int16SubOp -> primOp (OP_SIZED_SUB primArg1Width) - Word16SubOp -> primOp (OP_SIZED_SUB primArg1Width) - Int32SubOp -> primOp (OP_SIZED_SUB primArg1Width) - Word32SubOp -> primOp (OP_SIZED_SUB primArg1Width) + Int8SubOp -> primOp OP_SUB + Word8SubOp -> primOp OP_SUB + Int16SubOp -> primOp OP_SUB + Word16SubOp -> primOp OP_SUB + Int32SubOp -> primOp OP_SUB + Word32SubOp -> primOp OP_SUB IntAndOp -> primOp OP_AND WordAndOp -> primOp OP_AND @@ -869,6 +870,19 @@ doPrimOp op init_d s p args = WordXorOp -> primOp OP_XOR Word64XorOp -> primOp OP_XOR + IntOrOp -> primOp OP_OR + WordOrOp -> primOp OP_OR + Word64OrOp -> primOp OP_OR + + WordSllOp -> primOp OP_SHL + Word64SllOp -> primOp OP_SHL + IntSllOp -> primOp OP_SHL + Int64SllOp -> primOp OP_SHL + Word64SrlOp -> primOp OP_LSR + WordSrlOp -> primOp OP_LSR + IntSrlOp -> primOp OP_ASR + Int64SrlOp -> primOp OP_ASR + IntNeOp -> primOp OP_NEQ WordNeOp -> primOp OP_NEQ Word64NeOp -> primOp OP_NEQ @@ -912,20 +926,47 @@ doPrimOp op init_d s p args = OrdOp -> no_op _ -> Nothing - where - primArg1Width = (stgArgRepU $ head args) :: PrimRep - -- Push args, execute primop, slide, return_N - primOp op_inst = Just $ do - platform <- profilePlatform <$> getProfile - prim_code <- mkPrimOpCode init_d s p op_inst args - let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N - return $ prim_code `appOL` slide + where + primArg1Width platform (arg:_) + | rep <- (stgArgRepU arg) + = case rep of + AddrRep -> platformWordWidth platform + IntRep -> platformWordWidth platform + WordRep -> platformWordWidth platform - no_op = Just $ do - platform <- profilePlatform <$> getProfile - prim_code <- terribleNoOp init_d s p undefined args - let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N - return $ prim_code `appOL` slide + Int64Rep -> W64 + Word64Rep -> W64 + + Int32Rep -> W32 + Word32Rep -> W32 + + Int16Rep -> W16 + Word16Rep -> W16 + + Int8Rep -> W8 + Word8Rep -> W8 + + FloatRep -> unexpectedRep + DoubleRep -> unexpectedRep + + BoxedRep{} -> unexpectedRep + VecRep{} -> unexpectedRep + where + unexpectedRep = panic "doPrimOp: Unexpected argument rep" + primArg1Width _ _ = panic "doPrimOp: Unexpected argument count" + + -- Push args, execute primop, slide, return_N + primOp op_inst = Just $ do + platform <- profilePlatform <$> getProfile + prim_code <- mkPrimOpCode init_d s p (op_inst $ primArg1Width platform args) $ args + let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N + return $ prim_code `appOL` slide + + no_op = Just $ do + platform <- profilePlatform <$> getProfile + prim_code <- terribleNoOp init_d s p undefined args + let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N + return $ prim_code `appOL` slide -- It's horrible, but still better than calling intToWord ... terribleNoOp ===================================== rts/Disassembler.c ===================================== @@ -63,6 +63,26 @@ disInstr ( StgBCO *bco, int pc ) #endif #define BCO_GET_LARGE_ARG ((instr & bci_FLAG_LARGE_ARGS) ? BCO_READ_NEXT_WORD : BCO_NEXT) #define BCO_GET_BCI_WIDTH(bci) ((bci & bci_FLAG_WIDTH) >> 13) +// For brevity +#define BELCH_INSTR_NAME(OP_NAME) \ + case bci_ ## OP_NAME: \ + debugBelch("OP_NAME\n"); \ + break + +#define BELCH_INSTR_NAME_ALL_SIZES(OP_NAME) \ + case bci_ ## OP_NAME ## _64: \ + debugBelch("#OP_NAME" "_64\n"); \ + break; \ + case bci_ ## OP_NAME ## _32: \ + debugBelch("#OP_NAME" "_32\n"); \ + break; \ + case bci_ ## OP_NAME ## _16: \ + debugBelch("#OP_NAME" "_16\n"); \ + break; \ + case bci_ ## OP_NAME ## _08: \ + debugBelch("#OP_NAME" "_08\n"); \ + break; + switch (instr & 0xff) { case bci_BRK_FUN: @@ -420,38 +440,20 @@ disInstr ( StgBCO *bco, int pc ) debugBelch("TESTEQ_P %d, fail to %d\n", instrs[pc], instrs[pc+1]); pc += 2; break; - case bci_CASEFAIL: - debugBelch("CASEFAIL\n" ); - break; + BELCH_INSTR_NAME(CASEFAIL); case bci_JMP: debugBelch("JMP to %d\n", instrs[pc]); pc += 1; break; - case bci_ENTER: - debugBelch("ENTER\n"); - break; + BELCH_INSTR_NAME(ENTER); + BELCH_INSTR_NAME(RETURN_P); + BELCH_INSTR_NAME(RETURN_N); + BELCH_INSTR_NAME(RETURN_F); + BELCH_INSTR_NAME(RETURN_D); + BELCH_INSTR_NAME(RETURN_L); + BELCH_INSTR_NAME(RETURN_V); + BELCH_INSTR_NAME(RETURN_T); - case bci_RETURN_P: - debugBelch("RETURN_P\n" ); - break; - case bci_RETURN_N: - debugBelch("RETURN_N\n" ); - break; - case bci_RETURN_F: - debugBelch("RETURN_F\n" ); - break; - case bci_RETURN_D: - debugBelch("RETURN_D\n" ); - break; - case bci_RETURN_L: - debugBelch("RETURN_L\n" ); - break; - case bci_RETURN_V: - debugBelch("RETURN_V\n" ); - break; - case bci_RETURN_T: - debugBelch("RETURN_T\n "); - break; case bci_BCO_NAME: { const char *name = (const char*) literals[instrs[pc]]; @@ -460,74 +462,30 @@ disInstr ( StgBCO *bco, int pc ) break; } - case bci_OP_ADD: - debugBelch("OP_ADD\n"); - break; - case bci_OP_SUB: - debugBelch("OP_SUB\n"); - break; - case bci_OP_AND: - debugBelch("OP_AND\n"); - break; - case bci_OP_XOR: - debugBelch("OP_XOR\n"); - break; - case bci_OP_NOT: - debugBelch("OP_NOT\n"); - break; - case bci_OP_NEG: - debugBelch("OP_NEG\n"); - break; - case bci_OP_MUL: - debugBelch("OP_MUL\n"); - break; - case bci_OP_SHL: - debugBelch("OP_SHL\n"); - break; - case bci_OP_ASR: - debugBelch("OP_ASR\n"); - break; - case bci_OP_LSR: - debugBelch("OP_LSR\n"); - break; - - case bci_OP_NEQ: - debugBelch("OP_NEQ\n"); - break; - case bci_OP_EQ: - debugBelch("OP_EQ\n"); - break; - - case bci_OP_U_GT: - debugBelch("OP_U_GT\n"); - break; - case bci_OP_U_LE: - debugBelch("OP_U_LE\n"); - break; - case bci_OP_U_GE: - debugBelch("OP_U_GE\n"); - break; - case bci_OP_U_LT: - debugBelch("OP_U_LT\n"); - break; - - case bci_OP_S_GT: - debugBelch("OP_S_GT\n"); - break; - case bci_OP_S_LE: - debugBelch("OP_S_LE\n"); - break; - case bci_OP_S_GE: - debugBelch("OP_S_GE\n"); - break; - case bci_OP_S_LT: - debugBelch("OP_S_LT\n"); - break; - - case bci_OP_SIZED_SUB: - debugBelch("OP_SIZED_SUB_%d\n",BCO_GET_BCI_WIDTH(instr)); - break; - + BELCH_INSTR_NAME_ALL_SIZES(OP_ADD); + BELCH_INSTR_NAME_ALL_SIZES(OP_SUB); + BELCH_INSTR_NAME_ALL_SIZES(OP_AND); + BELCH_INSTR_NAME_ALL_SIZES(OP_XOR); + BELCH_INSTR_NAME_ALL_SIZES(OP_OR); + BELCH_INSTR_NAME_ALL_SIZES(OP_NOT); + BELCH_INSTR_NAME_ALL_SIZES(OP_NEG); + BELCH_INSTR_NAME_ALL_SIZES(OP_MUL); + BELCH_INSTR_NAME_ALL_SIZES(OP_SHL); + BELCH_INSTR_NAME_ALL_SIZES(OP_ASR); + BELCH_INSTR_NAME_ALL_SIZES(OP_LSR); + + BELCH_INSTR_NAME_ALL_SIZES(OP_NEQ); + BELCH_INSTR_NAME_ALL_SIZES(OP_EQ); + + BELCH_INSTR_NAME_ALL_SIZES(OP_U_GT); + BELCH_INSTR_NAME_ALL_SIZES(OP_U_LE); + BELCH_INSTR_NAME_ALL_SIZES(OP_U_GE); + BELCH_INSTR_NAME_ALL_SIZES(OP_U_LT); + + BELCH_INSTR_NAME_ALL_SIZES(OP_S_GT); + BELCH_INSTR_NAME_ALL_SIZES(OP_S_LE); + BELCH_INSTR_NAME_ALL_SIZES(OP_S_GE); + BELCH_INSTR_NAME_ALL_SIZES(OP_S_LT); default: barf("disInstr: unknown opcode %u", (unsigned int) instr); ===================================== rts/Interpreter.c ===================================== @@ -1144,9 +1144,9 @@ run_BCO: #endif bci = BCO_NEXT; - /* We use the high 8 bits for flags. The highest three of which are - * currently allocated to LARGE_ARGS and WIDTH */ - ASSERT((bci & 0xFF00) == (bci & ( bci_FLAG_LARGE_ARGS | bci_FLAG_WIDTH ))); + /* We use the high 8 bits for flags. The highest of which is + * currently allocated to LARGE_ARGS */ + ASSERT((bci & 0xFF00) == (bci & ( bci_FLAG_LARGE_ARGS ))); switch (bci & 0xFF) { @@ -2171,45 +2171,108 @@ run_BCO: goto nextInsn; \ } -#define UN_INT64_OP(op) UN_SIZED_OP(op,StgInt64) -#define BIN_INT64_OP(op) SIZED_BIN_OP(op,StgInt64) -#define BIN_WORD64_OP(op) SIZED_BIN_OP(op,StgWord64) - - case bci_OP_ADD: BIN_INT64_OP(+) - case bci_OP_SUB: BIN_INT64_OP(-) - case bci_OP_AND: BIN_INT64_OP(&) - case bci_OP_XOR: BIN_INT64_OP(^) - case bci_OP_MUL: BIN_INT64_OP(*) - case bci_OP_SHL: BIN_WORD64_OP(<<) - case bci_OP_LSR: BIN_WORD64_OP(>>) - case bci_OP_ASR: BIN_INT64_OP(>>) - - case bci_OP_NEQ: BIN_INT64_OP(!=) - case bci_OP_EQ: BIN_INT64_OP(==) - case bci_OP_U_GT: BIN_WORD64_OP(>) - case bci_OP_U_GE: BIN_WORD64_OP(>=) - case bci_OP_U_LT: BIN_WORD64_OP(<) - case bci_OP_U_LE: BIN_WORD64_OP(<=) - - case bci_OP_S_GT: BIN_INT64_OP(>) - case bci_OP_S_GE: BIN_INT64_OP(>=) - case bci_OP_S_LT: BIN_INT64_OP(<) - case bci_OP_S_LE: BIN_INT64_OP(<=) - - - case bci_OP_NOT: UN_INT64_OP(~) - case bci_OP_NEG: UN_INT64_OP(-) - - case bci_OP_SIZED_SUB: - { - StgWord width = BCO_GET_BCI_WIDTH(bci); - switch (width) { - case 0: SIZED_BIN_OP(-,StgInt8 ) - case 1: SIZED_BIN_OP(-,StgInt16) - case 2: SIZED_BIN_OP(-,StgInt32) - default: barf("Unexpected bci width."); - }; - } + case bci_OP_ADD_64: SIZED_BIN_OP(+, StgInt64) + case bci_OP_SUB_64: SIZED_BIN_OP(-, StgInt64) + case bci_OP_AND_64: SIZED_BIN_OP(&, StgInt64) + case bci_OP_XOR_64: SIZED_BIN_OP(^, StgInt64) + case bci_OP_OR_64: SIZED_BIN_OP(|, StgInt64) + case bci_OP_MUL_64: SIZED_BIN_OP(*, StgInt64) + case bci_OP_SHL_64: SIZED_BIN_OP(<<, StgWord64) + case bci_OP_LSR_64: SIZED_BIN_OP(>>, StgWord64) + case bci_OP_ASR_64: SIZED_BIN_OP(>>, StgInt64) + + case bci_OP_NEQ_64: SIZED_BIN_OP(!=, StgWord64) + case bci_OP_EQ_64: SIZED_BIN_OP(==, StgWord64) + case bci_OP_U_GT_64: SIZED_BIN_OP(>, StgWord64) + case bci_OP_U_GE_64: SIZED_BIN_OP(>=, StgWord64) + case bci_OP_U_LT_64: SIZED_BIN_OP(<, StgWord64) + case bci_OP_U_LE_64: SIZED_BIN_OP(<=, StgWord64) + + case bci_OP_S_GT_64: SIZED_BIN_OP(>, StgInt64) + case bci_OP_S_GE_64: SIZED_BIN_OP(>=, StgInt64) + case bci_OP_S_LT_64: SIZED_BIN_OP(<, StgInt64) + case bci_OP_S_LE_64: SIZED_BIN_OP(<=, StgInt64) + + case bci_OP_NOT_64: UN_SIZED_OP(~, StgWord64) + case bci_OP_NEG_64: UN_SIZED_OP(-, StgInt64) + + + case bci_OP_ADD_32: SIZED_BIN_OP(+, StgInt32) + case bci_OP_SUB_32: SIZED_BIN_OP(-, StgInt32) + case bci_OP_AND_32: SIZED_BIN_OP(&, StgInt32) + case bci_OP_XOR_32: SIZED_BIN_OP(^, StgInt32) + case bci_OP_OR_32: SIZED_BIN_OP(|, StgInt32) + case bci_OP_MUL_32: SIZED_BIN_OP(*, StgInt32) + case bci_OP_SHL_32: SIZED_BIN_OP(<<, StgWord32) + case bci_OP_LSR_32: SIZED_BIN_OP(>>, StgWord32) + case bci_OP_ASR_32: SIZED_BIN_OP(>>, StgInt32) + + case bci_OP_NEQ_32: SIZED_BIN_OP(!=, StgWord32) + case bci_OP_EQ_32: SIZED_BIN_OP(==, StgWord32) + case bci_OP_U_GT_32: SIZED_BIN_OP(>, StgWord32) + case bci_OP_U_GE_32: SIZED_BIN_OP(>=, StgWord32) + case bci_OP_U_LT_32: SIZED_BIN_OP(<, StgWord32) + case bci_OP_U_LE_32: SIZED_BIN_OP(<=, StgWord32) + + case bci_OP_S_GT_32: SIZED_BIN_OP(>, StgInt32) + case bci_OP_S_GE_32: SIZED_BIN_OP(>=, StgInt32) + case bci_OP_S_LT_32: SIZED_BIN_OP(<, StgInt32) + case bci_OP_S_LE_32: SIZED_BIN_OP(<=, StgInt32) + + case bci_OP_NOT_32: UN_SIZED_OP(~, StgWord32) + case bci_OP_NEG_32: UN_SIZED_OP(-, StgInt32) + + + case bci_OP_ADD_16: SIZED_BIN_OP(+, StgInt16) + case bci_OP_SUB_16: SIZED_BIN_OP(-, StgInt16) + case bci_OP_AND_16: SIZED_BIN_OP(&, StgInt16) + case bci_OP_XOR_16: SIZED_BIN_OP(^, StgInt16) + case bci_OP_OR_16: SIZED_BIN_OP(|, StgInt16) + case bci_OP_MUL_16: SIZED_BIN_OP(*, StgInt16) + case bci_OP_SHL_16: SIZED_BIN_OP(<<, StgWord16) + case bci_OP_LSR_16: SIZED_BIN_OP(>>, StgWord16) + case bci_OP_ASR_16: SIZED_BIN_OP(>>, StgInt16) + + case bci_OP_NEQ_16: SIZED_BIN_OP(!=, StgWord16) + case bci_OP_EQ_16: SIZED_BIN_OP(==, StgWord16) + case bci_OP_U_GT_16: SIZED_BIN_OP(>, StgWord16) + case bci_OP_U_GE_16: SIZED_BIN_OP(>=, StgWord16) + case bci_OP_U_LT_16: SIZED_BIN_OP(<, StgWord16) + case bci_OP_U_LE_16: SIZED_BIN_OP(<=, StgWord16) + + case bci_OP_S_GT_16: SIZED_BIN_OP(>, StgInt16) + case bci_OP_S_GE_16: SIZED_BIN_OP(>=, StgInt16) + case bci_OP_S_LT_16: SIZED_BIN_OP(<, StgInt16) + case bci_OP_S_LE_16: SIZED_BIN_OP(<=, StgInt16) + + case bci_OP_NOT_16: UN_SIZED_OP(~, StgWord16) + case bci_OP_NEG_16: UN_SIZED_OP(-, StgInt16) + + + case bci_OP_ADD_08: SIZED_BIN_OP(+, StgInt8) + case bci_OP_SUB_08: SIZED_BIN_OP(-, StgInt8) + case bci_OP_AND_08: SIZED_BIN_OP(&, StgInt8) + case bci_OP_XOR_08: SIZED_BIN_OP(^, StgInt8) + case bci_OP_OR_08: SIZED_BIN_OP(|, StgInt8) + case bci_OP_MUL_08: SIZED_BIN_OP(*, StgInt8) + case bci_OP_SHL_08: SIZED_BIN_OP(<<, StgWord8) + case bci_OP_LSR_08: SIZED_BIN_OP(>>, StgWord8) + case bci_OP_ASR_08: SIZED_BIN_OP(>>, StgInt8) + + case bci_OP_NEQ_08: SIZED_BIN_OP(!=, StgWord8) + case bci_OP_EQ_08: SIZED_BIN_OP(==, StgWord8) + case bci_OP_U_GT_08: SIZED_BIN_OP(>, StgWord8) + case bci_OP_U_GE_08: SIZED_BIN_OP(>=, StgWord8) + case bci_OP_U_LT_08: SIZED_BIN_OP(<, StgWord8) + case bci_OP_U_LE_08: SIZED_BIN_OP(<=, StgWord8) + + case bci_OP_S_GT_08: SIZED_BIN_OP(>, StgInt8) + case bci_OP_S_GE_08: SIZED_BIN_OP(>=, StgInt8) + case bci_OP_S_LT_08: SIZED_BIN_OP(<, StgInt8) + case bci_OP_S_LE_08: SIZED_BIN_OP(<=, StgInt8) + + case bci_OP_NOT_08: UN_SIZED_OP(~, StgWord8) + case bci_OP_NEG_08: UN_SIZED_OP(-, StgInt8) case bci_CCALL: { void *tok; ===================================== rts/include/rts/Bytecodes.h ===================================== @@ -114,29 +114,100 @@ #define bci_BCO_NAME 88 -#define bci_OP_ADD 89 -#define bci_OP_SUB 90 -#define bci_OP_AND 91 -#define bci_OP_XOR 92 -#define bci_OP_NOT 93 -#define bci_OP_NEG 94 -#define bci_OP_MUL 95 -#define bci_OP_SHL 96 -#define bci_OP_ASR 97 -#define bci_OP_LSR 98 - -#define bci_OP_NEQ 110 -#define bci_OP_EQ 111 -#define bci_OP_U_GE 112 -#define bci_OP_U_GT 113 -#define bci_OP_U_LT 114 -#define bci_OP_U_LE 115 -#define bci_OP_S_GE 116 -#define bci_OP_S_GT 117 -#define bci_OP_S_LT 118 -#define bci_OP_S_LE 119 - -#define bci_OP_SIZED_SUB 130 +#define bci_OP_ADD_64 90 +#define bci_OP_SUB_64 91 +#define bci_OP_AND_64 92 +#define bci_OP_XOR_64 93 +#define bci_OP_NOT_64 94 +#define bci_OP_NEG_64 95 +#define bci_OP_MUL_64 96 +#define bci_OP_SHL_64 97 +#define bci_OP_ASR_64 98 +#define bci_OP_LSR_64 99 +#define bci_OP_OR_64 100 + +#define bci_OP_NEQ_64 110 +#define bci_OP_EQ_64 111 +#define bci_OP_U_GE_64 112 +#define bci_OP_U_GT_64 113 +#define bci_OP_U_LT_64 114 +#define bci_OP_U_LE_64 115 +#define bci_OP_S_GE_64 116 +#define bci_OP_S_GT_64 117 +#define bci_OP_S_LT_64 118 +#define bci_OP_S_LE_64 119 + + +#define bci_OP_ADD_32 130 +#define bci_OP_SUB_32 131 +#define bci_OP_AND_32 132 +#define bci_OP_XOR_32 133 +#define bci_OP_NOT_32 134 +#define bci_OP_NEG_32 135 +#define bci_OP_MUL_32 136 +#define bci_OP_SHL_32 137 +#define bci_OP_ASR_32 138 +#define bci_OP_LSR_32 139 +#define bci_OP_OR_32 140 + +#define bci_OP_NEQ_32 150 +#define bci_OP_EQ_32 151 +#define bci_OP_U_GE_32 152 +#define bci_OP_U_GT_32 153 +#define bci_OP_U_LT_32 154 +#define bci_OP_U_LE_32 155 +#define bci_OP_S_GE_32 156 +#define bci_OP_S_GT_32 157 +#define bci_OP_S_LT_32 158 +#define bci_OP_S_LE_32 159 + + +#define bci_OP_ADD_16 170 +#define bci_OP_SUB_16 171 +#define bci_OP_AND_16 172 +#define bci_OP_XOR_16 173 +#define bci_OP_NOT_16 174 +#define bci_OP_NEG_16 175 +#define bci_OP_MUL_16 176 +#define bci_OP_SHL_16 177 +#define bci_OP_ASR_16 178 +#define bci_OP_LSR_16 179 +#define bci_OP_OR_16 180 + +#define bci_OP_NEQ_16 190 +#define bci_OP_EQ_16 191 +#define bci_OP_U_GE_16 192 +#define bci_OP_U_GT_16 193 +#define bci_OP_U_LT_16 194 +#define bci_OP_U_LE_16 195 +#define bci_OP_S_GE_16 196 +#define bci_OP_S_GT_16 197 +#define bci_OP_S_LT_16 198 +#define bci_OP_S_LE_16 199 + + +#define bci_OP_ADD_08 200 +#define bci_OP_SUB_08 201 +#define bci_OP_AND_08 202 +#define bci_OP_XOR_08 203 +#define bci_OP_NOT_08 204 +#define bci_OP_NEG_08 205 +#define bci_OP_MUL_08 206 +#define bci_OP_SHL_08 207 +#define bci_OP_ASR_08 208 +#define bci_OP_LSR_08 209 +#define bci_OP_OR_08 210 + +#define bci_OP_NEQ_08 220 +#define bci_OP_EQ_08 221 +#define bci_OP_U_GE_08 222 +#define bci_OP_U_GT_08 223 +#define bci_OP_U_LT_08 224 +#define bci_OP_U_LE_08 225 +#define bci_OP_S_GE_08 226 +#define bci_OP_S_GT_08 227 +#define bci_OP_S_LT_08 228 +#define bci_OP_S_LE_08 229 /* If you need to go past 255 then you will run into the flags */ @@ -144,12 +215,6 @@ /* If you need to go below 0x0100 then you will run into the instructions */ #define bci_FLAG_LARGE_ARGS 0x8000 -/* Width of primitiv operations if width-polymorphic. We use two bits to store - * the width. - * 0->Word8;1->Word16;2->Word32 - * Word64 operations always should take the OP with fixed width instead. */ -#define bci_FLAG_WIDTH 0x6000 - /* If a BCO definitely requires less than this many words of stack, don't include an explicit STKCHECK insn in it. The interpreter will check for this many words of stack before running each BCO, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ed53c04bf881c20645fbd539bc130e3fcd9e6ff -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ed53c04bf881c20645fbd539bc130e3fcd9e6ff You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/afa72219/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 17:32:59 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 03 Mar 2025 12:32:59 -0500 Subject: [Git][ghc/ghc][wip/22188] 12 commits: haddock/doc: Drop version and release Message-ID: <67c5e7cb865b6_277dc59225fc53115@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 1f8dd609 by Matthew Pickering at 2025-03-03T16:44:38+00:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - d9c8ea1a by Matthew Pickering at 2025-03-03T16:44:38+00:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 590ecbd8 by Matthew Pickering at 2025-03-03T17:32:40+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-self-recomp-info which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. In addition to this, the change alerted me to the incorrect implemenation of the reifyModule function. See #8489 for more discussion about how to fix this if anyone was so inclined. For now I just added a warning `-Wreify-module-missing-info` which triggers if the module you are trying to reify doesn't have a suitable interface. Interfaces which are unsuitable include: * The GHC.Prim interface, which is a fake interface * Interfaces compiled with -fno-write-self-recomp-info The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - a97a1e28 by Matthew Pickering at 2025-03-03T17:32:40+00:00 Disable self recomp in release flavour - - - - - 145 changed files: - compiler/GHC.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - distrib/configure.ac.in - docs/users_guide/phases.rst - docs/users_guide/using-warnings.rst - ghc/GHCi/UI.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Flavours/Release.hs - m4/fp_settings.m4 - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - utils/haddock/doc/conf.py The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/44dae5353ed1adff372f4257e537e66de9ee2208...a97a1e28dd5d1f0f28eb359661524aebe610c62e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/44dae5353ed1adff372f4257e537e66de9ee2208...a97a1e28dd5d1f0f28eb359661524aebe610c62e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/ca353a38/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 17:38:56 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Mar 2025 12:38:56 -0500 Subject: [Git][ghc/ghc][wip/T25657] Wibbles Message-ID: <67c5e930b26ee_277dc5ab12105397c@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25657 at Glasgow Haskell Compiler / GHC Commits: 6e0326d8 by Simon Peyton Jones at 2025-03-03T17:38:42+00:00 Wibbles - - - - - 2 changed files: - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Types/Constraint.hs Changes: ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -147,7 +147,7 @@ alwaysBindTv _tv _ty = BindMe alwaysBindFam :: BindFamFun alwaysBindFam _tc _args _rhs = BindMe -dontCareBindFam :: HasDebugCallStack => BindFamFun +dontCareBindFam :: HasCallStack => BindFamFun dontCareBindFam tc args rhs = pprPanic "dontCareBindFam" $ vcat [ ppr tc <+> ppr args, text "rhs" <+> ppr rhs ] @@ -1374,10 +1374,11 @@ unify_ty env ty1 ty2 kco unify_ty env (CastTy ty1 co1) ty2 kco | mentionsForAllBoundTyVarsL env (tyCoVarsOfCo co1) = surelyApart + -- xxx todo ... MaybeApart perhaps? F a b, where b is forall-bound, but a is not + -- and F Int b = Int | um_unif env = unify_ty env ty1 ty2 (co1 `mkTransCo` kco) - -- ToDo: what if co2 mentions forall-bound variables? | otherwise -- We are matching, not unifying = do { subst <- getSubst env @@ -1596,9 +1597,8 @@ isSatFamApp _ = Nothing --------------------------------- uVarOrFam :: UMEnv -> CanEqLHS -> InType -> OutCoercion -> UM () --- Invariants: (a) ty1 is a TyVarTy or a saturated type-family application --- (b) If ty1 is a ty-fam-app, then ty2 is NOT a TyVarTy --- (c) both args have had coreView already applied +-- Invariants: (a) If ty1 is a TyFamLHS, then ty2 is NOT a TyVarTy +-- (b) both args have had coreView already applied -- Why saturated? See (ATF4) in Note [Apartness and type families] uVarOrFam env ty1 ty2 kco = do { substs <- getSubstEnvs @@ -1646,12 +1646,12 @@ uVarOrFam env ty1 ty2 kco , let tv2' = umRnOccR env tv2 , tv1' == tv2' = if | um_unif env -> return () - | tv1_is_bindable -> extendTvEnv tv1 ty2 + | tv1_is_bindable -> extendTvEnv tv1' ty2 | otherwise -> return () | tv1_is_bindable - , not (mentionsForAllBoundTyVarsR env rhs_fvs) - -- kco does not mention forall-bound vars + , not (mentionsForAllBoundTyVarsR env ty2_fvs) + -- ty2_fvs: kco does not mention forall-bound vars , not occurs_check = -- No occurs check, nor skolem-escape; just bind the tv -- We don't need to rename `rhs` because it mentions no forall-bound vars @@ -1671,21 +1671,23 @@ uVarOrFam env ty1 ty2 kco where tv1' = umRnOccL env tv1 - rhs_fvs = tyCoVarsOfType ty2 - all_rhs_fvs = rhs_fvs `unionVarSet` tyCoVarsOfCo kco + ty2_fvs = tyCoVarsOfType ty2 + rhs_fvs = ty2_fvs `unionVarSet` tyCoVarsOfCo kco rhs = ty2 `mkCastTy` mkSymCo kco tv1_is_bindable | not (tv1' `elemVarSet` um_foralls env) - -- tv1' is not forall-bound, so tv1==tv1' - , BindMe <- um_bind_tv_fun env tv1 rhs + -- tv1' is not forall-bound, but tv1 can still differ + -- from tv1; see Note [Cloning the template binders] + -- in GHC.Core.Rules. So give tv1' to um_bind_tv_fun. + , BindMe <- um_bind_tv_fun env tv1' rhs = True | otherwise = False occurs_check = um_unif env && - occursCheck (um_tv_env substs) tv1 all_rhs_fvs + occursCheck (um_tv_env substs) tv1 rhs_fvs -- Occurs check, only when unifying -- see Note [Fine-grained unification] - -- Make sure you include `kco` in all_rhs_tvs #14846 + -- Make sure you include `kco` in rhs_tvs #14846 ----------------------------- -- go_fam: LHS is a saturated type-family application ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -46,7 +46,11 @@ module GHC.Tc.Types.Constraint ( cterHasNoProblem, cterHasProblem, cterHasOnlyProblem, cterHasOnlyProblems, cterRemoveProblem, cterHasOccursCheck, cterFromKind, + -- Equality left-hand sides, re-exported from GHC.Core.Predicate + CanEqLHS(..), canEqLHS_maybe, canTyFamEqLHS_maybe, + canEqLHSKind, canEqLHSType, eqCanEqLHS, + -- Holes Hole(..), HoleSort(..), isOutOfScopeHole, DelayedError(..), NotConcreteError(..), View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6e0326d8af2dbcad227b55db2c234c213f2c70b5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6e0326d8af2dbcad227b55db2c234c213f2c70b5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/11bfc25d/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 17:39:27 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 03 Mar 2025 12:39:27 -0500 Subject: [Git][ghc/ghc][wip/mi_top_env_serialise] 2 commits: ghci: Serialise mi_top_env Message-ID: <67c5e94f16ce6_277dc5ab10bc544d6@gitlab.mail> Matthew Pickering pushed to branch wip/mi_top_env_serialise at Glasgow Haskell Compiler / GHC Commits: cf8ff3d9 by Matthew Pickering at 2025-03-03T17:39:07+00:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 20dc4049 by Matthew Pickering at 2025-03-03T17:39:07+00:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 17 changed files: - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModIface.hs - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T Changes: ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -47,7 +47,6 @@ import GHC.Core.RoughMap ( RoughMatchTc(..) ) import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env -import GHC.Driver.Backend import GHC.Driver.DynFlags import GHC.Driver.Plugins @@ -342,7 +341,7 @@ mkIface_ hsc_env trust_info = setSafeMode safe_mode annotations = map mkIfaceAnnotation anns icomplete_matches = map mkIfaceCompleteMatch complete_matches - !rdrs = maybeGlobalRdrEnv rdr_env + !rdrs = mkIfaceTopEnv rdr_env emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag @@ -395,15 +394,11 @@ mkIface_ hsc_env -- Desugar.addExportFlagsAndRules). The mi_top_env field is used -- by GHCi to decide whether the module has its full top-level -- scope available. (#5534) - maybeGlobalRdrEnv :: GlobalRdrEnv -> Maybe IfaceTopEnv - maybeGlobalRdrEnv rdr_env - | backendWantsGlobalBindings (backend dflags) - = Just $! let !exports = forceGlobalRdrEnv (globalRdrEnvLocal rdr_env) - !imports = mkIfaceImports import_decls - in IfaceTopEnv exports imports - -- See Note [Forcing GREInfo] in GHC.Types.GREInfo. - | otherwise - = Nothing + mkIfaceTopEnv :: GlobalRdrEnv -> IfaceTopEnv + mkIfaceTopEnv rdr_env + = let !exports = sortAvails $ gresToAvailInfo $ globalRdrEnvElts $ globalRdrEnvLocal rdr_env + !imports = mkIfaceImports import_decls + in IfaceTopEnv exports imports ifFamInstTcName = ifFamInstFam @@ -515,8 +510,8 @@ mkIfaceImports :: [ImportUserSpec] -> [IfaceImport] mkIfaceImports = map go where go (ImpUserSpec decl ImpUserAll) = IfaceImport decl ImpIfaceAll - go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env)) - go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns) + go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (sortAvails env)) + go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut (nameSetElemsStable ns)) mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -26,7 +26,8 @@ module GHC.Iface.Syntax ( IfaceCompleteMatch(..), IfaceLFInfo(..), IfaceTopBndrInfo(..), IfaceImport(..), - ImpIfaceList(..), + ifImpModule, + ImpIfaceList(..), IfaceExport, -- * Binding names IfaceTopBndr, @@ -69,6 +70,7 @@ import GHC.Types.Name.Set import GHC.Types.Name.Reader import GHC.Types.CostCentre import GHC.Types.Literal +import GHC.Types.Avail import GHC.Types.ForeignCall import GHC.Types.Annotations( AnnPayload, AnnTarget ) import GHC.Types.Basic @@ -112,12 +114,48 @@ infixl 3 &&& ************************************************************************ -} +type IfaceExport = AvailInfo + data IfaceImport = IfaceImport ImpDeclSpec ImpIfaceList data ImpIfaceList = ImpIfaceAll -- ^ no user import list - | ImpIfaceExplicit !IfGlobalRdrEnv - | ImpIfaceEverythingBut !NameSet + | ImpIfaceExplicit !DetOrdAvails + | ImpIfaceEverythingBut ![Name] + + +-- | Extract the imported module from an IfaceImport +ifImpModule :: IfaceImport -> Module +ifImpModule (IfaceImport declSpec _) = is_mod declSpec + +instance Binary IfaceImport where + put_ bh (IfaceImport declSpec ifaceList) = do + put_ bh declSpec + put_ bh ifaceList + get bh = do + declSpec <- get bh + ifaceList <- get bh + return (IfaceImport declSpec ifaceList) + +instance Binary ImpIfaceList where + put_ bh ImpIfaceAll = putByte bh 0 + put_ bh (ImpIfaceExplicit env) = do + putByte bh 1 + put_ bh env + put_ bh (ImpIfaceEverythingBut ns) = do + putByte bh 2 + put_ @[Name] bh ns + get bh = do + tag <- getByte bh + case tag of + 0 -> return ImpIfaceAll + 1 -> do + env <- get bh + return (ImpIfaceExplicit env) + 2 -> do + ns <- get @[Name] bh + return (ImpIfaceEverythingBut ns) + _ -> fail "instance Binary ImpIfaceList: Invalid tag" -- | A binding top-level 'Name' in an interface file (e.g. the name of an -- 'IfaceDecl'). ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -104,6 +104,7 @@ import GHC.Types.SourceText import GHC.Types.Basic hiding ( SuccessFlag(..) ) import GHC.Types.CompleteMatch import GHC.Types.SrcLoc +import GHC.Types.Avail import GHC.Types.TypeEnv import GHC.Types.Unique.FM import GHC.Types.Unique.DSet ( mkUniqDSet ) @@ -114,7 +115,7 @@ import GHC.Types.Literal import GHC.Types.Var as Var import GHC.Types.Var.Set import GHC.Types.Name -import GHC.Types.Name.Reader +import GHC.Types.Name.Set import GHC.Types.Name.Env import GHC.Types.DefaultEnv ( ClassDefaults(..), defaultEnv ) import GHC.Types.Id @@ -2242,9 +2243,7 @@ hydrateCgBreakInfo CgBreakInfo{..} = do -- | This function is only used to construct the environment for GHCi, -- so we make up fake locations -tcIfaceImport :: HscEnv -> IfaceImport -> ImportUserSpec -tcIfaceImport _ (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll -tcIfaceImport _ (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut ns) -tcIfaceImport hsc_env (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (hydrateGlobalRdrEnv get_GRE_info gre)) - where - get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm +tcIfaceImport :: IfaceImport -> ImportUserSpec +tcIfaceImport (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll +tcIfaceImport (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut (mkNameSet ns)) +tcIfaceImport (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (getDetOrdAvails gre)) ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -2015,6 +2015,8 @@ lookupGREInfo hsc_env nm -- and looks up the TyThing in the type environment. -- -- See Note [Retrieving the GREInfo from interfaces] in GHC.Types.GREInfo. + -- Note: This function is very similar to 'tcIfaceGlobal', it would be better to + -- use that if possible. = case nameModule_maybe nm of Nothing -> UnboundGRE Just mod -> ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -1189,7 +1189,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) (gres, imp_user_list) = case want_hiding of Exactly -> let gre_env = mkGlobalRdrEnv $ concatMap (gresFromIE decl_spec) items2 - in (gre_env, ImpUserExplicit gre_env) + in (gre_env, ImpUserExplicit (gresToAvailInfo $ globalRdrEnvElts $ gre_env)) EverythingBut -> let hidden_names = mkNameSet $ concatMap (map greName . snd) items2 in (importsFromIface hsc_env iface decl_spec (Just hidden_names), ImpUserEverythingBut hidden_names) ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -53,7 +53,7 @@ import GHC.Driver.DynFlags import GHC.Driver.Ppr import GHC.Driver.Config -import GHC.Rename.Names (importsFromIface) +import GHC.Rename.Names (importsFromIface, gresFromAvails) import GHC.Runtime.Eval.Types import GHC.Runtime.Interpreter as GHCi @@ -113,6 +113,7 @@ import GHC.Types.TyThing import GHC.Types.Breakpoint import GHC.Types.Unique.Map +import GHC.Types.Avail import GHC.Unit import GHC.Unit.Module.Graph import GHC.Unit.Module.ModIface @@ -122,7 +123,7 @@ import GHC.Unit.Home.PackageTable import GHC.Tc.Module ( runTcInteractive, tcRnType, loadUnqualIfaces ) import GHC.Tc.Solver (simplifyWantedsTcM) -import GHC.Tc.Utils.Env (tcGetInstEnvs, lookupGlobal) +import GHC.Tc.Utils.Env (tcGetInstEnvs) import GHC.Tc.Utils.Instantiate (instDFunType) import GHC.Tc.Utils.Monad import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) @@ -848,21 +849,25 @@ mkTopLevEnv hsc_env modl Nothing -> pure $ Left "not a home module" Just details -> case mi_top_env (hm_iface details) of - Nothing -> pure $ Left "not interpreted" - Just (IfaceTopEnv exports imports) -> do + (IfaceTopEnv exports imports) -> do imports_env <- runInteractiveHsc hsc_env $ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv) $ forM imports $ \iface_import -> do - let ImpUserSpec spec details = tcIfaceImport hsc_env iface_import + let ImpUserSpec spec details = tcIfaceImport iface_import iface <- loadSrcInterface (text "imported by GHCi") (moduleName $ is_mod spec) (is_isboot spec) (is_pkg_qual spec) pure $ case details of ImpUserAll -> importsFromIface hsc_env iface spec Nothing ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns) - ImpUserExplicit x -> x - let get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm - let exports_env = hydrateGlobalRdrEnv get_GRE_info exports + ImpUserExplicit x -> + -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y). + -- It is only used for error messages. It seems dubious even to add an import context to these GREs as + -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that + -- the test case produce the same output as before. + let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } } + in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x + let exports_env = mkGlobalRdrEnv $ gresFromAvails hsc_env Nothing (getDetOrdAvails exports) pure $ Right $ plusGlobalRdrEnv imports_env exports_env where hpt = hsc_HPT hsc_env @@ -880,8 +885,8 @@ moduleIsInterpreted :: GhcMonad m => Module -> m Bool moduleIsInterpreted modl = withSession $ \h -> if notHomeModule (hsc_home_unit h) modl then return False - else liftIO (lookupHpt (hsc_HPT h) (moduleName modl)) >>= \case - Just details -> return (isJust (mi_top_env (hm_iface details))) + else liftIO (HUG.lookupHugByModule modl (hsc_HUG h)) >>= \case + Just hmi -> return (isJust $ homeModInfoByteCode hmi) _not_a_home_module -> return False -- | Looks up an identifier in the current interactive context (for :info) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -124,7 +124,7 @@ import GHC.Serialized import GHC.Unit.Finder import GHC.Unit.Module import GHC.Unit.Module.ModIface -import GHC.Unit.Module.Deps +import GHC.Iface.Syntax import GHC.Utils.Misc import GHC.Utils.Panic as Panic @@ -2887,16 +2887,12 @@ reifyModule (TH.Module (TH.PkgName pkgString) (TH.ModName mString)) = do reifyFromIface reifMod = do iface <- loadInterfaceForModule (text "reifying module from TH for" <+> ppr reifMod) reifMod - let usages = [modToTHMod m | usage <- mi_usages iface, - Just m <- [usageToModule (moduleUnit reifMod) usage] ] + let IfaceTopEnv _ imports = mi_top_env iface + -- Convert IfaceImport to module names + usages = [modToTHMod (ifImpModule imp) | imp <- imports] return $ TH.ModuleInfo usages - usageToModule :: Unit -> Usage -> Maybe Module - usageToModule _ (UsageFile {}) = Nothing - usageToModule this_pkg (UsageHomeModule { usg_mod_name = mn }) = Just $ mkModule this_pkg mn - usageToModule _ (UsagePackageModule { usg_mod = m }) = Just m - usageToModule _ (UsageMergedRequirement { usg_mod = m }) = Just m - usageToModule this_pkg (UsageHomeModuleInterface { usg_mod_name = mn }) = Just $ mkModule this_pkg mn + ------------------------------ mkThAppTs :: TH.Type -> [TH.Type] -> TH.Type ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -206,7 +206,7 @@ data ImportUserSpec data ImpUserList = ImpUserAll -- ^ no user import list - | ImpUserExplicit !GlobalRdrEnv + | ImpUserExplicit ![AvailInfo] | ImpUserEverythingBut !NameSet -- | A 'NameShape' is a substitution on 'Name's that can be used ===================================== compiler/GHC/Types/Avail.hs ===================================== @@ -22,7 +22,8 @@ module GHC.Types.Avail ( filterAvails, nubAvails, sortAvails, - DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails) + DetOrdAvails(DetOrdAvails, getDetOrdAvails, DefinitelyDeterministicAvails), + emptyDetOrdAvails ) where import GHC.Prelude @@ -74,7 +75,7 @@ type Avails = [AvailInfo] -- We guarantee a deterministic order by either using the order explicitly -- given by the user (e.g. in an explicit constructor export list) or instead -- by sorting the avails with 'sortAvails'. -newtype DetOrdAvails = DefinitelyDeterministicAvails Avails +newtype DetOrdAvails = DefinitelyDeterministicAvails { getDetOrdAvails :: Avails } deriving newtype (Binary, Outputable, NFData) -- | It's always safe to match on 'DetOrdAvails' @@ -245,3 +246,7 @@ instance Binary AvailInfo where instance NFData AvailInfo where rnf (Avail n) = rnf n rnf (AvailTC a b) = rnf a `seq` rnf b + +-- | Create an empty DetOrdAvails +emptyDetOrdAvails :: DetOrdAvails +emptyDetOrdAvails = DefinitelyDeterministicAvails [] ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -133,6 +133,7 @@ import GHC.Unit.Module import GHC.Utils.Misc as Utils import GHC.Utils.Outputable import GHC.Utils.Panic +import GHC.Utils.Binary import Control.DeepSeq import Control.Monad ( guard ) @@ -1946,6 +1947,22 @@ data ImpDeclSpec instance NFData ImpDeclSpec where rnf = rwhnf -- Already strict in all fields +instance Binary ImpDeclSpec where + put_ bh (ImpDeclSpec mod as pkg_qual qual _dloc isboot) = do + put_ bh mod + put_ bh as + put_ bh pkg_qual + put_ bh qual + put_ bh isboot + + get bh = do + mod <- get bh + as <- get bh + pkg_qual <- get bh + qual <- get bh + isboot <- get bh + return (ImpDeclSpec mod as pkg_qual qual noSrcSpan isboot) + -- | Import Item Specification -- -- Describes import info a particular Name ===================================== compiler/GHC/Types/PkgQual.hs ===================================== @@ -6,6 +6,7 @@ module GHC.Types.PkgQual where import GHC.Prelude import GHC.Types.SourceText import GHC.Unit.Types +import GHC.Utils.Binary import GHC.Utils.Outputable import Data.Data @@ -38,4 +39,22 @@ instance Outputable PkgQual where ThisPkg u -> doubleQuotes (ppr u) OtherPkg u -> doubleQuotes (ppr u) +instance Binary PkgQual where + put_ bh NoPkgQual = putByte bh 0 + put_ bh (ThisPkg u) = do + putByte bh 1 + put_ bh u + put_ bh (OtherPkg u) = do + putByte bh 2 + put_ bh u + + get bh = do + tag <- getByte bh + case tag of + 0 -> return NoPkgQual + 1 -> do u <- get bh + return (ThisPkg u) + 2 -> do u <- get bh + return (OtherPkg u) + _ -> fail "instance Binary PkgQual: Invalid tag" ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -111,7 +111,6 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name -import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -299,20 +298,13 @@ data ModIface_ (phase :: ModIfacePhase) mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: !(Maybe IfaceTopEnv), + mi_top_env_ :: IfaceTopEnv, -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which -- may contains declarations for things not actually -- defined by the user). Used for GHCi and for inspecting -- the contents of modules via the GHC API only. - -- - -- (We need the source file to figure out the - -- top-level environment, if we didn't compile this module - -- from source then this field contains @Nothing@). - -- - -- Strictly speaking this field should live in the - -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -365,13 +357,23 @@ data ModIface_ (phase :: ModIfacePhase) -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !IfGlobalRdrEnv -- ^ all top level things in this module, including unexported stuff + { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where rnf (IfaceTopEnv a b) = rnf a `seq` rnf b +instance Binary IfaceTopEnv where + put_ bh (IfaceTopEnv exports imports) = do + put_ bh exports + put_ bh imports + get bh = do + exports <- get bh + imports <- get bh + return (IfaceTopEnv exports imports) + + {- Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -479,6 +481,7 @@ instance Binary ModIface where mi_trust_ = trust, mi_trust_pkg_ = trust_pkg, mi_complete_matches_ = complete_matches, + mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header @@ -526,6 +529,7 @@ instance Binary ModIface where put_ bh trust put_ bh trust_pkg put_ bh complete_matches + lazyPut bh top_env lazyPutMaybe bh docs get bh = do @@ -560,6 +564,7 @@ instance Binary ModIface where trust <- get bh trust_pkg <- get bh complete_matches <- get bh + top_env <- lazyGet bh docs <- lazyGetMaybe bh return (PrivateModIface { mi_module_ = mod, @@ -582,7 +587,6 @@ instance Binary ModIface where mi_decls_ = decls, mi_extra_decls_ = extra_decls, mi_foreign_ = foreign_, - mi_top_env_ = Nothing, mi_defaults_ = defaults, mi_insts_ = insts, mi_fam_insts_ = fam_insts, @@ -593,6 +597,7 @@ instance Binary ModIface where -- And build the cached values mi_complete_matches_ = complete_matches, mi_docs_ = docs, + mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read mi_final_exts_ = ModIfaceBackend { @@ -613,8 +618,6 @@ instance Binary ModIface where }}) --- | The original names declared of a certain module that are exported -type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod @@ -638,7 +641,7 @@ emptyPartialModIface mod mi_decls_ = [], mi_extra_decls_ = Nothing, mi_foreign_ = emptyIfaceForeign, - mi_top_env_ = Nothing, + mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , mi_hpc_ = False, mi_trust_ = noIfaceTrustInfo, mi_trust_pkg_ = False, @@ -810,15 +813,14 @@ addSourceFingerprint val iface = iface { mi_src_hash_ = val } -- | Copy fields that aren't serialised to disk to the new 'ModIface_'. -- This includes especially hashes that are usually stored in the interface --- file header and 'mi_top_env'. +-- file header. -- -- We need this function after calling 'shareIface', to make sure the -- 'ModIface_' doesn't lose any information. This function does not discard -- the in-memory byte array buffer 'mi_hi_bytes'. restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase restoreFromOldModIface old new = new - { mi_top_env_ = mi_top_env_ old - , mi_hsc_src_ = mi_hsc_src_ old + { mi_hsc_src_ = mi_hsc_src_ old , mi_src_hash_ = mi_src_hash_ old } @@ -879,7 +881,7 @@ set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } -set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase @@ -996,7 +998,7 @@ pattern ModIface :: [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> ModIface_ phase ===================================== testsuite/tests/ghci/should_run/Makefile ===================================== @@ -7,3 +7,9 @@ T3171: echo "do Control.Concurrent.threadDelay 3000000; putStrLn \"threadDelay was not interrupted\"" | \ "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) & \ sleep 2; kill -INT $$!; wait + +TopEnvIface: + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface + # Second compilation starts from interface files, but still can print "a" + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface + ===================================== testsuite/tests/ghci/should_run/TopEnvIface.hs ===================================== @@ -0,0 +1,4 @@ +module TopEnvIface where + +import TopEnvIface2 + ===================================== testsuite/tests/ghci/should_run/TopEnvIface.stdout ===================================== @@ -0,0 +1,8 @@ +[1 of 2] Compiling TopEnvIface2 ( TopEnvIface2.hs, interpreted ) +[2 of 2] Compiling TopEnvIface ( TopEnvIface.hs, interpreted ) +Ok, two modules loaded. +"I should be printed twice" +Leaving GHCi. +Ok, two modules loaded. +"I should be printed twice" +Leaving GHCi. ===================================== testsuite/tests/ghci/should_run/TopEnvIface2.hs ===================================== @@ -0,0 +1,3 @@ +module TopEnvIface2 where + +a = "I should be printed twice" ===================================== testsuite/tests/ghci/should_run/all.T ===================================== @@ -96,3 +96,4 @@ test('LargeBCO', [extra_files(['LargeBCO_A.hs']), req_interp, extra_hc_opts("-O test('T24115', just_ghci + [extra_run_opts("-e ':add T24115.hs'")], ghci_script, ['T24115.script']) test('T10920', [only_ways(ghci_ways), extra_files(['LocalPrelude/Prelude.hs'])], ghci_script, ['T10920.script']) +test('TopEnvIface', [only_ways(ghci_ways)], makefile_test, []) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a5de39dec43ad4fb91234235ca7a22c9ea3c9d0c...20dc404996ef97644df121eae62776e59f86221e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a5de39dec43ad4fb91234235ca7a22c9ea3c9d0c...20dc404996ef97644df121eae62776e59f86221e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/4ef551d1/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 19:33:22 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 03 Mar 2025 14:33:22 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/az/sync-ghc-exactprint Message-ID: <67c60402e88d6_2ae4294cbff872778@gitlab.mail> Alan Zimmerman pushed new branch wip/az/sync-ghc-exactprint at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/sync-ghc-exactprint You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/917ed3c8/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 3 19:36:45 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 03 Mar 2025 14:36:45 -0500 Subject: [Git][ghc/ghc][wip/T25577] 12 commits: haddock/doc: Drop version and release Message-ID: <67c604cdde943_2bc5d8d22d096717@gitlab.mail> Ben Gamari pushed to branch wip/T25577 at Glasgow Haskell Compiler / GHC Commits: 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 88e509b5 by Ben Gamari at 2025-03-03T14:32:38-05:00 testsuite: Add testcase for #25577 - - - - - 1b8b1847 by Ben Gamari at 2025-03-03T14:32:38-05:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - f6ff58d1 by Ben Gamari at 2025-03-03T14:32:38-05:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - de7343a4 by Ben Gamari at 2025-03-03T14:36:16-05:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 119 changed files: - compiler/GHC.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - distrib/configure.ac.in - ghc/GHCi/UI.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - m4/fp_settings.m4 - rts/linker/MachO.c - rts/linker/MachOTypes.h - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - utils/haddock/doc/conf.py The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c726b895cadebc91fdfca013455ffa2eebdb929...de7343a4cf222d88629f4e5279b55666aad5ce77 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c726b895cadebc91fdfca013455ffa2eebdb929...de7343a4cf222d88629f4e5279b55666aad5ce77 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/aa1d7b28/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 20:03:26 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Mon, 03 Mar 2025 15:03:26 -0500 Subject: [Git][ghc/ghc][wip/andreask/interpreter_primops] Add Addr# indexing primops. Fix some obvious 32bit bugs. Message-ID: <67c60b0e27489_2c674bc5d0051546@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/interpreter_primops at Glasgow Haskell Compiler / GHC Commits: c5e9a83e by Andreas Klebinger at 2025-03-03T20:40:56+01:00 Add Addr# indexing primops. Fix some obvious 32bit bugs. - - - - - 6 changed files: - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/StgToByteCode.hs - rts/Disassembler.c - rts/Interpreter.c - rts/include/rts/Bytecodes.h Changes: ===================================== compiler/GHC/ByteCode/Asm.hs ===================================== @@ -544,109 +544,137 @@ assembleI platform i = case i of W64 -> emit bci_OP_ADD_64 [] W32 -> emit bci_OP_ADD_32 [] W16 -> emit bci_OP_ADD_16 [] - W8 -> emit bci_OP_ADD_08 [] + W8 -> emit bci_OP_ADD_08 [] + _ -> unsupported_width OP_SUB w -> case w of W64 -> emit bci_OP_SUB_64 [] W32 -> emit bci_OP_SUB_32 [] W16 -> emit bci_OP_SUB_16 [] - W8 -> emit bci_OP_SUB_08 [] + W8 -> emit bci_OP_SUB_08 [] + _ -> unsupported_width OP_AND w -> case w of W64 -> emit bci_OP_AND_64 [] W32 -> emit bci_OP_AND_32 [] W16 -> emit bci_OP_AND_16 [] - W8 -> emit bci_OP_AND_08 [] + W8 -> emit bci_OP_AND_08 [] + _ -> unsupported_width OP_XOR w -> case w of W64 -> emit bci_OP_XOR_64 [] W32 -> emit bci_OP_XOR_32 [] W16 -> emit bci_OP_XOR_16 [] - W8 -> emit bci_OP_XOR_08 [] + W8 -> emit bci_OP_XOR_08 [] + _ -> unsupported_width OP_OR w -> case w of W64 -> emit bci_OP_OR_64 [] W32 -> emit bci_OP_OR_32 [] W16 -> emit bci_OP_OR_16 [] - W8 -> emit bci_OP_OR_08 [] + W8 -> emit bci_OP_OR_08 [] + _ -> unsupported_width OP_NOT w -> case w of W64 -> emit bci_OP_NOT_64 [] W32 -> emit bci_OP_NOT_32 [] W16 -> emit bci_OP_NOT_16 [] - W8 -> emit bci_OP_NOT_08 [] + W8 -> emit bci_OP_NOT_08 [] + _ -> unsupported_width OP_NEG w -> case w of W64 -> emit bci_OP_NEG_64 [] W32 -> emit bci_OP_NEG_32 [] W16 -> emit bci_OP_NEG_16 [] - W8 -> emit bci_OP_NEG_08 [] + W8 -> emit bci_OP_NEG_08 [] + _ -> unsupported_width OP_MUL w -> case w of W64 -> emit bci_OP_MUL_64 [] W32 -> emit bci_OP_MUL_32 [] W16 -> emit bci_OP_MUL_16 [] - W8 -> emit bci_OP_MUL_08 [] + W8 -> emit bci_OP_MUL_08 [] + _ -> unsupported_width OP_SHL w -> case w of W64 -> emit bci_OP_SHL_64 [] W32 -> emit bci_OP_SHL_32 [] W16 -> emit bci_OP_SHL_16 [] - W8 -> emit bci_OP_SHL_08 [] + W8 -> emit bci_OP_SHL_08 [] + _ -> unsupported_width OP_ASR w -> case w of W64 -> emit bci_OP_ASR_64 [] W32 -> emit bci_OP_ASR_32 [] W16 -> emit bci_OP_ASR_16 [] - W8 -> emit bci_OP_ASR_08 [] + W8 -> emit bci_OP_ASR_08 [] + _ -> unsupported_width OP_LSR w -> case w of W64 -> emit bci_OP_LSR_64 [] W32 -> emit bci_OP_LSR_32 [] W16 -> emit bci_OP_LSR_16 [] - W8 -> emit bci_OP_LSR_08 [] + W8 -> emit bci_OP_LSR_08 [] + _ -> unsupported_width OP_NEQ w -> case w of W64 -> emit bci_OP_NEQ_64 [] W32 -> emit bci_OP_NEQ_32 [] W16 -> emit bci_OP_NEQ_16 [] - W8 -> emit bci_OP_NEQ_08 [] + W8 -> emit bci_OP_NEQ_08 [] + _ -> unsupported_width OP_EQ w -> case w of W64 -> emit bci_OP_EQ_64 [] W32 -> emit bci_OP_EQ_32 [] W16 -> emit bci_OP_EQ_16 [] - W8 -> emit bci_OP_EQ_08 [] + W8 -> emit bci_OP_EQ_08 [] + _ -> unsupported_width OP_U_LT w -> case w of W64 -> emit bci_OP_U_LT_64 [] W32 -> emit bci_OP_U_LT_32 [] W16 -> emit bci_OP_U_LT_16 [] - W8 -> emit bci_OP_U_LT_08 [] + W8 -> emit bci_OP_U_LT_08 [] + _ -> unsupported_width OP_S_LT w -> case w of W64 -> emit bci_OP_S_LT_64 [] W32 -> emit bci_OP_S_LT_32 [] W16 -> emit bci_OP_S_LT_16 [] - W8 -> emit bci_OP_S_LT_08 [] + W8 -> emit bci_OP_S_LT_08 [] + _ -> unsupported_width OP_U_GE w -> case w of W64 -> emit bci_OP_U_GE_64 [] W32 -> emit bci_OP_U_GE_32 [] W16 -> emit bci_OP_U_GE_16 [] - W8 -> emit bci_OP_U_GE_08 [] + W8 -> emit bci_OP_U_GE_08 [] + _ -> unsupported_width OP_S_GE w -> case w of W64 -> emit bci_OP_S_GE_64 [] W32 -> emit bci_OP_S_GE_32 [] W16 -> emit bci_OP_S_GE_16 [] - W8 -> emit bci_OP_S_GE_08 [] + W8 -> emit bci_OP_S_GE_08 [] + _ -> unsupported_width OP_U_GT w -> case w of W64 -> emit bci_OP_U_GT_64 [] W32 -> emit bci_OP_U_GT_32 [] W16 -> emit bci_OP_U_GT_16 [] - W8 -> emit bci_OP_U_GT_08 [] + W8 -> emit bci_OP_U_GT_08 [] + _ -> unsupported_width OP_S_GT w -> case w of W64 -> emit bci_OP_S_GT_64 [] W32 -> emit bci_OP_S_GT_32 [] W16 -> emit bci_OP_S_GT_16 [] - W8 -> emit bci_OP_S_GT_08 [] + W8 -> emit bci_OP_S_GT_08 [] + _ -> unsupported_width OP_U_LE w -> case w of W64 -> emit bci_OP_U_LE_64 [] W32 -> emit bci_OP_U_LE_32 [] W16 -> emit bci_OP_U_LE_16 [] - W8 -> emit bci_OP_U_LE_08 [] + W8 -> emit bci_OP_U_LE_08 [] + _ -> unsupported_width OP_S_LE w -> case w of W64 -> emit bci_OP_S_LE_64 [] W32 -> emit bci_OP_S_LE_32 [] W16 -> emit bci_OP_S_LE_16 [] - W8 -> emit bci_OP_S_LE_08 [] + W8 -> emit bci_OP_S_LE_08 [] + _ -> unsupported_width + + OP_INDEX_ADDR w -> case w of + W64 -> emit bci_OP_INDEX_ADDR_64 [] + W32 -> emit bci_OP_INDEX_ADDR_32 [] + W16 -> emit bci_OP_INDEX_ADDR_16 [] + W8 -> emit bci_OP_INDEX_ADDR_08 [] + _ -> unsupported_width BRK_FUN arr tick_mod tickx info_mod infox cc -> do p1 <- ptr (BCOPtrBreakArray arr) @@ -664,6 +692,7 @@ assembleI platform i = case i of #endif where + unsupported_width = panic "GHC.ByteCode.Asm: Unsupported Width" literal (LitLabel fs _) = litlabel fs literal LitNullAddr = word 0 literal (LitFloat r) = float (fromRational r) ===================================== compiler/GHC/ByteCode/Instr.hs ===================================== @@ -36,7 +36,6 @@ import GHC.Stack.CCS (CostCentre) import GHC.Stg.Syntax import GHCi.BreakArray (BreakArray) import Language.Haskell.Syntax.Module.Name (ModuleName) -import GHC.Types.RepType (PrimRep) import GHC.Cmm.Type (Width) -- ---------------------------------------------------------------------------- @@ -245,6 +244,10 @@ data BCInstr | OP_S_GT !Width | OP_S_LE !Width + -- Always puts at least a machine word on the stack, with the low part of the stack containing the result. + -- We zero extend the result we put on the stack. + | OP_INDEX_ADDR !Width + -- For doing magic ByteArray passing to foreign calls | SWIZZLE !WordOff -- to the ptr N words down the stack, !Int -- add M @@ -448,6 +451,8 @@ instance Outputable BCInstr where ppr (OP_U_GT w) = text "OP_U_GT_" <> ppr w ppr (OP_U_LE w) = text "OP_U_LE_" <> ppr w + ppr (OP_INDEX_ADDR w) = text "OP_INDEX_ADDR_" <> ppr w + ppr (SWIZZLE stkoff n) = text "SWIZZLE " <+> text "stkoff" <+> ppr stkoff <+> text "by" <+> ppr n ppr ENTER = text "ENTER" @@ -578,6 +583,7 @@ bciStackUse OP_U_LT{} = 0 bciStackUse OP_U_GT{} = 0 bciStackUse OP_U_LE{} = 0 bciStackUse OP_U_GE{} = 0 +bciStackUse OP_INDEX_ADDR{} = 0 bciStackUse SWIZZLE{} = 0 bciStackUse BRK_FUN{} = 0 ===================================== compiler/GHC/StgToByteCode.hs ===================================== @@ -734,9 +734,14 @@ schemeT d s p (StgOpApp (StgFCallOp (CCall ccall_spec) _ty) args result_ty) then generateCCall d s p ccall_spec result_ty args else unsupportedCConvException -schemeT d s p (StgOpApp (StgPrimOp op) args _ty) - | Just prim_code <- doPrimOp op d s p args = prim_code - | otherwise = doTailCall d s p (primOpId op) (reverse args) +schemeT d s p (StgOpApp (StgPrimOp op) args _ty) = do + profile <- getProfile + let platform = profilePlatform profile + case doPrimOp platform op d s p args of + -- Can we do this right in the interpreter? + Just prim_code -> prim_code + -- Otherwise we have to do a call to the primop wrapper instead :( + _ -> doTailCall d s p (primOpId op) (reverse args) schemeT d s p (StgOpApp (StgPrimCallOp (PrimCall label unit)) args result_ty) = generatePrimCall d s p label (Just unit) result_ty args @@ -831,15 +836,15 @@ doTailCall init_d s p fn args = do (final_d, more_push_code) <- push_seq (d + sz) args return (final_d, push_code `appOL` more_push_code) -doPrimOp :: PrimOp +doPrimOp :: Platform + -> PrimOp -> StackDepth -> Sequel -> BCEnv -> [StgArg] -> Maybe (BcM BCInstrList) -doPrimOp op init_d s p args = +doPrimOp platform op init_d s p args = case op of - -- TODO: IntAddOp and friends are only 64bit on 64bit platforms IntAddOp -> primOp OP_ADD Int64AddOp -> primOp OP_ADD WordAddOp -> primOp OP_ADD @@ -850,6 +855,7 @@ doPrimOp op init_d s p args = WordSubOp -> primOp OP_SUB Int64SubOp -> primOp OP_SUB Word64SubOp -> primOp OP_SUB + AddrSubOp -> primOp OP_SUB Int8SubOp -> primOp OP_SUB Word8SubOp -> primOp OP_SUB @@ -886,26 +892,33 @@ doPrimOp op init_d s p args = IntNeOp -> primOp OP_NEQ WordNeOp -> primOp OP_NEQ Word64NeOp -> primOp OP_NEQ + AddrNeOp -> primOp OP_NEQ IntEqOp -> primOp OP_EQ WordEqOp -> primOp OP_EQ Word64EqOp -> primOp OP_EQ + AddrEqOp -> primOp OP_EQ + CharEqOp -> primOp OP_EQ IntLtOp -> primOp OP_S_LT WordLtOp -> primOp OP_U_LT Word64LtOp -> primOp OP_U_LT + AddrLtOp -> primOp OP_U_LT IntGeOp -> primOp OP_S_GE WordGeOp -> primOp OP_U_GE Word64GeOp -> primOp OP_U_GE + AddrGeOp -> primOp OP_U_GE IntGtOp -> primOp OP_S_GT WordGtOp -> primOp OP_U_GT Word64GtOp -> primOp OP_U_GT + AddrGtOp -> primOp OP_U_GT IntLeOp -> primOp OP_S_LE WordLeOp -> primOp OP_U_LE Word64LeOp -> primOp OP_U_LE + AddrLeOp -> primOp OP_U_LE IntNegOp -> primOp OP_NEG Int64NegOp -> primOp OP_NEG @@ -925,9 +938,14 @@ doPrimOp op init_d s p args = ChrOp -> no_op -- Int# and Char# are rep'd the same OrdOp -> no_op + IndexOffAddrOp_Word8 -> primOpWithRep (OP_INDEX_ADDR W8) W8 + IndexOffAddrOp_Word16 -> primOpWithRep (OP_INDEX_ADDR W16) W16 + IndexOffAddrOp_Word32 -> primOpWithRep (OP_INDEX_ADDR W32) W32 + IndexOffAddrOp_Word64 -> primOpWithRep (OP_INDEX_ADDR W64) W64 + _ -> Nothing where - primArg1Width platform (arg:_) + primArg1Width arg | rep <- (stgArgRepU arg) = case rep of AddrRep -> platformWordWidth platform @@ -953,19 +971,33 @@ doPrimOp op init_d s p args = VecRep{} -> unexpectedRep where unexpectedRep = panic "doPrimOp: Unexpected argument rep" - primArg1Width _ _ = panic "doPrimOp: Unexpected argument count" + + + -- TODO: The slides for the result need to be two words on 32bit for 64bit ops. + mkNReturn width + | W64 <- width = RETURN L -- L works for 64 bit on any platform + | otherwise = RETURN N -- <64bit width, fits in word on all platforms + + mkSlideWords width = if platformWordWidth platform < width then 2 else 1 -- Push args, execute primop, slide, return_N primOp op_inst = Just $ do - platform <- profilePlatform <$> getProfile - prim_code <- mkPrimOpCode init_d s p (op_inst $ primArg1Width platform args) $ args - let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N + let width = primArg1Width (head args) + prim_code <- mkPrimOpCode init_d s p (op_inst width) $ args + let slide = mkSlideW (mkSlideWords width) (bytesToWords platform $ init_d - s) `snocOL` mkNReturn width + return $ prim_code `appOL` slide + + primOpWithRep :: BCInstr -> Width -> Maybe (BcM (OrdList BCInstr)) + primOpWithRep op_inst width = Just $ do + prim_code <- mkPrimOpCode init_d s p op_inst $ args + + let slide = mkSlideW (mkSlideWords width) (bytesToWords platform $ init_d - s) `snocOL` mkNReturn width return $ prim_code `appOL` slide no_op = Just $ do - platform <- profilePlatform <$> getProfile + let width = primArg1Width (head args) prim_code <- terribleNoOp init_d s p undefined args - let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N + let slide = mkSlideW (mkSlideWords width) (bytesToWords platform $ init_d - s) `snocOL` mkNReturn width return $ prim_code `appOL` slide -- It's horrible, but still better than calling intToWord ... ===================================== rts/Disassembler.c ===================================== @@ -487,6 +487,8 @@ disInstr ( StgBCO *bco, int pc ) BELCH_INSTR_NAME_ALL_SIZES(OP_S_GE); BELCH_INSTR_NAME_ALL_SIZES(OP_S_LT); + BELCH_INSTR_NAME_ALL_SIZES(OP_INDEX_ADDR); + default: barf("disInstr: unknown opcode %u", (unsigned int) instr); } ===================================== rts/Interpreter.c ===================================== @@ -2274,6 +2274,40 @@ run_BCO: case bci_OP_NOT_08: UN_SIZED_OP(~, StgWord8) case bci_OP_NEG_08: UN_SIZED_OP(-, StgInt8) + case bci_OP_INDEX_ADDR_64: + { + StgWord64* addr = (StgWord64*) SpW(1); + StgWord offset = (StgWord) SpW(0); + if(sizeof(StgPtr) == sizeof(StgWord64)) { + Sp_addW(1); + } + SpW64(0) = *(addr+offset); + goto nextInsn; + } + + case bci_OP_INDEX_ADDR_32: + { + StgWord32* addr = (StgWord32*) SpW(1); + StgWord offset = (StgWord) SpW(0); + Sp_addW(1); + SpW(0) = (StgWord) *(addr+offset); + goto nextInsn; + } + case bci_OP_INDEX_ADDR_16: + { + StgWord16* addr = (StgWord16*) SpW(0); + SpW(0) = (StgWord) *addr; + goto nextInsn; + } + case bci_OP_INDEX_ADDR_08: + { + StgWord8* addr = (StgWord8*) SpW(1); + StgWord offset = (StgWord) SpW(0); + Sp_addW(1); + SpW(0) = (StgWord) *(addr+offset); + goto nextInsn; + } + case bci_CCALL: { void *tok; W_ stk_offset = BCO_GET_LARGE_ARG; ===================================== rts/include/rts/Bytecodes.h ===================================== @@ -209,6 +209,11 @@ #define bci_OP_S_LT_08 228 #define bci_OP_S_LE_08 229 +#define bci_OP_INDEX_ADDR_08 240 +#define bci_OP_INDEX_ADDR_16 241 +#define bci_OP_INDEX_ADDR_32 242 +#define bci_OP_INDEX_ADDR_64 243 + /* If you need to go past 255 then you will run into the flags */ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c5e9a83e9bfb7d9b0cfc9406712a7cbcf3d32eec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c5e9a83e9bfb7d9b0cfc9406712a7cbcf3d32eec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/852ca224/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 20:28:03 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Mar 2025 15:28:03 -0500 Subject: [Git][ghc/ghc][master] Remove most of `GHC.Internal.Pack` Message-ID: <67c610d3cdf17_2c674b4ae12457738@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - 1 changed file: - libraries/ghc-internal/src/GHC/Internal/Pack.hs Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Pack.hs ===================================== @@ -12,95 +12,20 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- ⚠Warning: Starting @base-4.18@, this module is being deprecated. --- See https://gitlab.haskell.org/ghc/ghc/-/issues/21461 for more information. --- --- --- --- This module provides a small set of low-level functions for packing --- and unpacking a chunk of bytes. Used by code emitted by the compiler --- plus the prelude libraries. --- --- The programmer level view of packed strings is provided by a GHC --- system library PackedString. +-- This function is just used by `rts_mkString` -- ----------------------------------------------------------------------------- module GHC.Internal.Pack ( - -- (**) - emitted by compiler. - - packCString#, unpackCString, - unpackCString#, - unpackNBytes#, - unpackFoldrCString#, -- (**) - unpackAppendCString#, -- (**) ) where import GHC.Internal.Base -import GHC.Internal.List ( length ) -import GHC.Internal.ST import GHC.Internal.Ptr -data ByteArray ix = ByteArray ix ix ByteArray# -data MutableByteArray s ix = MutableByteArray ix ix (MutableByteArray# s) - unpackCString :: Ptr a -> [Char] unpackCString a@(Ptr addr) | a == nullPtr = [] | otherwise = unpackCString# addr - -packCString# :: [Char] -> ByteArray# -packCString# str = case (packString str) of { ByteArray _ _ bytes -> bytes } - -packString :: [Char] -> ByteArray Int -packString str = runST (packStringST str) - -packStringST :: [Char] -> ST s (ByteArray Int) -packStringST str = - let len = length str in - packNBytesST len str - -packNBytesST :: Int -> [Char] -> ST s (ByteArray Int) -packNBytesST (I# length#) str = - {- - allocate an array that will hold the string - (not forgetting the NUL byte at the end) - -} - new_ps_array (length# +# 1#) >>= \ ch_array -> - -- fill in packed string from "str" - fill_in ch_array 0# str >> - -- freeze the puppy: - freeze_ps_array ch_array length# - where - fill_in :: MutableByteArray s Int -> Int# -> [Char] -> ST s () - fill_in arr_in# idx [] = - write_ps_array arr_in# idx (chr# 0#) >> - return () - - fill_in arr_in# idx (C# c : cs) = - write_ps_array arr_in# idx c >> - fill_in arr_in# (idx +# 1#) cs - --- (Very :-) ``Specialised'' versions of some CharArray things... - -new_ps_array :: Int# -> ST s (MutableByteArray s Int) -write_ps_array :: MutableByteArray s Int -> Int# -> Char# -> ST s () -freeze_ps_array :: MutableByteArray s Int -> Int# -> ST s (ByteArray Int) - -new_ps_array size = ST $ \ s -> - case (newByteArray# size s) of { (# s2#, barr# #) -> - (# s2#, MutableByteArray bot bot barr# #) } - where - bot = errorWithoutStackTrace "new_ps_array" - -write_ps_array (MutableByteArray _ _ barr#) n ch = ST $ \ s# -> - case writeCharArray# barr# n ch s# of { s2# -> - (# s2#, () #) } - --- same as unsafeFreezeByteArray -freeze_ps_array (MutableByteArray _ _ arr#) len# = ST $ \ s# -> - case unsafeFreezeByteArray# arr# s# of { (# s2#, frozen# #) -> - (# s2#, ByteArray 0 (I# len#) frozen# #) } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b78e139033ab07232313888cc503712799fa76c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b78e139033ab07232313888cc503712799fa76c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/876d85bb/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 20:28:50 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Mar 2025 15:28:50 -0500 Subject: [Git][ghc/ghc][master] 2 commits: ghci: Don't set virtualCWD on every iteration Message-ID: <67c611025a99c_2c674b4703246204a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - 4 changed files: - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs Changes: ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -18,7 +18,7 @@ module GHC.Runtime.Eval ( abandon, abandonAll, getResumeContext, getHistorySpan, - getModBreaks, + getModBreaks, readModBreaks, getHistoryModule, setupBreakpoint, back, forward, @@ -130,14 +130,12 @@ import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) import GHC.IfaceToCore import Control.Monad -import Control.Monad.Catch as MC import Data.Array import Data.Dynamic import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.List (find,intercalate) import Data.List.NonEmpty (NonEmpty) -import System.Directory import Unsafe.Coerce ( unsafeCoerce ) import qualified GHC.Unit.Home.Graph as HUG @@ -156,9 +154,8 @@ getHistoryModule = ibi_tick_mod . historyBreakpointId getHistorySpan :: HscEnv -> History -> IO SrcSpan getHistorySpan hsc_env hist = do let ibi = historyBreakpointId hist - HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) >>= pure . \case - Just hmi -> modBreaks_locs (getModBreaks hmi) ! ibi_tick_index ibi - _ -> panic "getHistorySpan" + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi {- | Finds the enclosing top level function name -} -- ToDo: a better way to do this would be to keep hold of the decl_path computed @@ -166,9 +163,8 @@ getHistorySpan hsc_env hist = do -- for each tick. findEnclosingDecls :: HscEnv -> InternalBreakpointId -> IO [String] findEnclosingDecls hsc_env ibi = do - hmi <- expectJust <$> HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) - return $ - modBreaks_decls (getModBreaks hmi) ! ibi_tick_index ibi + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_decls brks ! ibi_tick_index ibi -- | Update fixity environment in the current interactive context. updateFixityEnv :: GhcMonad m => FixityEnv -> m () @@ -232,10 +228,9 @@ execStmt' stmt stmt_text ExecOptions{..} = do updateFixityEnv fix_env status <- - withVirtualCWD $ - liftIO $ do - let eval_opts = initEvalOpts idflags' (isStep execSingleStep) - evalStmt interp eval_opts (execWrap hval) + liftIO $ do + let eval_opts = initEvalOpts idflags' (enableGhcStepMode execSingleStep) + evalStmt interp eval_opts (execWrap hval) let ic = hsc_IC hsc_env bindings = (ic_tythings ic, ic_gre_cache ic) @@ -282,38 +277,17 @@ them. The relevant predicate is OccName.isDerivedOccName. See #11051 for more background and examples. -} -withVirtualCWD :: GhcMonad m => m a -> m a -withVirtualCWD m = do - hsc_env <- getSession - - -- a virtual CWD is only necessary when we're running interpreted code in - -- the same process as the compiler. - case interpInstance <$> hsc_interp hsc_env of - Just (ExternalInterp {}) -> m - _ -> do - let ic = hsc_IC hsc_env - let set_cwd = do - dir <- liftIO $ getCurrentDirectory - case ic_cwd ic of - Just dir -> liftIO $ setCurrentDirectory dir - Nothing -> return () - return dir - - reset_cwd orig_dir = do - virt_dir <- liftIO $ getCurrentDirectory - hsc_env <- getSession - let old_IC = hsc_IC hsc_env - setSession hsc_env{ hsc_IC = old_IC{ ic_cwd = Just virt_dir } } - liftIO $ setCurrentDirectory orig_dir - - MC.bracket set_cwd reset_cwd $ \_ -> m - parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) parseImportDecl expr = withSession $ \hsc_env -> liftIO $ hscImport hsc_env expr emptyHistory :: Int -> BoundedList History emptyHistory size = nilBL size +-- | Turn an 'EvalStatus_' result from interpreting Haskell into a GHCi 'ExecResult'. +-- +-- This function is responsible for resuming execution at an intermediate +-- breakpoint if we don't care about that breakpoint (e.g. if using :steplocal +-- or :stepmodule, rather than :step, we only care about certain breakpoints). handleRunStatus :: GhcMonad m => SingleStep -> String -> ResumeBindings @@ -322,92 +296,107 @@ handleRunStatus :: GhcMonad m -> BoundedList History -> m ExecResult -handleRunStatus step expr bindings final_ids status history0 - | RunAndLogSteps <- step = tracing - | otherwise = not_tracing - where - tracing - | EvalBreak apStack_ref (Just eval_break) resume_ctxt _ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - let dflags = hsc_dflags hsc_env - ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break - hmi <- liftIO $ expectJust <$> - lookupHpt (hsc_HPT hsc_env) (moduleName (ibi_tick_mod ibi)) - let breaks = getModBreaks hmi - - b <- liftIO $ - breakpointStatus interp (modBreaks_flags breaks) (ibi_tick_index ibi) - if b - then not_tracing - -- This breakpoint is explicitly enabled; we want to stop - -- instead of just logging it. - else do - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi - let !history' = history1 `consBL` history0 - -- history is strict, otherwise our BoundedList is pointless. - fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - let eval_opts = initEvalOpts dflags True - status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv - handleRunStatus RunAndLogSteps expr bindings final_ids - status history' - | otherwise - = not_tracing - - not_tracing - -- Hit a breakpoint - | EvalBreak apStack_ref maybe_break resume_ctxt ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - ibi <- case maybe_break of - Nothing -> pure Nothing - Just break -> fmap Just $ liftIO $ - evalBreakpointToId (hsc_HPT hsc_env) break - (hsc_env1, names, span, decl) <- liftIO $ - bindLocalsAtBreakpoint hsc_env apStack_fhv ibi - let - resume = Resume - { resumeStmt = expr - , resumeContext = resume_ctxt_fhv - , resumeBindings = bindings - , resumeFinalIds = final_ids - , resumeApStack = apStack_fhv - , resumeBreakpointId = ibi - , resumeSpan = span - , resumeHistory = toListBL history0 - , resumeDecl = decl - , resumeCCS = ccs - , resumeHistoryIx = 0 - } - hsc_env2 = pushResume hsc_env1 resume - - setSession hsc_env2 - return (ExecBreak names ibi) +handleRunStatus step expr bindings final_ids status history0 = do + hsc_env <- getSession + let + interp = hscInterp hsc_env + dflags = hsc_dflags hsc_env + case status of -- Completed successfully - | EvalComplete allocs (EvalSuccess hvals) <- status - = do hsc_env <- getSession - let final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids - final_names = map getName final_ids - interp = hscInterp hsc_env - liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) - hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} - setSession hsc_env' - return (ExecComplete (Right final_names) allocs) + EvalComplete allocs (EvalSuccess hvals) -> do + let + final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids + final_names = map getName final_ids + liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) + hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} + setSession hsc_env' + return (ExecComplete (Right final_names) allocs) -- Completed with an exception - | EvalComplete alloc (EvalException e) <- status - = return (ExecComplete (Left (fromSerializableException e)) alloc) - + EvalComplete alloc (EvalException e) -> + return (ExecComplete (Left (fromSerializableException e)) alloc) + + -- Nothing case: we stopped when an exception was raised, not at a breakpoint. + EvalBreak apStack_ref Nothing resume_ctxt ccs -> do + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + let span = mkGeneralSrcSpan (fsLit "<unknown>") + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span Nothing + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Nothing + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = "<exception thrown>" + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + + setSession hsc_env2 + return (ExecBreak names Nothing) + + -- Just case: we stopped at a breakpoint + EvalBreak apStack_ref (Just eval_break) resume_ctxt ccs -> do + ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break + tick_brks <- liftIO $ readModBreaks hsc_env (ibi_tick_mod ibi) + let + span = modBreaks_locs tick_brks ! ibi_tick_index ibi + decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi + + b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi) + + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + + -- This breakpoint is explicitly enabled; we want to stop + -- instead of just logging it. + if b || breakHere step span then do + -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break. + -- Specifically, for :steplocal or :stepmodule, don't return control + -- and simply resume execution from here until we hit a breakpoint we do want to stop at. + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Just ibi + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = decl + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + setSession hsc_env2 + return (ExecBreak names (Just ibi)) + else do + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) + status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv + history <- if not tracing then pure history0 else do + history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi + let !history' = history1 `consBL` history0 + -- history is strict, otherwise our BoundedList is pointless. + return history' + handleRunStatus step expr bindings final_ids status history + where + tracing | RunAndLogSteps <- step = True + | otherwise = False -resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> Maybe Int +resumeExec :: GhcMonad m => SingleStep -> Maybe Int -> m ExecResult -resumeExec canLogSpan step mbCnt +resumeExec step mbCnt = do hsc_env <- getSession let ic = hsc_IC hsc_env @@ -445,42 +434,41 @@ resumeExec canLogSpan step mbCnt , resumeBreakpointId = mb_brkpt , resumeSpan = span , resumeHistory = hist } -> - withVirtualCWD $ do + do -- When the user specified a break ignore count, set it -- in the interpreter case (mb_brkpt, mbCnt) of (Just brkpt, Just cnt) -> setupBreakpoint hsc_env (toBreakpointId brkpt) cnt _ -> return () - let eval_opts = initEvalOpts dflags (isStep step) + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv let prevHistoryLst = fromListBL 50 hist hist' = case mb_brkpt of Nothing -> pure prevHistoryLst Just bi - | not $ canLogSpan span -> pure prevHistoryLst - | otherwise -> do + | breakHere step span -> do hist1 <- liftIO (mkHistory hsc_env apStack bi) return $ hist1 `consBL` fromListBL 50 hist + | otherwise -> pure prevHistoryLst handleRunStatus step expr bindings final_ids status =<< hist' setupBreakpoint :: GhcMonad m => HscEnv -> BreakpointId -> Int -> m () -- #19157 setupBreakpoint hsc_env bi cnt = do let modl = bi_tick_mod bi - modBreaks <- getModBreaks . expectJust <$> - liftIO (lookupHpt (hsc_HPT hsc_env) (moduleName modl)) + modBreaks <- liftIO $ readModBreaks hsc_env modl let breakarray = modBreaks_flags modBreaks interp = hscInterp hsc_env _ <- liftIO $ GHCi.storeBreakpoint interp breakarray (bi_tick_index bi) cnt pure () -back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) back n = moveHist (+n) -forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) forward n = moveHist (subtract n) -moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan, String) +moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan) moveHist fn = do hsc_env <- getSession case ic_resume (hsc_IC hsc_env) of @@ -498,15 +486,20 @@ moveHist fn = do let update_ic apStack mb_info = do - (hsc_env1, names, span, decl) <- - liftIO $ bindLocalsAtBreakpoint hsc_env apStack mb_info + span <- case mb_info of + Nothing -> return $ mkGeneralSrcSpan (fsLit "<unknown>") + Just ibi -> liftIO $ do + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi + (hsc_env1, names) <- + liftIO $ bindLocalsAtBreakpoint hsc_env apStack span mb_info let ic = hsc_IC hsc_env1 r' = r { resumeHistoryIx = new_ix } ic' = ic { ic_resume = r':rs } setSession hsc_env1{ hsc_IC = ic' } - return (names, new_ix, span, decl) + return (names, new_ix, span) -- careful: we want apStack to be the AP_STACK itself, not a thunk -- around it, hence the cases are carefully constructed below to @@ -527,19 +520,25 @@ moveHist fn = do result_fs :: FastString result_fs = fsLit "_result" +-- | Read the 'ModBreaks' of the given home 'Module' from the 'HomeUnitGraph'. +readModBreaks :: HscEnv -> Module -> IO ModBreaks +readModBreaks hsc_env mod = + getModBreaks . expectJust <$> + HUG.lookupHugByModule mod (hsc_HUG hsc_env) + bindLocalsAtBreakpoint :: HscEnv -> ForeignHValue + -> SrcSpan -> Maybe InternalBreakpointId - -> IO (HscEnv, [Name], SrcSpan, String) + -> IO (HscEnv, [Name]) -- Nothing case: we stopped when an exception was raised, not at a -- breakpoint. We have no location information or local variables to -- bind, all we can do is bind a local variable to the exception -- value. -bindLocalsAtBreakpoint hsc_env apStack Nothing = do +bindLocalsAtBreakpoint hsc_env apStack span Nothing = do let exn_occ = mkVarOccFS (fsLit "_exception") - span = mkGeneralSrcSpan (fsLit "<unknown>") exn_name <- newInteractiveBinder hsc_env exn_occ span let e_fs = fsLit "e" @@ -552,32 +551,21 @@ bindLocalsAtBreakpoint hsc_env apStack Nothing = do interp = hscInterp hsc_env -- Loader.extendLoadedEnv interp [(exn_name, apStack)] - return (hsc_env{ hsc_IC = ictxt1 }, [exn_name], span, "<exception thrown>") + return (hsc_env{ hsc_IC = ictxt1 }, [exn_name]) -- Just case: we stopped at a breakpoint, we have information about the location -- of the breakpoint and the free variables of the expression. -bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do - let - interp = hscInterp hsc_env - - info_mod = ibi_info_mod ibi - info_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName info_mod) - let - info_brks = getModBreaks info_hmi - info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) - - tick_mod = ibi_tick_mod ibi - tick_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName tick_mod) - let - tick_brks = getModBreaks tick_hmi - occs = modBreaks_vars tick_brks ! ibi_tick_index ibi - span = modBreaks_locs tick_brks ! ibi_tick_index ibi - decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi +bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do + info_brks <- readModBreaks hsc_env (ibi_info_mod ibi) + tick_brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + let info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) + interp = hscInterp hsc_env + occs = modBreaks_vars tick_brks ! ibi_tick_index ibi -- Rehydrate to understand the breakpoint info relative to the current environment. -- This design is critical to preventing leaks (#22530) (mbVars, result_ty) <- initIfaceLoad hsc_env - $ initIfaceLcl info_mod (text "debugger") NotBoot + $ initIfaceLcl (ibi_info_mod ibi) (text "debugger") NotBoot $ hydrateCgBreakInfo info let @@ -624,7 +612,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do Loader.extendLoadedEnv interp (zip names fhvs) when result_ok $ Loader.extendLoadedEnv interp [(result_name, apStack_fhv)] hsc_env1 <- rttiEnvironment hsc_env{ hsc_IC = ictxt1 } - return (hsc_env1, if result_ok then result_name:names else names, span, decl) + return (hsc_env1, if result_ok then result_name:names else names) where -- We need a fresh Unique for each Id we bind, because the linker -- state is single-threaded and otherwise we'd spam old bindings ===================================== compiler/GHC/Runtime/Eval/Types.hs ===================================== @@ -9,7 +9,8 @@ module GHC.Runtime.Eval.Types ( Resume(..), ResumeBindings, IcGlobalRdrEnv(..), History(..), ExecResult(..), - SingleStep(..), isStep, ExecOptions(..) + SingleStep(..), enableGhcStepMode, breakHere, + ExecOptions(..) ) where import GHC.Prelude @@ -35,21 +36,59 @@ data ExecOptions , execWrap :: ForeignHValue -> EvalExpr ForeignHValue } +-- | What kind of stepping are we doing? data SingleStep = RunToCompletion - | SingleStep + + -- | :trace [expr] | RunAndLogSteps -isStep :: SingleStep -> Bool -isStep RunToCompletion = False -isStep _ = True + -- | :step [expr] + | SingleStep + + -- | :steplocal [expr] + | LocalStep + { breakAt :: SrcSpan } + + -- | :stepmodule [expr] + | ModuleStep + { breakAt :: SrcSpan } + +-- | Whether this 'SingleStep' mode requires instructing the interpreter to +-- step at every breakpoint. +enableGhcStepMode :: SingleStep -> Bool +enableGhcStepMode RunToCompletion = False +enableGhcStepMode _ = True + +-- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return +-- @True@ if based on the step-mode alone we should stop at this breakpoint. +-- +-- In particular, this will always be @False@ for @'RunToCompletion'@ and +-- @'RunAndLogSteps'@. We'd need further information e.g. about the user +-- breakpoints to determine whether to break in those modes. +breakHere :: SingleStep -> SrcSpan -> Bool +breakHere step break_span = case step of + RunToCompletion -> False + RunAndLogSteps -> False + SingleStep -> True + LocalStep span -> break_span `isSubspanOf` span + ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span data ExecResult + + -- | Execution is complete = ExecComplete { execResult :: Either SomeException [Name] , execAllocation :: Word64 } - | ExecBreak + + -- | Execution stopped at a breakpoint. + -- + -- Note: `ExecBreak` is only returned by `handleRunStatus` when GHCi should + -- definitely stop at this breakpoint. GHCi is /not/ responsible for + -- subsequently deciding whether to really stop here. + -- `ExecBreak` always means GHCi breaks. + | ExecBreak { breakNames :: [Name] , breakPointId :: Maybe InternalBreakpointId } ===================================== ghc/GHCi/UI.hs ===================================== @@ -1310,7 +1310,7 @@ runStmt input step = do m_result <- GhciMonad.runStmt stmt input step case m_result of Nothing -> return Nothing - Just result -> Just <$> afterRunStmt (const True) result + Just result -> Just <$> afterRunStmt step result -- `x = y` (a declaration) should be treated as `let x = y` (a statement). -- The reason is because GHCi wasn't designed to support `x = y`, but then @@ -1342,7 +1342,7 @@ runStmt input step = do _ <- liftIO $ tryIO $ hFlushAll stdin m_result <- GhciMonad.runDecls' decls forM m_result $ \result -> - afterRunStmt (const True) (GHC.ExecComplete (Right result) 0) + afterRunStmt step (GHC.ExecComplete (Right result) 0) mk_stmt :: SrcSpan -> HsBind GhcPs -> GhciLStmt GhcPs mk_stmt loc bind = @@ -1359,9 +1359,9 @@ runStmt input step = do modStr = moduleNameString $ moduleName $ icInteractiveModule $ ic -- | Clean up the GHCi environment after a statement has run -afterRunStmt :: GhciMonad m - => (SrcSpan -> Bool) -> GHC.ExecResult -> m GHC.ExecResult -afterRunStmt step_here run_result = do +afterRunStmt :: GhciMonad m => SingleStep {-^ Type of step we took just before -} + -> GHC.ExecResult -> m GHC.ExecResult +afterRunStmt step run_result = do resumes <- GHC.getResumeContext case run_result of GHC.ExecComplete{..} -> @@ -1372,9 +1372,7 @@ afterRunStmt step_here run_result = do when show_types $ printTypeOfNames names GHC.ExecBreak names mb_info | first_resume : _ <- resumes - , isNothing mb_info || - step_here (GHC.resumeSpan first_resume) -> do - mb_id_loc <- toBreakIdAndLocation mb_info + -> do mb_id_loc <- toBreakIdAndLocation mb_info let bCmd = maybe "" ( \(_,l) -> onBreakCmd l ) mb_id_loc if (null bCmd) then printStoppedAtBreakInfo first_resume names @@ -1383,8 +1381,9 @@ afterRunStmt step_here run_result = do st <- getGHCiState enqueueCommands [stop st] return () - | otherwise -> resume step_here GHC.SingleStep Nothing >>= - afterRunStmt step_here >> return () + + | otherwise -> resume step Nothing >>= + afterRunStmt step >> return () flushInterpBuffers withSignalHandlers $ do @@ -3810,7 +3809,7 @@ forceCmd = pprintClosureCommand False True stepCmd :: GhciMonad m => String -> m () stepCmd arg = withSandboxOnly ":step" $ step arg where - step [] = doContinue (const True) GHC.SingleStep + step [] = doContinue GHC.SingleStep step expression = runStmt expression GHC.SingleStep >> return () stepLocalCmd :: GhciMonad m => String -> m () @@ -3829,7 +3828,7 @@ stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg Just loc -> do md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule current_toplevel_decl <- enclosingTickSpan md loc - doContinue (`isSubspanOf` RealSrcSpan current_toplevel_decl Strict.Nothing) GHC.SingleStep + doContinue (GHC.LocalStep (RealSrcSpan current_toplevel_decl Strict.Nothing)) stepModuleCmd :: GhciMonad m => String -> m () stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg @@ -3840,9 +3839,7 @@ stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg mb_span <- getCurrentBreakSpan case mb_span of Nothing -> stepCmd [] - Just pan -> do - let f some_span = srcSpanFileName_maybe pan == srcSpanFileName_maybe some_span - doContinue f GHC.SingleStep + Just pan -> doContinue (GHC.ModuleStep pan) -- | Returns the span of the largest tick containing the srcspan given enclosingTickSpan :: GhciMonad m => Module -> SrcSpan -> m RealSrcSpan @@ -3863,14 +3860,14 @@ traceCmd :: GhciMonad m => String -> m () traceCmd arg = withSandboxOnly ":trace" $ tr arg where - tr [] = doContinue (const True) GHC.RunAndLogSteps + tr [] = doContinue GHC.RunAndLogSteps tr expression = runStmt expression GHC.RunAndLogSteps >> return () continueCmd :: GhciMonad m => String -> m () -- #19157 continueCmd argLine = withSandboxOnly ":continue" $ case contSwitch (words argLine) of Left sdoc -> printForUser sdoc - Right mbCnt -> doContinue' (const True) GHC.RunToCompletion mbCnt + Right mbCnt -> doContinue' GHC.RunToCompletion mbCnt where contSwitch :: [String] -> Either SDoc (Maybe Int) contSwitch [ ] = Right Nothing @@ -3878,13 +3875,13 @@ continueCmd argLine = withSandboxOnly ":continue" $ contSwitch _ = Left $ text "After ':continue' only one ignore count is allowed" -doContinue :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> m () -doContinue pre step = doContinue' pre step Nothing +doContinue :: GhciMonad m => SingleStep -> m () +doContinue step = doContinue' step Nothing -doContinue' :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m () -doContinue' pre step mbCnt= do - runResult <- resume pre step mbCnt - _ <- afterRunStmt pre runResult +doContinue' :: GhciMonad m => SingleStep -> Maybe Int -> m () +doContinue' step mbCnt= do + runResult <- resume step mbCnt + _ <- afterRunStmt step runResult return () abandonCmd :: GhciMonad m => String -> m () @@ -4036,7 +4033,7 @@ backCmd arg | otherwise = liftIO $ putStrLn "Syntax: :back [num]" where back num = withSandboxOnly ":back" $ do - (names, _, pan, _) <- GHC.back num + (names, _, pan) <- GHC.back num printForUser $ text "Logged breakpoint at" <+> ppr pan printTypeOfNames names -- run the command set with ":set stop <cmd>" @@ -4050,7 +4047,7 @@ forwardCmd arg | otherwise = liftIO $ putStrLn "Syntax: :forward [num]" where forward num = withSandboxOnly ":forward" $ do - (names, ix, pan, _) <- GHC.forward num + (names, ix, pan) <- GHC.forward num printForUser $ (if (ix == 0) then text "Stopped at" else text "Logged breakpoint at") <+> ppr pan ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -401,14 +401,14 @@ runDecls' decls = do return Nothing) (Just <$> GHC.runParsedDecls decls) -resume :: GhciMonad m => (SrcSpan -> Bool) -> GHC.SingleStep -> Maybe Int -> m GHC.ExecResult -resume canLogSpan step mbIgnoreCnt = do +resume :: GhciMonad m => GHC.SingleStep -> Maybe Int -> m GHC.ExecResult +resume step mbIgnoreCnt = do st <- getGHCiState reifyGHCi $ \x -> withProgName (progname st) $ withArgs (args st) $ reflectGHCi x $ do - GHC.resumeExec canLogSpan step mbIgnoreCnt + GHC.resumeExec step mbIgnoreCnt -- -------------------------------------------------------------------------- -- timing & statistics View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3b78e139033ab07232313888cc503712799fa76c...73ba1e6ec811c19baaf77abc72ba886a80fef5b4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3b78e139033ab07232313888cc503712799fa76c...73ba1e6ec811c19baaf77abc72ba886a80fef5b4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/a7fab15a/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 20:29:20 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 03 Mar 2025 15:29:20 -0500 Subject: [Git][ghc/ghc][wip/az/sync-ghc-exactprint] Apply 1 suggestion(s) to 1 file(s) Message-ID: <67c61120343f5_2c674b6cf804622fd@gitlab.mail> Alan Zimmerman pushed to branch wip/az/sync-ghc-exactprint at Glasgow Haskell Compiler / GHC Commits: 531b275c by Alan Zimmerman at 2025-03-03T20:29:16+00:00 Apply 1 suggestion(s) to 1 file(s) Co-authored-by: Brandon S. Allbery <allbery.b at gmail.com> - - - - - 1 changed file: - utils/check-exact/Transform.hs Changes: ===================================== utils/check-exact/Transform.hs ===================================== @@ -260,7 +260,7 @@ setEntryDP (L (EpAnn (EpaDelta ss d csd) an cs) a) dp where -- I suspect we should assume the comments are already in the -- right place, and just set the entry DP for this case. This - -- avoids suprises from the caller. + -- avoids surprises from the caller. (d', csd', cs') = case cs of EpaComments (h:t) -> let View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/531b275c8b980b03fe7f2085aa3eae694a840741 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/531b275c8b980b03fe7f2085aa3eae694a840741 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/1d9b4814/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 3 20:58:55 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 03 Mar 2025 15:58:55 -0500 Subject: [Git][ghc/ghc][wip/wasm-jsffi-sync-export] 9 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67c6180ecd946_2c674bdbc5a46455f@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-sync-export at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - 18 changed files: - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Tc/Gen/Foreign.hs - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/include/RtsAPI.h - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs Changes: ===================================== compiler/GHC/HsToCore/Foreign/C.hs ===================================== @@ -515,8 +515,7 @@ mkFExportCBits dflags c_nm maybe_target arg_htys res_hty is_IO_res_ty cc , text "rts_inCall" <> parens ( char '&' <> cap <> text "rts_apply" <> parens ( - cap <> - text "(HaskellObj)" + cap <> (if is_IO_res_ty then text "runIO_closure" else text "runNonIO_closure") ===================================== compiler/GHC/HsToCore/Foreign/Wasm.hs ===================================== @@ -11,6 +11,7 @@ import Data.List ( intercalate, stripPrefix, ) +import Data.List qualified import Data.Maybe import GHC.Builtin.Names import GHC.Builtin.Types @@ -46,6 +47,9 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import Language.Haskell.Syntax.Basic +data Synchronicity = Sync | Async + deriving (Eq) + dsWasmJSImport :: Id -> Coercion -> @@ -53,10 +57,15 @@ dsWasmJSImport :: Safety -> DsM ([Binding], CHeader, CStub, [Id]) dsWasmJSImport id co (CFunction (StaticTarget _ js_src mUnitId _)) safety - | js_src == "wrapper" = dsWasmJSDynamicExport id co mUnitId + | js_src == "wrapper" = dsWasmJSDynamicExport Async id co mUnitId + | js_src == "wrapper sync" = dsWasmJSDynamicExport Sync id co mUnitId | otherwise = do - (bs, h, c) <- dsWasmJSStaticImport id co (unpackFS js_src) mUnitId safety + (bs, h, c) <- dsWasmJSStaticImport id co (unpackFS js_src) mUnitId sync pure (bs, h, c, []) + where + sync = case safety of + PlayRisky -> Sync + _ -> Async dsWasmJSImport _ _ _ _ = panic "dsWasmJSImport: unreachable" {- @@ -77,17 +86,24 @@ We desugar it to three bindings under the hood: mk_wrapper_worker :: StablePtr HsFuncType -> HsFuncType mk_wrapper_worker sp = unsafeDupablePerformIO (deRefStablePtr sp) -No need to bother with eta-expansion here. Also, the worker function -is marked as a JSFFI static export. +The worker function is marked as a JSFFI static export. It turns a +dynamic export to a static one by prepending a StablePtr to the +argument list. + +We don't actually generate a Core binding for the worker function +though; the JSFFI static export C stub generation logic would just +generate a function that doesn't need to refer to the worker Id's +closure. This is not just for convenience, it's actually required for +correctness, see #25473. 2. The adjustor function foreign import javascript unsafe "(...args) => __exports.mk_wrapper_worker($1, ...args)" mk_wrapper_adjustor :: StablePtr HsFuncType -> IO JSVal -It generates a JavaScript callback that captures the stable pointer. -When the callback is invoked later, it calls our worker function and -passes the stable pointer as well as the rest of the arguments. +Now that mk_wrapper_worker is exported in __exports, we need to make a +JavaScript callback that invokes mk_wrapper_worker with the right +StablePtr as well as the rest of the arguments. 3. The wrapper function @@ -102,43 +118,47 @@ a StablePtr# field which is NULL by default, but for JSFFI dynamic exports, it's set to the Haskell function's stable pointer. This way, when we call freeJSVal, the Haskell function can be freed as well. +By default, JSFFI exports are async JavaScript functions. One can use +"wrapper sync" instead of "wrapper" to indicate the Haskell function +is meant to be exported as a sync JavaScript function. All the +comments above still hold, with only only difference: +mk_wrapper_worker is exported as a sync function. See +Note [Desugaring JSFFI static export] for further details. + -} dsWasmJSDynamicExport :: - Id -> Coercion -> Maybe Unit -> DsM ([Binding], CHeader, CStub, [Id]) -dsWasmJSDynamicExport fn_id co mUnitId = do + Synchronicity -> + Id -> + Coercion -> + Maybe Unit -> + DsM ([Binding], CHeader, CStub, [Id]) +dsWasmJSDynamicExport sync fn_id co mUnitId = do sp_tycon <- dsLookupTyCon stablePtrTyConName let ty = coercionLKind co (tv_bndrs, fun_ty) = tcSplitForAllTyVarBinders ty ([Scaled ManyTy arg_ty], io_jsval_ty) = tcSplitFunTys fun_ty sp_ty = mkTyConApp sp_tycon [arg_ty] - (real_arg_tys, _) = tcSplitFunTys arg_ty sp_id <- newSysLocalMDs sp_ty - work_uniq <- newUnique - work_export_name <- uniqueCFunName - deRefStablePtr_id <- lookupGhcInternalVarId "GHC.Internal.Stable" "deRefStablePtr" + work_export_name <- unpackFS <$> uniqueCFunName + deRefStablePtr_id <- + lookupGhcInternalVarId + "GHC.Internal.Stable" + "deRefStablePtr" unsafeDupablePerformIO_id <- lookupGhcInternalVarId "GHC.Internal.IO.Unsafe" "unsafeDupablePerformIO" - let work_id = - mkExportedVanillaId - ( mkExternalName - work_uniq - (nameModule $ getName fn_id) - (mkVarOcc $ "jsffi_" ++ occNameString (getOccName fn_id) ++ "_work") - generatedSrcSpan - ) - work_ty - work_rhs = + let work_rhs = mkCoreLams ([tv | Bndr tv _ <- tv_bndrs] ++ [sp_id]) $ mkApps (Var unsafeDupablePerformIO_id) [Type arg_ty, mkApps (Var deRefStablePtr_id) [Type arg_ty, Var sp_id]] work_ty = exprType work_rhs (work_h, work_c, _, work_ids, work_bs) <- - dsWasmJSExport - work_id + dsWasmJSExport' + sync + Nothing (mkRepReflCo work_ty) work_export_name adjustor_uniq <- newUnique @@ -157,21 +177,18 @@ dsWasmJSDynamicExport fn_id co mUnitId = do adjustor_ty adjustor_ty = mkForAllTys tv_bndrs $ mkVisFunTysMany [sp_ty] io_jsval_ty adjustor_js_src = - "(" - ++ intercalate "," ["a" ++ show i | i <- [1 .. length real_arg_tys]] - ++ ") => __exports." - ++ unpackFS work_export_name - ++ "($1" - ++ mconcat [",a" ++ show i | i <- [1 .. length real_arg_tys]] - ++ ")" + "(...args) => __exports." ++ work_export_name ++ "($1, ...args)" (adjustor_bs, adjustor_h, adjustor_c) <- dsWasmJSStaticImport adjustor_id (mkRepReflCo adjustor_ty) adjustor_js_src mUnitId - PlayRisky - mkJSCallback_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "mkJSCallback" + Sync + mkJSCallback_id <- + lookupGhcInternalVarId + "GHC.Internal.Wasm.Prim.Exports" + "mkJSCallback" let wrap_rhs = mkCoreLams [tv | Bndr tv _ <- tv_bndrs] $ mkApps @@ -182,7 +199,7 @@ dsWasmJSDynamicExport fn_id co mUnitId = do [Type $ mkTyVarTy tv | Bndr tv _ <- tv_bndrs] ] pure - ( [(fn_id, Cast wrap_rhs co), (work_id, work_rhs)] ++ work_bs ++ adjustor_bs, + ( [(fn_id, Cast wrap_rhs co)] ++ work_bs ++ adjustor_bs, work_h `mappend` adjustor_h, work_c `mappend` adjustor_c, work_ids @@ -194,7 +211,7 @@ Note [Desugaring JSFFI import] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The simplest case is JSFFI sync import, those marked as unsafe. It is -implemented on top of C FFI unsafe import. +implemented on top of C FFI safe import. Unlike C FFI which generates a worker/wrapper pair that unboxes the arguments and boxes the result in Haskell, we only desugar to a single @@ -202,10 +219,11 @@ Haskell binding that case-binds the arguments to ensure they're evaluated, then passes the boxed arguments directly to C and receive the boxed result from C as well. -This is of course less efficient than how C FFI does it, and unboxed -FFI types aren't supported, but it's the easiest way to implement it, +This is slightly less efficient than how C FFI does it, and unboxed +FFI types aren't supported, but it's the simplest way to implement it, especially since leaving all the boxing/unboxing business to C unifies -the implementation of JSFFI imports and exports. +the implementation of JSFFI imports and exports +(rts_mkJSVal/rts_getJSVal). Now, each sync import calls a generated C function with a unique symbol. The C function uses rts_get* to unbox the arguments, call into @@ -240,6 +258,14 @@ module. Note that above is assembly source file, but we're only generating a C stub, so we need to smuggle the assembly code into C via __asm__. +The C FFI import that calls the generated C function is always marked +as safe. There is some extra overhead, but this allows re-entrance by +Haskell -> JavaScript -> Haskell function calls with each call being a +synchronous one. It's possible to steal the "interruptible" keyword to +indicate async imports, "safe" for sync imports and "unsafe" for sync +imports sans the safe C FFI overhead, but it's simply not worth the +extra complexity. + JSFFI async import is implemented on top of JSFFI sync import. We still desugar it to a single Haskell binding that calls C, with some subtle differences: @@ -250,12 +276,6 @@ subtle differences: "($1, $2)". As you can see, it is the arrow function binder, and the post-linker will respect the async binder and allow await in the function body. -- The C import is also marked as safe. This is required since the - JavaScript code may re-enter Haskell. If re-entrance only happens in - future event loop tasks, it's fine to mark the C import as unsafe - since the current Haskell execution context has already been freed - at that point, but there's no such guarantee, so better safe than - sorry here. Now we have the Promise JSVal, we apply stg_blockPromise to it to get a thunk with the desired return type. When the thunk is forced, it @@ -270,9 +290,9 @@ dsWasmJSStaticImport :: Coercion -> String -> Maybe Unit -> - Safety -> + Synchronicity -> DsM ([Binding], CHeader, CStub) -dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do +dsWasmJSStaticImport fn_id co js_src' mUnitId sync = do cfun_name <- uniqueCFunName let ty = coercionLKind co (tvs, fun_ty) = tcSplitForAllInvisTyVars ty @@ -289,36 +309,31 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do ++ ")" | otherwise = js_src' - case safety of - PlayRisky -> do - rhs <- - importBindingRHS - mUnitId - PlayRisky - cfun_name - tvs - arg_tys - orig_res_ty - id + case sync of + Sync -> do + rhs <- importBindingRHS mUnitId cfun_name tvs arg_tys orig_res_ty id pure ( [(fn_id, Cast rhs co)], CHeader commonCDecls, - importCStub - PlayRisky - cfun_name - (map scaledThing arg_tys) - res_ty - js_src + importCStub Sync cfun_name (map scaledThing arg_tys) res_ty js_src ) - _ -> do + Async -> do + err_msg <- mkStringExpr $ js_src io_tycon <- dsLookupTyCon ioTyConName - jsval_ty <- mkTyConTy <$> lookupGhcInternalTyCon "GHC.Internal.Wasm.Prim.Types" "JSVal" + jsval_ty <- + mkTyConTy + <$> lookupGhcInternalTyCon "GHC.Internal.Wasm.Prim.Types" "JSVal" bindIO_id <- dsLookupGlobalId bindIOName returnIO_id <- dsLookupGlobalId returnIOName promise_id <- newSysLocalMDs jsval_ty - blockPromise_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" "stg_blockPromise" + blockPromise_id <- + lookupGhcInternalVarId + "GHC.Internal.Wasm.Prim.Imports" + "stg_blockPromise" msgPromise_id <- - lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" $ "stg_messagePromise" ++ ffiType res_ty + lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" + $ "stg_messagePromise" + ++ ffiType res_ty unsafeDupablePerformIO_id <- lookupGhcInternalVarId "GHC.Internal.IO.Unsafe" @@ -326,7 +341,6 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do rhs <- importBindingRHS mUnitId - PlaySafe cfun_name tvs arg_tys @@ -350,19 +364,14 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do [ Type res_ty, mkApps (Var blockPromise_id) - [Type res_ty, Var promise_id, Var msgPromise_id] + [Type res_ty, err_msg, Var promise_id, Var msgPromise_id] ] ] ) pure ( [(fn_id, Cast rhs co)], CHeader commonCDecls, - importCStub - PlaySafe - cfun_name - (map scaledThing arg_tys) - jsval_ty - js_src + importCStub Async cfun_name (map scaledThing arg_tys) jsval_ty js_src ) uniqueCFunName :: DsM FastString @@ -372,92 +381,91 @@ uniqueCFunName = do importBindingRHS :: Maybe Unit -> - Safety -> FastString -> [TyVar] -> [Scaled Type] -> Type -> (CoreExpr -> CoreExpr) -> DsM CoreExpr -importBindingRHS mUnitId safety cfun_name tvs arg_tys orig_res_ty res_trans = - do - ccall_uniq <- newUnique - args_unevaled <- newSysLocalsDs arg_tys - args_evaled <- newSysLocalsDs arg_tys - -- ccall_action_ty: type of the_call, State# RealWorld -> (# State# RealWorld, a #) - -- res_wrapper: turn the_call to (IO a) or a - (ccall_action_ty, res_wrapper) <- case tcSplitIOType_maybe orig_res_ty of - Just (io_tycon, res_ty) -> do - s0_id <- newSysLocalMDs realWorldStatePrimTy - s1_id <- newSysLocalMDs realWorldStatePrimTy - let io_data_con = tyConSingleDataCon io_tycon - toIOCon = dataConWorkId io_data_con - (ccall_res_ty, wrap) - | res_ty `eqType` unitTy = - ( mkTupleTy Unboxed [realWorldStatePrimTy], - \the_call -> - mkApps - (Var toIOCon) - [ Type res_ty, - Lam s0_id - $ mkWildCase - (App the_call (Var s0_id)) - (unrestricted ccall_res_ty) - (mkTupleTy Unboxed [realWorldStatePrimTy, unitTy]) - [ Alt - (DataAlt (tupleDataCon Unboxed 1)) - [s1_id] - (mkCoreUnboxedTuple [Var s1_id, unitExpr]) - ] - ] - ) - | otherwise = - ( mkTupleTy Unboxed [realWorldStatePrimTy, res_ty], - \the_call -> mkApps (Var toIOCon) [Type res_ty, the_call] - ) - pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) - Nothing -> do - unsafeDupablePerformIO_id <- - lookupGhcInternalVarId - "GHC.Internal.IO.Unsafe" - "unsafeDupablePerformIO" - io_data_con <- dsLookupDataCon ioDataConName - let ccall_res_ty = - mkTupleTy Unboxed [realWorldStatePrimTy, orig_res_ty] - toIOCon = dataConWorkId io_data_con - wrap the_call = - mkApps - (Var unsafeDupablePerformIO_id) - [ Type orig_res_ty, - mkApps (Var toIOCon) [Type orig_res_ty, the_call] - ] - pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) - let cfun_fcall = - CCall - ( CCallSpec - (StaticTarget NoSourceText cfun_name mUnitId True) - CCallConv - safety - ) - call_app = - mkFCall ccall_uniq cfun_fcall (map Var args_evaled) ccall_action_ty - rhs = - mkCoreLams (tvs ++ args_unevaled) - $ foldr - (\(arg_u, arg_e) acc -> mkDefaultCase (Var arg_u) arg_e acc) - -- res_trans transforms the result. When desugaring - -- JSFFI sync imports, the result is just (IO a) or a, - -- and res_trans is id; for async cases, the result is - -- always (IO JSVal), and res_trans will wrap it in a - -- thunk that has the original return type. This way, we - -- can reuse most of the RHS generation logic for both - -- sync/async imports. - (res_trans $ res_wrapper call_app) - (zip args_unevaled args_evaled) - pure rhs - -importCStub :: Safety -> FastString -> [Type] -> Type -> String -> CStub -importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] +importBindingRHS mUnitId cfun_name tvs arg_tys orig_res_ty res_trans = do + ccall_uniq <- newUnique + args_unevaled <- newSysLocalsDs arg_tys + args_evaled <- newSysLocalsDs arg_tys + -- ccall_action_ty: type of the_call, State# RealWorld -> (# State# RealWorld, a #) + -- res_wrapper: turn the_call to (IO a) or a + (ccall_action_ty, res_wrapper) <- case tcSplitIOType_maybe orig_res_ty of + Just (io_tycon, res_ty) -> do + s0_id <- newSysLocalMDs realWorldStatePrimTy + s1_id <- newSysLocalMDs realWorldStatePrimTy + let io_data_con = tyConSingleDataCon io_tycon + toIOCon = dataConWorkId io_data_con + (ccall_res_ty, wrap) + | res_ty `eqType` unitTy = + ( mkTupleTy Unboxed [realWorldStatePrimTy], + \the_call -> + mkApps + (Var toIOCon) + [ Type res_ty, + Lam s0_id + $ mkWildCase + (App the_call (Var s0_id)) + (unrestricted ccall_res_ty) + (mkTupleTy Unboxed [realWorldStatePrimTy, unitTy]) + [ Alt + (DataAlt (tupleDataCon Unboxed 1)) + [s1_id] + (mkCoreUnboxedTuple [Var s1_id, unitExpr]) + ] + ] + ) + | otherwise = + ( mkTupleTy Unboxed [realWorldStatePrimTy, res_ty], + \the_call -> mkApps (Var toIOCon) [Type res_ty, the_call] + ) + pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) + Nothing -> do + unsafeDupablePerformIO_id <- + lookupGhcInternalVarId + "GHC.Internal.IO.Unsafe" + "unsafeDupablePerformIO" + io_data_con <- dsLookupDataCon ioDataConName + let ccall_res_ty = mkTupleTy Unboxed [realWorldStatePrimTy, orig_res_ty] + toIOCon = dataConWorkId io_data_con + wrap the_call = + mkApps + (Var unsafeDupablePerformIO_id) + [ Type orig_res_ty, + mkApps (Var toIOCon) [Type orig_res_ty, the_call] + ] + pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) + let cfun_fcall = + CCall + ( CCallSpec + (StaticTarget NoSourceText cfun_name mUnitId True) + CCallConv + -- Same even for foreign import javascript unsafe, for + -- the sake of re-entrancy. + PlaySafe + ) + call_app = + mkFCall ccall_uniq cfun_fcall (map Var args_evaled) ccall_action_ty + rhs = + mkCoreLams (tvs ++ args_unevaled) + $ foldr + (\(arg_u, arg_e) acc -> mkDefaultCase (Var arg_u) arg_e acc) + -- res_trans transforms the result. When desugaring + -- JSFFI sync imports, the result is just (IO a) or a, + -- and res_trans is id; for async cases, the result is + -- always (IO JSVal), and res_trans will wrap it in a + -- thunk that has the original return type. This way, we + -- can reuse most of the RHS generation logic for both + -- sync/async imports. + (res_trans $ res_wrapper call_app) + (zip args_unevaled args_evaled) + pure rhs + +importCStub :: Synchronicity -> FastString -> [Type] -> Type -> String -> CStub +importCStub sync cfun_name arg_tys res_ty js_src = CStub c_doc [] [] where import_name = fromJust $ stripPrefix "ghczuwasmzujsffi" (unpackFS cfun_name) import_asm = @@ -465,18 +473,18 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] <> parens ( vcat [ text (show l) - | l <- - [ ".section .custom_section.ghc_wasm_jsffi,\"\",@\n", - ".asciz \"" ++ import_name ++ "\"\n", - ".asciz \"" - ++ ( case safety of - PlayRisky -> "(" - _ -> "async (" - ) - ++ intercalate "," ["$" ++ show i | i <- [1 .. length arg_tys]] - ++ ")\"\n", - ".asciz " ++ show js_src ++ "\n" - ] + | l <- + [ ".section .custom_section.ghc_wasm_jsffi,\"\",@\n", + ".asciz \"" ++ import_name ++ "\"\n", + ".asciz \"" + ++ ( case sync of + Sync -> "(" + Async -> "async (" + ) + ++ intercalate "," ["$" ++ show i | i <- [1 .. length arg_tys]] + ++ ")\"\n", + ".asciz " ++ show js_src ++ "\n" + ] ] ) <> semi @@ -488,8 +496,8 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] ( punctuate comma [ text k <> parens (doubleQuotes (text v)) - | (k, v) <- - [("import_module", "ghc_wasm_jsffi"), ("import_name", import_name)] + | (k, v) <- + [("import_module", "ghc_wasm_jsffi"), ("import_name", import_name)] ] ) ) @@ -501,7 +509,7 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] | otherwise = text ("Hs" ++ ffiType res_ty) import_arg_list = [ text ("Hs" ++ ffiType arg_ty) <+> char 'a' <> int i - | (i, arg_ty) <- zip [1 ..] arg_tys + | (i, arg_ty) <- zip [1 ..] arg_tys ] import_args = case import_arg_list of [] -> text "void" @@ -528,7 +536,7 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] ( punctuate comma [ cfun_make_arg arg_ty (char 'a' <> int n) - | (arg_ty, n) <- zip arg_tys [1 ..] + | (arg_ty, n) <- zip arg_tys [1 ..] ] ) ) @@ -554,7 +562,8 @@ Note [Desugaring JSFFI static export] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A JSFFI static export wraps a top-level Haskell binding as a wasm -module export that can be called in JavaScript as an async function: +module export that can be called in JavaScript as an async/sync +function: foreign export javascript "plus" (+) :: Int -> Int -> Int @@ -565,32 +574,27 @@ stub for a JSFFI export as well: __attribute__((export_name("plus"))) HsJSVal plus(HsInt a1, HsInt a2) { ... } +The generated C stub function would be exported as __exports.plus and +can be called in JavaScript. By default, it's exported as an async +function, so the C stub would always return an HsJSVal which +represents the result Promise; in case of a sync export (using "plus +sync" instead of "plus"), it returns the original result type. + +The C stub function body applies the function closure to arguments, +wrap it with a runIO/runNonIO top handler function, then schedules +Haskell computation to happen, then fetches the result. In case of an +async export, the top handler creates a JavaScript Promise that stands +for Haskell evaluation result, and the Promise will eventually be +resolved with the result or rejected with an exception. That Promise +is what we return in the C stub function. See +Note [Async JSFFI scheduler] for detailed explanation. + At link time, you need to pass -optl-Wl,--export=plus,--export=... to specify your entrypoint function symbols as roots of wasm-ld link-time garbage collection. As for the auto-generated exports when desugaring the JSFFI dynamic exports, they will be transitively included as well due to the export_name attribute. -For each JSFFI static export, we create an internal worker function -which takes the same arguments as the exported Haskell binding, but -always returns (IO JSVal). Its RHS simply applies the arguments to the -original binding, then applies a runIO/runNonIO top handler function -to the result. The top handler creates a JavaScript Promise that -stands for Haskell evaluation result, schedules Haskell computation to -happen, and the Promise will eventually be resolved with the result or -rejected with an exception. That Promise is what we return in the C -stub function. See Note [Async JSFFI scheduler] for detailed -explanation. - -There's nothing else to explain about the C stub function body; just -like C FFI exports, it calls rts_mk* to box the arguments, rts_apply -to apply them to the worker function, evaluates the result, then -unboxes the resulting Promise using rts_getJSVal and returns it. - -Now, in JavaScript, once the wasm instance is initialized, you can -directly call these exports and await them, as if they're real -JavaScript async functions. - -} dsWasmJSExport :: @@ -598,108 +602,140 @@ dsWasmJSExport :: Coercion -> CLabelString -> DsM (CHeader, CStub, String, [Id], [Binding]) -dsWasmJSExport fn_id co ext_name = do - work_uniq <- newUnique +dsWasmJSExport fn_id co str = dsWasmJSExport' sync (Just fn_id) co ext_name + where + (sync, ext_name) = case words $ unpackFS str of + [ext_name] -> (Async, ext_name) + [ext_name, "sync"] -> (Sync, ext_name) + _ -> panic "dsWasmJSExport: unrecognized label string" + +dsWasmJSExport' :: + Synchronicity -> + Maybe Id -> + Coercion -> + String -> + DsM (CHeader, CStub, String, [Id], [Binding]) +dsWasmJSExport' sync m_fn_id co ext_name = do let ty = coercionRKind co - (tvs, fun_ty) = tcSplitForAllInvisTyVars ty + (_, fun_ty) = tcSplitForAllInvisTyVars ty (arg_tys, orig_res_ty) = tcSplitFunTys fun_ty (res_ty, is_io) = case tcSplitIOType_maybe orig_res_ty of Just (_, res_ty) -> (res_ty, True) Nothing -> (orig_res_ty, False) - (_, res_ty_args) = splitTyConApp res_ty res_ty_str = ffiType res_ty - args <- newSysLocalsDs arg_tys + top_handler_mod = case sync of + Sync -> "GHC.Internal.TopHandler" + Async -> "GHC.Internal.Wasm.Prim.Exports" + top_handler_name + | is_io = "runIO" + | otherwise = "runNonIO" + -- In case of sync export, we use the normal C FFI tophandler + -- functions. They would call flushStdHandles in case of uncaught + -- exception but not in normal cases, but we want flushStdHandles to + -- be called so that there are less run-time surprises for users, + -- and that's what our tophandler functions already do. + -- + -- So for each sync export, we first wrap the computation with a C + -- FFI tophandler, and then sequence it with flushStdHandles using + -- (<*) :: IO a -> IO b -> IO a. But it's trickier to call (<*) + -- using RTS API given type class dictionary is involved, so we'll + -- just use finally. + finally_id <- + lookupGhcInternalVarId + "GHC.Internal.Control.Exception.Base" + "finally" + flushStdHandles_id <- + lookupGhcInternalVarId + "GHC.Internal.TopHandler" + "flushStdHandles" promiseRes_id <- - lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" $ "js_promiseResolve" ++ res_ty_str - runIO_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "runIO" - runNonIO_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "runNonIO" - let work_id = - mkExportedVanillaId - ( mkExternalName - work_uniq - (nameModule $ getName fn_id) - (mkVarOcc $ "jsffi_" ++ occNameString (getOccName fn_id)) - generatedSrcSpan - ) - (exprType work_rhs) - work_rhs = - mkCoreLams (tvs ++ args) - $ mkApps - (Var $ if is_io then runIO_id else runNonIO_id) - [ Type res_ty, - mkApps (Var promiseRes_id) $ map Type res_ty_args, - mkApps (Cast (Var fn_id) co) - $ map (Type . mkTyVarTy) tvs - ++ map Var args - ] - work_closure = ppr work_id <> text "_closure" - work_closure_decl = text "extern StgClosure" <+> work_closure <> semi + lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" + $ "js_promiseResolve" + ++ res_ty_str + top_handler_id <- lookupGhcInternalVarId top_handler_mod top_handler_name + let ppr_closure c = ppr c <> text "_closure" + mk_extern_closure_decl c = + text "extern StgClosure" <+> ppr_closure c <> semi + gc_root_closures = maybeToList m_fn_id ++ case sync of + -- In case of C FFI top handlers, they are already declared in + -- RtsAPI.h and registered as GC roots in initBuiltinGcRoots. + -- flushStdHandles is already registered but somehow the C + -- stub can't access its declaration, won't hurt to declare it + -- again here. + Sync -> [finally_id, flushStdHandles_id] + Async -> [top_handler_id, promiseRes_id] + extern_closure_decls = vcat $ map mk_extern_closure_decl gc_root_closures cstub_attr = text "__attribute__" <> parens - (parens $ text "export_name" <> parens (doubleQuotes $ ftext ext_name)) + (parens $ text "export_name" <> parens (doubleQuotes $ text ext_name)) cstub_arg_list = [ text ("Hs" ++ ffiType (scaledThing arg_ty)) <+> char 'a' <> int i - | (i, arg_ty) <- zip [1 ..] arg_tys + | (i, arg_ty) <- zip [1 ..] arg_tys ] cstub_args = case cstub_arg_list of [] -> text "void" _ -> hsep $ punctuate comma cstub_arg_list - cstub_proto = text "HsJSVal" <+> ftext ext_name <> parens cstub_args + cstub_proto + | Sync <- sync, + res_ty `eqType` unitTy = + text "void" <+> text ext_name <> parens cstub_args + | Sync <- sync = + text ("Hs" ++ res_ty_str) <+> text ext_name <> parens cstub_args + | Async <- sync = + text "HsJSVal" <+> text ext_name <> parens cstub_args + c_closure c = char '&' <> ppr_closure c + c_call fn args = text fn <> parens (hsep $ punctuate comma args) + c_rts_apply = + Data.List.foldl1' $ \fn arg -> c_call "rts_apply" [text "cap", fn, arg] + apply_top_handler expr = case sync of + Sync -> + c_rts_apply + [ c_closure finally_id, + c_rts_apply [c_closure top_handler_id, expr], + c_closure flushStdHandles_id + ] + Async -> + c_rts_apply [c_closure top_handler_id, c_closure promiseRes_id, expr] + cstub_ret + | Sync <- sync, res_ty `eqType` unitTy = empty + | Sync <- sync = text $ "return rts_get" ++ res_ty_str ++ "(ret);" + | Async <- sync = text "return rts_getJSVal(ret);" + (cstub_target, real_args) + | Just fn_id <- m_fn_id = (c_closure fn_id, zip [1 ..] arg_tys) + | otherwise = (text "(HaskellObj)deRefStablePtr(a1)", zip [2 ..] $ tail arg_tys) cstub_body = vcat [ lbrace, text "Capability *cap = rts_lock();", text "HaskellObj ret;", - -- rts_evalLazyIO is fine, the top handler always returns - -- an evaluated result - text "rts_evalLazyIO" - <> parens - ( hsep - $ punctuate - comma - [ text "&cap", - foldl' - ( \acc (i, arg_ty) -> - text "rts_apply" - <> parens - ( hsep - $ punctuate - comma - [ text "cap", - acc, - text ("rts_mk" ++ ffiType (scaledThing arg_ty)) - <> parens - (hsep $ punctuate comma [text "cap", char 'a' <> int i]) - ] - ) - ) - (char '&' <> work_closure) - $ zip [1 ..] arg_tys, - text "&ret" - ] - ) + c_call + "rts_inCall" + [ text "&cap", + apply_top_handler + $ c_rts_apply + $ cstub_target + : [ c_call + ("rts_mk" ++ ffiType (scaledThing arg_ty)) + [text "cap", char 'a' <> int i] + | (i, arg_ty) <- real_args + ], + text "&ret" + ] <> semi, - text "rts_checkSchedStatus" - <> parens (doubleQuotes (ftext ext_name) <> comma <> text "cap") + c_call "rts_checkSchedStatus" [doubleQuotes (text ext_name), text "cap"] <> semi, text "rts_unlock(cap);", - text "return rts_getJSVal(ret);", + cstub_ret, rbrace ] cstub = commonCDecls - $+$ work_closure_decl + $+$ extern_closure_decls $+$ cstub_attr $+$ cstub_proto $+$ cstub_body - pure - ( CHeader commonCDecls, - CStub cstub [] [], - "", - [work_id], - [(work_id, work_rhs)] - ) + pure (CHeader commonCDecls, CStub cstub [] [], "", gc_root_closures, []) lookupGhcInternalVarId :: FastString -> String -> DsM Id lookupGhcInternalVarId m v = do ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -18,7 +18,7 @@ module GHC.Runtime.Eval ( abandon, abandonAll, getResumeContext, getHistorySpan, - getModBreaks, + getModBreaks, readModBreaks, getHistoryModule, setupBreakpoint, back, forward, @@ -130,14 +130,12 @@ import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) import GHC.IfaceToCore import Control.Monad -import Control.Monad.Catch as MC import Data.Array import Data.Dynamic import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.List (find,intercalate) import Data.List.NonEmpty (NonEmpty) -import System.Directory import Unsafe.Coerce ( unsafeCoerce ) import qualified GHC.Unit.Home.Graph as HUG @@ -156,9 +154,8 @@ getHistoryModule = ibi_tick_mod . historyBreakpointId getHistorySpan :: HscEnv -> History -> IO SrcSpan getHistorySpan hsc_env hist = do let ibi = historyBreakpointId hist - HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) >>= pure . \case - Just hmi -> modBreaks_locs (getModBreaks hmi) ! ibi_tick_index ibi - _ -> panic "getHistorySpan" + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi {- | Finds the enclosing top level function name -} -- ToDo: a better way to do this would be to keep hold of the decl_path computed @@ -166,9 +163,8 @@ getHistorySpan hsc_env hist = do -- for each tick. findEnclosingDecls :: HscEnv -> InternalBreakpointId -> IO [String] findEnclosingDecls hsc_env ibi = do - hmi <- expectJust <$> HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) - return $ - modBreaks_decls (getModBreaks hmi) ! ibi_tick_index ibi + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_decls brks ! ibi_tick_index ibi -- | Update fixity environment in the current interactive context. updateFixityEnv :: GhcMonad m => FixityEnv -> m () @@ -232,10 +228,9 @@ execStmt' stmt stmt_text ExecOptions{..} = do updateFixityEnv fix_env status <- - withVirtualCWD $ - liftIO $ do - let eval_opts = initEvalOpts idflags' (isStep execSingleStep) - evalStmt interp eval_opts (execWrap hval) + liftIO $ do + let eval_opts = initEvalOpts idflags' (enableGhcStepMode execSingleStep) + evalStmt interp eval_opts (execWrap hval) let ic = hsc_IC hsc_env bindings = (ic_tythings ic, ic_gre_cache ic) @@ -282,38 +277,17 @@ them. The relevant predicate is OccName.isDerivedOccName. See #11051 for more background and examples. -} -withVirtualCWD :: GhcMonad m => m a -> m a -withVirtualCWD m = do - hsc_env <- getSession - - -- a virtual CWD is only necessary when we're running interpreted code in - -- the same process as the compiler. - case interpInstance <$> hsc_interp hsc_env of - Just (ExternalInterp {}) -> m - _ -> do - let ic = hsc_IC hsc_env - let set_cwd = do - dir <- liftIO $ getCurrentDirectory - case ic_cwd ic of - Just dir -> liftIO $ setCurrentDirectory dir - Nothing -> return () - return dir - - reset_cwd orig_dir = do - virt_dir <- liftIO $ getCurrentDirectory - hsc_env <- getSession - let old_IC = hsc_IC hsc_env - setSession hsc_env{ hsc_IC = old_IC{ ic_cwd = Just virt_dir } } - liftIO $ setCurrentDirectory orig_dir - - MC.bracket set_cwd reset_cwd $ \_ -> m - parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) parseImportDecl expr = withSession $ \hsc_env -> liftIO $ hscImport hsc_env expr emptyHistory :: Int -> BoundedList History emptyHistory size = nilBL size +-- | Turn an 'EvalStatus_' result from interpreting Haskell into a GHCi 'ExecResult'. +-- +-- This function is responsible for resuming execution at an intermediate +-- breakpoint if we don't care about that breakpoint (e.g. if using :steplocal +-- or :stepmodule, rather than :step, we only care about certain breakpoints). handleRunStatus :: GhcMonad m => SingleStep -> String -> ResumeBindings @@ -322,92 +296,107 @@ handleRunStatus :: GhcMonad m -> BoundedList History -> m ExecResult -handleRunStatus step expr bindings final_ids status history0 - | RunAndLogSteps <- step = tracing - | otherwise = not_tracing - where - tracing - | EvalBreak apStack_ref (Just eval_break) resume_ctxt _ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - let dflags = hsc_dflags hsc_env - ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break - hmi <- liftIO $ expectJust <$> - lookupHpt (hsc_HPT hsc_env) (moduleName (ibi_tick_mod ibi)) - let breaks = getModBreaks hmi - - b <- liftIO $ - breakpointStatus interp (modBreaks_flags breaks) (ibi_tick_index ibi) - if b - then not_tracing - -- This breakpoint is explicitly enabled; we want to stop - -- instead of just logging it. - else do - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi - let !history' = history1 `consBL` history0 - -- history is strict, otherwise our BoundedList is pointless. - fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - let eval_opts = initEvalOpts dflags True - status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv - handleRunStatus RunAndLogSteps expr bindings final_ids - status history' - | otherwise - = not_tracing - - not_tracing - -- Hit a breakpoint - | EvalBreak apStack_ref maybe_break resume_ctxt ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - ibi <- case maybe_break of - Nothing -> pure Nothing - Just break -> fmap Just $ liftIO $ - evalBreakpointToId (hsc_HPT hsc_env) break - (hsc_env1, names, span, decl) <- liftIO $ - bindLocalsAtBreakpoint hsc_env apStack_fhv ibi - let - resume = Resume - { resumeStmt = expr - , resumeContext = resume_ctxt_fhv - , resumeBindings = bindings - , resumeFinalIds = final_ids - , resumeApStack = apStack_fhv - , resumeBreakpointId = ibi - , resumeSpan = span - , resumeHistory = toListBL history0 - , resumeDecl = decl - , resumeCCS = ccs - , resumeHistoryIx = 0 - } - hsc_env2 = pushResume hsc_env1 resume - - setSession hsc_env2 - return (ExecBreak names ibi) +handleRunStatus step expr bindings final_ids status history0 = do + hsc_env <- getSession + let + interp = hscInterp hsc_env + dflags = hsc_dflags hsc_env + case status of -- Completed successfully - | EvalComplete allocs (EvalSuccess hvals) <- status - = do hsc_env <- getSession - let final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids - final_names = map getName final_ids - interp = hscInterp hsc_env - liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) - hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} - setSession hsc_env' - return (ExecComplete (Right final_names) allocs) + EvalComplete allocs (EvalSuccess hvals) -> do + let + final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids + final_names = map getName final_ids + liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) + hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} + setSession hsc_env' + return (ExecComplete (Right final_names) allocs) -- Completed with an exception - | EvalComplete alloc (EvalException e) <- status - = return (ExecComplete (Left (fromSerializableException e)) alloc) - + EvalComplete alloc (EvalException e) -> + return (ExecComplete (Left (fromSerializableException e)) alloc) + + -- Nothing case: we stopped when an exception was raised, not at a breakpoint. + EvalBreak apStack_ref Nothing resume_ctxt ccs -> do + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + let span = mkGeneralSrcSpan (fsLit "<unknown>") + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span Nothing + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Nothing + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = "<exception thrown>" + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + + setSession hsc_env2 + return (ExecBreak names Nothing) + + -- Just case: we stopped at a breakpoint + EvalBreak apStack_ref (Just eval_break) resume_ctxt ccs -> do + ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break + tick_brks <- liftIO $ readModBreaks hsc_env (ibi_tick_mod ibi) + let + span = modBreaks_locs tick_brks ! ibi_tick_index ibi + decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi + + b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi) + + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + + -- This breakpoint is explicitly enabled; we want to stop + -- instead of just logging it. + if b || breakHere step span then do + -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break. + -- Specifically, for :steplocal or :stepmodule, don't return control + -- and simply resume execution from here until we hit a breakpoint we do want to stop at. + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Just ibi + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = decl + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + setSession hsc_env2 + return (ExecBreak names (Just ibi)) + else do + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) + status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv + history <- if not tracing then pure history0 else do + history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi + let !history' = history1 `consBL` history0 + -- history is strict, otherwise our BoundedList is pointless. + return history' + handleRunStatus step expr bindings final_ids status history + where + tracing | RunAndLogSteps <- step = True + | otherwise = False -resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> Maybe Int +resumeExec :: GhcMonad m => SingleStep -> Maybe Int -> m ExecResult -resumeExec canLogSpan step mbCnt +resumeExec step mbCnt = do hsc_env <- getSession let ic = hsc_IC hsc_env @@ -445,42 +434,41 @@ resumeExec canLogSpan step mbCnt , resumeBreakpointId = mb_brkpt , resumeSpan = span , resumeHistory = hist } -> - withVirtualCWD $ do + do -- When the user specified a break ignore count, set it -- in the interpreter case (mb_brkpt, mbCnt) of (Just brkpt, Just cnt) -> setupBreakpoint hsc_env (toBreakpointId brkpt) cnt _ -> return () - let eval_opts = initEvalOpts dflags (isStep step) + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv let prevHistoryLst = fromListBL 50 hist hist' = case mb_brkpt of Nothing -> pure prevHistoryLst Just bi - | not $ canLogSpan span -> pure prevHistoryLst - | otherwise -> do + | breakHere step span -> do hist1 <- liftIO (mkHistory hsc_env apStack bi) return $ hist1 `consBL` fromListBL 50 hist + | otherwise -> pure prevHistoryLst handleRunStatus step expr bindings final_ids status =<< hist' setupBreakpoint :: GhcMonad m => HscEnv -> BreakpointId -> Int -> m () -- #19157 setupBreakpoint hsc_env bi cnt = do let modl = bi_tick_mod bi - modBreaks <- getModBreaks . expectJust <$> - liftIO (lookupHpt (hsc_HPT hsc_env) (moduleName modl)) + modBreaks <- liftIO $ readModBreaks hsc_env modl let breakarray = modBreaks_flags modBreaks interp = hscInterp hsc_env _ <- liftIO $ GHCi.storeBreakpoint interp breakarray (bi_tick_index bi) cnt pure () -back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) back n = moveHist (+n) -forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) forward n = moveHist (subtract n) -moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan, String) +moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan) moveHist fn = do hsc_env <- getSession case ic_resume (hsc_IC hsc_env) of @@ -498,15 +486,20 @@ moveHist fn = do let update_ic apStack mb_info = do - (hsc_env1, names, span, decl) <- - liftIO $ bindLocalsAtBreakpoint hsc_env apStack mb_info + span <- case mb_info of + Nothing -> return $ mkGeneralSrcSpan (fsLit "<unknown>") + Just ibi -> liftIO $ do + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi + (hsc_env1, names) <- + liftIO $ bindLocalsAtBreakpoint hsc_env apStack span mb_info let ic = hsc_IC hsc_env1 r' = r { resumeHistoryIx = new_ix } ic' = ic { ic_resume = r':rs } setSession hsc_env1{ hsc_IC = ic' } - return (names, new_ix, span, decl) + return (names, new_ix, span) -- careful: we want apStack to be the AP_STACK itself, not a thunk -- around it, hence the cases are carefully constructed below to @@ -527,19 +520,25 @@ moveHist fn = do result_fs :: FastString result_fs = fsLit "_result" +-- | Read the 'ModBreaks' of the given home 'Module' from the 'HomeUnitGraph'. +readModBreaks :: HscEnv -> Module -> IO ModBreaks +readModBreaks hsc_env mod = + getModBreaks . expectJust <$> + HUG.lookupHugByModule mod (hsc_HUG hsc_env) + bindLocalsAtBreakpoint :: HscEnv -> ForeignHValue + -> SrcSpan -> Maybe InternalBreakpointId - -> IO (HscEnv, [Name], SrcSpan, String) + -> IO (HscEnv, [Name]) -- Nothing case: we stopped when an exception was raised, not at a -- breakpoint. We have no location information or local variables to -- bind, all we can do is bind a local variable to the exception -- value. -bindLocalsAtBreakpoint hsc_env apStack Nothing = do +bindLocalsAtBreakpoint hsc_env apStack span Nothing = do let exn_occ = mkVarOccFS (fsLit "_exception") - span = mkGeneralSrcSpan (fsLit "<unknown>") exn_name <- newInteractiveBinder hsc_env exn_occ span let e_fs = fsLit "e" @@ -552,32 +551,21 @@ bindLocalsAtBreakpoint hsc_env apStack Nothing = do interp = hscInterp hsc_env -- Loader.extendLoadedEnv interp [(exn_name, apStack)] - return (hsc_env{ hsc_IC = ictxt1 }, [exn_name], span, "<exception thrown>") + return (hsc_env{ hsc_IC = ictxt1 }, [exn_name]) -- Just case: we stopped at a breakpoint, we have information about the location -- of the breakpoint and the free variables of the expression. -bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do - let - interp = hscInterp hsc_env - - info_mod = ibi_info_mod ibi - info_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName info_mod) - let - info_brks = getModBreaks info_hmi - info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) - - tick_mod = ibi_tick_mod ibi - tick_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName tick_mod) - let - tick_brks = getModBreaks tick_hmi - occs = modBreaks_vars tick_brks ! ibi_tick_index ibi - span = modBreaks_locs tick_brks ! ibi_tick_index ibi - decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi +bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do + info_brks <- readModBreaks hsc_env (ibi_info_mod ibi) + tick_brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + let info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) + interp = hscInterp hsc_env + occs = modBreaks_vars tick_brks ! ibi_tick_index ibi -- Rehydrate to understand the breakpoint info relative to the current environment. -- This design is critical to preventing leaks (#22530) (mbVars, result_ty) <- initIfaceLoad hsc_env - $ initIfaceLcl info_mod (text "debugger") NotBoot + $ initIfaceLcl (ibi_info_mod ibi) (text "debugger") NotBoot $ hydrateCgBreakInfo info let @@ -624,7 +612,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do Loader.extendLoadedEnv interp (zip names fhvs) when result_ok $ Loader.extendLoadedEnv interp [(result_name, apStack_fhv)] hsc_env1 <- rttiEnvironment hsc_env{ hsc_IC = ictxt1 } - return (hsc_env1, if result_ok then result_name:names else names, span, decl) + return (hsc_env1, if result_ok then result_name:names else names) where -- We need a fresh Unique for each Id we bind, because the linker -- state is single-threaded and otherwise we'd spam old bindings ===================================== compiler/GHC/Runtime/Eval/Types.hs ===================================== @@ -9,7 +9,8 @@ module GHC.Runtime.Eval.Types ( Resume(..), ResumeBindings, IcGlobalRdrEnv(..), History(..), ExecResult(..), - SingleStep(..), isStep, ExecOptions(..) + SingleStep(..), enableGhcStepMode, breakHere, + ExecOptions(..) ) where import GHC.Prelude @@ -35,21 +36,59 @@ data ExecOptions , execWrap :: ForeignHValue -> EvalExpr ForeignHValue } +-- | What kind of stepping are we doing? data SingleStep = RunToCompletion - | SingleStep + + -- | :trace [expr] | RunAndLogSteps -isStep :: SingleStep -> Bool -isStep RunToCompletion = False -isStep _ = True + -- | :step [expr] + | SingleStep + + -- | :steplocal [expr] + | LocalStep + { breakAt :: SrcSpan } + + -- | :stepmodule [expr] + | ModuleStep + { breakAt :: SrcSpan } + +-- | Whether this 'SingleStep' mode requires instructing the interpreter to +-- step at every breakpoint. +enableGhcStepMode :: SingleStep -> Bool +enableGhcStepMode RunToCompletion = False +enableGhcStepMode _ = True + +-- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return +-- @True@ if based on the step-mode alone we should stop at this breakpoint. +-- +-- In particular, this will always be @False@ for @'RunToCompletion'@ and +-- @'RunAndLogSteps'@. We'd need further information e.g. about the user +-- breakpoints to determine whether to break in those modes. +breakHere :: SingleStep -> SrcSpan -> Bool +breakHere step break_span = case step of + RunToCompletion -> False + RunAndLogSteps -> False + SingleStep -> True + LocalStep span -> break_span `isSubspanOf` span + ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span data ExecResult + + -- | Execution is complete = ExecComplete { execResult :: Either SomeException [Name] , execAllocation :: Word64 } - | ExecBreak + + -- | Execution stopped at a breakpoint. + -- + -- Note: `ExecBreak` is only returned by `handleRunStatus` when GHCi should + -- definitely stop at this breakpoint. GHCi is /not/ responsible for + -- subsequently deciding whether to really stop here. + -- `ExecBreak` always means GHCi breaks. + | ExecBreak { breakNames :: [Name] , breakPointId :: Maybe InternalBreakpointId } ===================================== compiler/GHC/Tc/Gen/Foreign.hs ===================================== @@ -78,7 +78,7 @@ import GHC.Data.Bag import GHC.Driver.Hooks import qualified GHC.LanguageExtensions as LangExt -import Control.Monad ( zipWithM ) +import Control.Monad ( when, zipWithM ) import Control.Monad.Trans.Writer.CPS ( WriterT, runWriterT, tell ) import Control.Monad.Trans.Class @@ -444,7 +444,7 @@ tcFExport d = pprPanic "tcFExport" (ppr d) tcCheckFEType :: Type -> ForeignExport GhcRn -> TcM (ForeignExport GhcTc) tcCheckFEType sig_ty edecl@(CExport src (L l (CExportStatic esrc str cconv))) = do checkCg (Left edecl) backendValidityOfCExport - checkTc (isCLabelString str) (TcRnInvalidCIdentifier str) + when (cconv /= JavaScriptCallConv) $ checkTc (isCLabelString str) (TcRnInvalidCIdentifier str) cconv' <- checkCConv (Left edecl) cconv checkForeignArgs isFFIExternalTy arg_tys checkForeignRes nonIOok noCheckSafe isFFIExportResultTy res_ty ===================================== docs/users_guide/wasm.rst ===================================== @@ -231,15 +231,15 @@ There are two kinds of JSFFI imports: synchronous/asynchronous imports. ``unsafe`` indicates synchronous imports, which has the following caveats: -- The calling thread as well as the entire runtime blocks on waiting - for the import result. -- If the JavaScript code throws, the runtime crashes with the same - error. A JavaScript exception cannot be handled as a Haskell - exception here, so you need to use a JavaScript ``catch`` explicitly - shall the need arise. -- Like ``unsafe`` C imports, re-entrance is not supported, the imported - foreign code must not call into Haskell again. Doing so would result - in a runtime panic. +- The calling thread as well as the entire runtime blocks on waiting for + the import result. +- If the JavaScript code throws, the runtime crashes with the same + error. A JavaScript exception cannot be handled as a Haskell exception + here, so you need to use a JavaScript ``catch`` explicitly shall the + need arise. +- Unlike ``unsafe`` C imports, re-entrance is actually supported, the + imported JavaScript code can call into Haskell again, provided that + Haskell function is exported as a synchronous one. When a JSFFI import is marked as ``safe`` / ``interruptible`` or lacks safety annotation, then it’s treated as an asynchronous import. The @@ -274,14 +274,12 @@ runtime, and resumed when the ``Promise`` actually resolves or rejects. Compared to synchronous JSFFI imports, asynchronous JSFFI imports have the following notable pros/cons: -- Waiting for the result only blocks a single Haskell thread, other - threads can still make progress and garbage collection may still - happen. -- If the ``Promise`` rejects, Haskell code can catch JavaScript errors - as ``JSException``\ s. -- Re-entrance is supported. The JavaScript code may call into Haskell - again and vice versa. -- Of course, it has higher overhead than synchronous JSFFI imports. +- Waiting for the result only blocks a single Haskell thread, other + threads can still make progress and garbage collection may still + happen. +- If the ``Promise`` rejects, Haskell code can catch JavaScript errors + as ``JSException``\ s. +- It has higher overhead than synchronous JSFFI imports. Using thunks to encapsulate ``Promise`` result allows cheaper concurrency without even needing to fork Haskell threads just for @@ -345,12 +343,17 @@ wrapper, and as long as the wasm instance is properly initialized, you can call ``await instance.exports.my_fib(10)`` to invoke the exported Haskell function and get the result. -Unlike JSFFI imports which have synchronous/asynchronous flavors, JSFFI -exports are always asynchronous. Calling them always return a -``Promise`` in JavaScript that needs to be ``await``\ ed for the real -result. If the Haskell function throws, the ``Promise`` is rejected with -a ``WebAssembly.RuntimeError``, and the ``message`` field contains a -JavaScript string of the Haskell exception. +JSFFI exports are asynchronous by default. Calling an async export +return a ``Promise`` in JavaScript that needs to be ``await``\ ed for +the real result. If the Haskell function throws, the ``Promise`` is +rejected with a ``WebAssembly.RuntimeError``, and the ``message`` field +contains a JavaScript string of the Haskell exception. + +Additionally, sync exports are also supported by using ``"my_fib sync"`` +instead of ``"my_fib"``. With ``sync`` added alongside export function +name, the JavaScript function would return the result synchronously. For +the time being, sync exports don’t support propagating uncaught Haskell +exception to a JavaScript exception at the call site yet. Above is the static flavor of JSFFI exports. It’s also possible to export a dynamically created Haskell function closure as a JavaScript @@ -366,8 +369,9 @@ function and obtain its ``JSVal``: This is also much like ``foreign import ccall "wrapper"``, which wraps a Haskell function closure as a C function pointer. Note that ``unsafe`` / ``safe`` annotation is ignored here, since the ``JSVal`` that represent -the exported function is always returned synchronously, but it is always -an asynchronous JavaScript function, just like static JSFFI exports. +the exported function is always returned synchronously. Likewise, you +can use ``"wrapper sync"`` instead of ``"wrapper"`` to indicate the +returned JavaScript function is sync instead of async. The ``JSVal`` callbacks created by dynamic JSFFI exports can be passed to the rest of JavaScript world to be invoked later. But wait, didn’t we ===================================== ghc/GHCi/UI.hs ===================================== @@ -1310,7 +1310,7 @@ runStmt input step = do m_result <- GhciMonad.runStmt stmt input step case m_result of Nothing -> return Nothing - Just result -> Just <$> afterRunStmt (const True) result + Just result -> Just <$> afterRunStmt step result -- `x = y` (a declaration) should be treated as `let x = y` (a statement). -- The reason is because GHCi wasn't designed to support `x = y`, but then @@ -1342,7 +1342,7 @@ runStmt input step = do _ <- liftIO $ tryIO $ hFlushAll stdin m_result <- GhciMonad.runDecls' decls forM m_result $ \result -> - afterRunStmt (const True) (GHC.ExecComplete (Right result) 0) + afterRunStmt step (GHC.ExecComplete (Right result) 0) mk_stmt :: SrcSpan -> HsBind GhcPs -> GhciLStmt GhcPs mk_stmt loc bind = @@ -1359,9 +1359,9 @@ runStmt input step = do modStr = moduleNameString $ moduleName $ icInteractiveModule $ ic -- | Clean up the GHCi environment after a statement has run -afterRunStmt :: GhciMonad m - => (SrcSpan -> Bool) -> GHC.ExecResult -> m GHC.ExecResult -afterRunStmt step_here run_result = do +afterRunStmt :: GhciMonad m => SingleStep {-^ Type of step we took just before -} + -> GHC.ExecResult -> m GHC.ExecResult +afterRunStmt step run_result = do resumes <- GHC.getResumeContext case run_result of GHC.ExecComplete{..} -> @@ -1372,9 +1372,7 @@ afterRunStmt step_here run_result = do when show_types $ printTypeOfNames names GHC.ExecBreak names mb_info | first_resume : _ <- resumes - , isNothing mb_info || - step_here (GHC.resumeSpan first_resume) -> do - mb_id_loc <- toBreakIdAndLocation mb_info + -> do mb_id_loc <- toBreakIdAndLocation mb_info let bCmd = maybe "" ( \(_,l) -> onBreakCmd l ) mb_id_loc if (null bCmd) then printStoppedAtBreakInfo first_resume names @@ -1383,8 +1381,9 @@ afterRunStmt step_here run_result = do st <- getGHCiState enqueueCommands [stop st] return () - | otherwise -> resume step_here GHC.SingleStep Nothing >>= - afterRunStmt step_here >> return () + + | otherwise -> resume step Nothing >>= + afterRunStmt step >> return () flushInterpBuffers withSignalHandlers $ do @@ -3810,7 +3809,7 @@ forceCmd = pprintClosureCommand False True stepCmd :: GhciMonad m => String -> m () stepCmd arg = withSandboxOnly ":step" $ step arg where - step [] = doContinue (const True) GHC.SingleStep + step [] = doContinue GHC.SingleStep step expression = runStmt expression GHC.SingleStep >> return () stepLocalCmd :: GhciMonad m => String -> m () @@ -3829,7 +3828,7 @@ stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg Just loc -> do md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule current_toplevel_decl <- enclosingTickSpan md loc - doContinue (`isSubspanOf` RealSrcSpan current_toplevel_decl Strict.Nothing) GHC.SingleStep + doContinue (GHC.LocalStep (RealSrcSpan current_toplevel_decl Strict.Nothing)) stepModuleCmd :: GhciMonad m => String -> m () stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg @@ -3840,9 +3839,7 @@ stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg mb_span <- getCurrentBreakSpan case mb_span of Nothing -> stepCmd [] - Just pan -> do - let f some_span = srcSpanFileName_maybe pan == srcSpanFileName_maybe some_span - doContinue f GHC.SingleStep + Just pan -> doContinue (GHC.ModuleStep pan) -- | Returns the span of the largest tick containing the srcspan given enclosingTickSpan :: GhciMonad m => Module -> SrcSpan -> m RealSrcSpan @@ -3863,14 +3860,14 @@ traceCmd :: GhciMonad m => String -> m () traceCmd arg = withSandboxOnly ":trace" $ tr arg where - tr [] = doContinue (const True) GHC.RunAndLogSteps + tr [] = doContinue GHC.RunAndLogSteps tr expression = runStmt expression GHC.RunAndLogSteps >> return () continueCmd :: GhciMonad m => String -> m () -- #19157 continueCmd argLine = withSandboxOnly ":continue" $ case contSwitch (words argLine) of Left sdoc -> printForUser sdoc - Right mbCnt -> doContinue' (const True) GHC.RunToCompletion mbCnt + Right mbCnt -> doContinue' GHC.RunToCompletion mbCnt where contSwitch :: [String] -> Either SDoc (Maybe Int) contSwitch [ ] = Right Nothing @@ -3878,13 +3875,13 @@ continueCmd argLine = withSandboxOnly ":continue" $ contSwitch _ = Left $ text "After ':continue' only one ignore count is allowed" -doContinue :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> m () -doContinue pre step = doContinue' pre step Nothing +doContinue :: GhciMonad m => SingleStep -> m () +doContinue step = doContinue' step Nothing -doContinue' :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m () -doContinue' pre step mbCnt= do - runResult <- resume pre step mbCnt - _ <- afterRunStmt pre runResult +doContinue' :: GhciMonad m => SingleStep -> Maybe Int -> m () +doContinue' step mbCnt= do + runResult <- resume step mbCnt + _ <- afterRunStmt step runResult return () abandonCmd :: GhciMonad m => String -> m () @@ -4036,7 +4033,7 @@ backCmd arg | otherwise = liftIO $ putStrLn "Syntax: :back [num]" where back num = withSandboxOnly ":back" $ do - (names, _, pan, _) <- GHC.back num + (names, _, pan) <- GHC.back num printForUser $ text "Logged breakpoint at" <+> ppr pan printTypeOfNames names -- run the command set with ":set stop <cmd>" @@ -4050,7 +4047,7 @@ forwardCmd arg | otherwise = liftIO $ putStrLn "Syntax: :forward [num]" where forward num = withSandboxOnly ":forward" $ do - (names, ix, pan, _) <- GHC.forward num + (names, ix, pan) <- GHC.forward num printForUser $ (if (ix == 0) then text "Stopped at" else text "Logged breakpoint at") <+> ppr pan ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -401,14 +401,14 @@ runDecls' decls = do return Nothing) (Just <$> GHC.runParsedDecls decls) -resume :: GhciMonad m => (SrcSpan -> Bool) -> GHC.SingleStep -> Maybe Int -> m GHC.ExecResult -resume canLogSpan step mbIgnoreCnt = do +resume :: GhciMonad m => GHC.SingleStep -> Maybe Int -> m GHC.ExecResult +resume step mbIgnoreCnt = do st <- getGHCiState reifyGHCi $ \x -> withProgName (progname st) $ withArgs (args st) $ reflectGHCi x $ do - GHC.resumeExec canLogSpan step mbIgnoreCnt + GHC.resumeExec step mbIgnoreCnt -- -------------------------------------------------------------------------- -- timing & statistics ===================================== libraries/ghc-internal/src/GHC/Internal/Pack.hs ===================================== @@ -12,95 +12,20 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- ⚠Warning: Starting @base-4.18@, this module is being deprecated. --- See https://gitlab.haskell.org/ghc/ghc/-/issues/21461 for more information. --- --- --- --- This module provides a small set of low-level functions for packing --- and unpacking a chunk of bytes. Used by code emitted by the compiler --- plus the prelude libraries. --- --- The programmer level view of packed strings is provided by a GHC --- system library PackedString. +-- This function is just used by `rts_mkString` -- ----------------------------------------------------------------------------- module GHC.Internal.Pack ( - -- (**) - emitted by compiler. - - packCString#, unpackCString, - unpackCString#, - unpackNBytes#, - unpackFoldrCString#, -- (**) - unpackAppendCString#, -- (**) ) where import GHC.Internal.Base -import GHC.Internal.List ( length ) -import GHC.Internal.ST import GHC.Internal.Ptr -data ByteArray ix = ByteArray ix ix ByteArray# -data MutableByteArray s ix = MutableByteArray ix ix (MutableByteArray# s) - unpackCString :: Ptr a -> [Char] unpackCString a@(Ptr addr) | a == nullPtr = [] | otherwise = unpackCString# addr - -packCString# :: [Char] -> ByteArray# -packCString# str = case (packString str) of { ByteArray _ _ bytes -> bytes } - -packString :: [Char] -> ByteArray Int -packString str = runST (packStringST str) - -packStringST :: [Char] -> ST s (ByteArray Int) -packStringST str = - let len = length str in - packNBytesST len str - -packNBytesST :: Int -> [Char] -> ST s (ByteArray Int) -packNBytesST (I# length#) str = - {- - allocate an array that will hold the string - (not forgetting the NUL byte at the end) - -} - new_ps_array (length# +# 1#) >>= \ ch_array -> - -- fill in packed string from "str" - fill_in ch_array 0# str >> - -- freeze the puppy: - freeze_ps_array ch_array length# - where - fill_in :: MutableByteArray s Int -> Int# -> [Char] -> ST s () - fill_in arr_in# idx [] = - write_ps_array arr_in# idx (chr# 0#) >> - return () - - fill_in arr_in# idx (C# c : cs) = - write_ps_array arr_in# idx c >> - fill_in arr_in# (idx +# 1#) cs - --- (Very :-) ``Specialised'' versions of some CharArray things... - -new_ps_array :: Int# -> ST s (MutableByteArray s Int) -write_ps_array :: MutableByteArray s Int -> Int# -> Char# -> ST s () -freeze_ps_array :: MutableByteArray s Int -> Int# -> ST s (ByteArray Int) - -new_ps_array size = ST $ \ s -> - case (newByteArray# size s) of { (# s2#, barr# #) -> - (# s2#, MutableByteArray bot bot barr# #) } - where - bot = errorWithoutStackTrace "new_ps_array" - -write_ps_array (MutableByteArray _ _ barr#) n ch = ST $ \ s# -> - case writeCharArray# barr# n ch s# of { s2# -> - (# s2#, () #) } - --- same as unsafeFreezeByteArray -freeze_ps_array (MutableByteArray _ _ arr#) len# = ST $ \ s# -> - case unsafeFreezeByteArray# arr# s# of { (# s2#, frozen# #) -> - (# s2#, ByteArray 0 (I# len#) frozen# #) } ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -79,9 +79,9 @@ filled is generated via raiseJSException. -} -stg_blockPromise :: JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r -stg_blockPromise p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> - case stg_jsffi_check (unsafeCoerce# $ toException WouldBlockException) s0 of +stg_blockPromise :: String -> JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r +stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> + case stg_jsffi_check (unsafeCoerce# $ toException $ WouldBlockException err_msg) s0 of (# s1 #) -> case myThreadId# s1 of (# s2, tso #) -> case makeStablePtr# tso s2 of (# s3, sp #) -> ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -139,8 +139,8 @@ foreign import javascript unsafe "`${$1.stack ? $1.stack : $1}`" instance Exception JSException -data WouldBlockException - = WouldBlockException +newtype WouldBlockException + = WouldBlockException String deriving (Show) instance Exception WouldBlockException ===================================== rts/include/RtsAPI.h ===================================== @@ -587,15 +587,15 @@ void rts_done (void); // the base package itself. // #if defined(COMPILING_WINDOWS_DLL) && !defined(COMPILING_GHC_INTERNAL_PACKAGE) -__declspec(dllimport) extern StgWord ghczminternal_GHCziInternalziTopHandler_runIO_closure[]; -__declspec(dllimport) extern StgWord ghczminternal_GHCziInternalziTopHandler_runNonIO_closure[]; +__declspec(dllimport) extern StgClosure ghczminternal_GHCziInternalziTopHandler_runIO_closure; +__declspec(dllimport) extern StgClosure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure; #else -extern StgWord ghczminternal_GHCziInternalziTopHandler_runIO_closure[]; -extern StgWord ghczminternal_GHCziInternalziTopHandler_runNonIO_closure[]; +extern StgClosure ghczminternal_GHCziInternalziTopHandler_runIO_closure; +extern StgClosure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure; #endif -#define runIO_closure ghczminternal_GHCziInternalziTopHandler_runIO_closure -#define runNonIO_closure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure +#define runIO_closure DLL_IMPORT_DATA_REF(ghczminternal_GHCziInternalziTopHandler_runIO_closure) +#define runNonIO_closure DLL_IMPORT_DATA_REF(ghczminternal_GHCziInternalziTopHandler_runNonIO_closure) /* ------------------------------------------------------------------------ */ ===================================== testsuite/tests/jsffi/jsffigc.hs ===================================== @@ -10,17 +10,16 @@ import System.Mem type BinOp a = a -> a -> a -foreign import javascript "wrapper" +foreign import javascript "wrapper sync" js_from_hs :: BinOp Int -> IO JSVal --- This must be safe since we intend to call back into Haskell again. -foreign import javascript safe "dynamic" +foreign import javascript unsafe "dynamic" js_to_hs :: JSVal -> BinOp Int foreign import javascript "wrapper" js_mk_cont :: IO () -> IO JSVal -foreign export javascript "testDynExportFree" +foreign export javascript "testDynExportFree sync" testDynExportFree :: Int -> Int -> Int -> IO () -- JSVal uses Weak# under the hood for garbage collection support, ===================================== testsuite/tests/jsffi/jsffigc.mjs ===================================== @@ -8,7 +8,7 @@ async function reallyGC() { } export default async (__exports) => { - await __exports.testDynExportFree(114, 514, 1919810); + __exports.testDynExportFree(114, 514, 1919810); const cont = await __exports.testDynExportGC(114, 514, 1919810); await reallyGC(); ===================================== testsuite/tests/jsffi/jsffisleep.hs ===================================== @@ -20,8 +20,8 @@ foreign export ccall "testWouldBlock" -- non-main exports in C FFI. In JSFFI, it's always done automatically -- for every export though. testWouldBlock :: IO () -testWouldBlock = catch (threadDelay 1000000) $ \WouldBlockException -> do - print WouldBlockException +testWouldBlock = catch (threadDelay 1000000) $ \(WouldBlockException err) -> do + print $ WouldBlockException err flushStdHandles foreign export javascript "testLazySleep" ===================================== testsuite/tests/jsffi/jsffisleep.stdout ===================================== @@ -1,4 +1,4 @@ -WouldBlockException +WouldBlockException "new Promise(res => setTimeout(res, $1 / 1000))" zzzzzzz i sleep Left thread killed ===================================== testsuite/tests/jsffi/textconv.hs ===================================== @@ -45,7 +45,7 @@ textToJSString (Text (ByteArray ba#) (I# off#) (I# len#)) = unsafeDupablePerform (# s1, mba# #) -> case copyByteArray# ba# off# mba# 0# len# s1 of s2 -> keepAlive# mba# s2 $ unIO $ js_to_str (Ptr (mutableByteArrayContents# mba#)) $ I# len# -foreign export javascript "main" +foreign export javascript "main sync" main :: IO () main :: IO () ===================================== testsuite/tests/jsffi/textconv.mjs ===================================== @@ -1,3 +1,3 @@ -export default async (__exports) => { - await __exports.main(); +export default (__exports) => { + __exports.main(); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3add7dc2927050afdefa75f44228a3d4e62d706d...9b54eecbee7329543e5016cec1574831bfb788c2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3add7dc2927050afdefa75f44228a3d4e62d706d...9b54eecbee7329543e5016cec1574831bfb788c2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/d7a8aef6/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 21:00:06 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Mar 2025 16:00:06 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67c6185662a74_2c674bd677ac6845f@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - 4a08d40d by Matthew Pickering at 2025-03-03T15:59:35-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - ce7358e7 by Matthew Pickering at 2025-03-03T15:59:35-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 6e0710bc by Ben Gamari at 2025-03-03T15:59:35-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 22 changed files: - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModIface.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/src/Rules/Test.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T Changes: ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -47,7 +47,6 @@ import GHC.Core.RoughMap ( RoughMatchTc(..) ) import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env -import GHC.Driver.Backend import GHC.Driver.DynFlags import GHC.Driver.Plugins @@ -342,7 +341,7 @@ mkIface_ hsc_env trust_info = setSafeMode safe_mode annotations = map mkIfaceAnnotation anns icomplete_matches = map mkIfaceCompleteMatch complete_matches - !rdrs = maybeGlobalRdrEnv rdr_env + !rdrs = mkIfaceTopEnv rdr_env emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag @@ -395,15 +394,11 @@ mkIface_ hsc_env -- Desugar.addExportFlagsAndRules). The mi_top_env field is used -- by GHCi to decide whether the module has its full top-level -- scope available. (#5534) - maybeGlobalRdrEnv :: GlobalRdrEnv -> Maybe IfaceTopEnv - maybeGlobalRdrEnv rdr_env - | backendWantsGlobalBindings (backend dflags) - = Just $! let !exports = forceGlobalRdrEnv (globalRdrEnvLocal rdr_env) - !imports = mkIfaceImports import_decls - in IfaceTopEnv exports imports - -- See Note [Forcing GREInfo] in GHC.Types.GREInfo. - | otherwise - = Nothing + mkIfaceTopEnv :: GlobalRdrEnv -> IfaceTopEnv + mkIfaceTopEnv rdr_env + = let !exports = sortAvails $ gresToAvailInfo $ globalRdrEnvElts $ globalRdrEnvLocal rdr_env + !imports = mkIfaceImports import_decls + in IfaceTopEnv exports imports ifFamInstTcName = ifFamInstFam @@ -515,8 +510,8 @@ mkIfaceImports :: [ImportUserSpec] -> [IfaceImport] mkIfaceImports = map go where go (ImpUserSpec decl ImpUserAll) = IfaceImport decl ImpIfaceAll - go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env)) - go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns) + go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (sortAvails env)) + go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut (nameSetElemsStable ns)) mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -26,7 +26,8 @@ module GHC.Iface.Syntax ( IfaceCompleteMatch(..), IfaceLFInfo(..), IfaceTopBndrInfo(..), IfaceImport(..), - ImpIfaceList(..), + ifImpModule, + ImpIfaceList(..), IfaceExport, -- * Binding names IfaceTopBndr, @@ -69,6 +70,7 @@ import GHC.Types.Name.Set import GHC.Types.Name.Reader import GHC.Types.CostCentre import GHC.Types.Literal +import GHC.Types.Avail import GHC.Types.ForeignCall import GHC.Types.Annotations( AnnPayload, AnnTarget ) import GHC.Types.Basic @@ -112,12 +114,48 @@ infixl 3 &&& ************************************************************************ -} +type IfaceExport = AvailInfo + data IfaceImport = IfaceImport ImpDeclSpec ImpIfaceList data ImpIfaceList = ImpIfaceAll -- ^ no user import list - | ImpIfaceExplicit !IfGlobalRdrEnv - | ImpIfaceEverythingBut !NameSet + | ImpIfaceExplicit !DetOrdAvails + | ImpIfaceEverythingBut ![Name] + + +-- | Extract the imported module from an IfaceImport +ifImpModule :: IfaceImport -> Module +ifImpModule (IfaceImport declSpec _) = is_mod declSpec + +instance Binary IfaceImport where + put_ bh (IfaceImport declSpec ifaceList) = do + put_ bh declSpec + put_ bh ifaceList + get bh = do + declSpec <- get bh + ifaceList <- get bh + return (IfaceImport declSpec ifaceList) + +instance Binary ImpIfaceList where + put_ bh ImpIfaceAll = putByte bh 0 + put_ bh (ImpIfaceExplicit env) = do + putByte bh 1 + put_ bh env + put_ bh (ImpIfaceEverythingBut ns) = do + putByte bh 2 + put_ @[Name] bh ns + get bh = do + tag <- getByte bh + case tag of + 0 -> return ImpIfaceAll + 1 -> do + env <- get bh + return (ImpIfaceExplicit env) + 2 -> do + ns <- get @[Name] bh + return (ImpIfaceEverythingBut ns) + _ -> fail "instance Binary ImpIfaceList: Invalid tag" -- | A binding top-level 'Name' in an interface file (e.g. the name of an -- 'IfaceDecl'). ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -104,6 +104,7 @@ import GHC.Types.SourceText import GHC.Types.Basic hiding ( SuccessFlag(..) ) import GHC.Types.CompleteMatch import GHC.Types.SrcLoc +import GHC.Types.Avail import GHC.Types.TypeEnv import GHC.Types.Unique.FM import GHC.Types.Unique.DSet ( mkUniqDSet ) @@ -114,7 +115,7 @@ import GHC.Types.Literal import GHC.Types.Var as Var import GHC.Types.Var.Set import GHC.Types.Name -import GHC.Types.Name.Reader +import GHC.Types.Name.Set import GHC.Types.Name.Env import GHC.Types.DefaultEnv ( ClassDefaults(..), defaultEnv ) import GHC.Types.Id @@ -2242,9 +2243,7 @@ hydrateCgBreakInfo CgBreakInfo{..} = do -- | This function is only used to construct the environment for GHCi, -- so we make up fake locations -tcIfaceImport :: HscEnv -> IfaceImport -> ImportUserSpec -tcIfaceImport _ (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll -tcIfaceImport _ (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut ns) -tcIfaceImport hsc_env (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (hydrateGlobalRdrEnv get_GRE_info gre)) - where - get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm +tcIfaceImport :: IfaceImport -> ImportUserSpec +tcIfaceImport (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll +tcIfaceImport (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut (mkNameSet ns)) +tcIfaceImport (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (getDetOrdAvails gre)) ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -2015,6 +2015,8 @@ lookupGREInfo hsc_env nm -- and looks up the TyThing in the type environment. -- -- See Note [Retrieving the GREInfo from interfaces] in GHC.Types.GREInfo. + -- Note: This function is very similar to 'tcIfaceGlobal', it would be better to + -- use that if possible. = case nameModule_maybe nm of Nothing -> UnboundGRE Just mod -> ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -1189,7 +1189,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) (gres, imp_user_list) = case want_hiding of Exactly -> let gre_env = mkGlobalRdrEnv $ concatMap (gresFromIE decl_spec) items2 - in (gre_env, ImpUserExplicit gre_env) + in (gre_env, ImpUserExplicit (gresToAvailInfo $ globalRdrEnvElts $ gre_env)) EverythingBut -> let hidden_names = mkNameSet $ concatMap (map greName . snd) items2 in (importsFromIface hsc_env iface decl_spec (Just hidden_names), ImpUserEverythingBut hidden_names) ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -18,7 +18,7 @@ module GHC.Runtime.Eval ( abandon, abandonAll, getResumeContext, getHistorySpan, - getModBreaks, + getModBreaks, readModBreaks, getHistoryModule, setupBreakpoint, back, forward, @@ -53,7 +53,7 @@ import GHC.Driver.DynFlags import GHC.Driver.Ppr import GHC.Driver.Config -import GHC.Rename.Names (importsFromIface) +import GHC.Rename.Names (importsFromIface, gresFromAvails) import GHC.Runtime.Eval.Types import GHC.Runtime.Interpreter as GHCi @@ -113,6 +113,7 @@ import GHC.Types.TyThing import GHC.Types.Breakpoint import GHC.Types.Unique.Map +import GHC.Types.Avail import GHC.Unit import GHC.Unit.Module.Graph import GHC.Unit.Module.ModIface @@ -122,7 +123,7 @@ import GHC.Unit.Home.PackageTable import GHC.Tc.Module ( runTcInteractive, tcRnType, loadUnqualIfaces ) import GHC.Tc.Solver (simplifyWantedsTcM) -import GHC.Tc.Utils.Env (tcGetInstEnvs, lookupGlobal) +import GHC.Tc.Utils.Env (tcGetInstEnvs) import GHC.Tc.Utils.Instantiate (instDFunType) import GHC.Tc.Utils.Monad import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) @@ -130,14 +131,12 @@ import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) import GHC.IfaceToCore import Control.Monad -import Control.Monad.Catch as MC import Data.Array import Data.Dynamic import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.List (find,intercalate) import Data.List.NonEmpty (NonEmpty) -import System.Directory import Unsafe.Coerce ( unsafeCoerce ) import qualified GHC.Unit.Home.Graph as HUG @@ -156,9 +155,8 @@ getHistoryModule = ibi_tick_mod . historyBreakpointId getHistorySpan :: HscEnv -> History -> IO SrcSpan getHistorySpan hsc_env hist = do let ibi = historyBreakpointId hist - HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) >>= pure . \case - Just hmi -> modBreaks_locs (getModBreaks hmi) ! ibi_tick_index ibi - _ -> panic "getHistorySpan" + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi {- | Finds the enclosing top level function name -} -- ToDo: a better way to do this would be to keep hold of the decl_path computed @@ -166,9 +164,8 @@ getHistorySpan hsc_env hist = do -- for each tick. findEnclosingDecls :: HscEnv -> InternalBreakpointId -> IO [String] findEnclosingDecls hsc_env ibi = do - hmi <- expectJust <$> HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) - return $ - modBreaks_decls (getModBreaks hmi) ! ibi_tick_index ibi + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_decls brks ! ibi_tick_index ibi -- | Update fixity environment in the current interactive context. updateFixityEnv :: GhcMonad m => FixityEnv -> m () @@ -232,10 +229,9 @@ execStmt' stmt stmt_text ExecOptions{..} = do updateFixityEnv fix_env status <- - withVirtualCWD $ - liftIO $ do - let eval_opts = initEvalOpts idflags' (isStep execSingleStep) - evalStmt interp eval_opts (execWrap hval) + liftIO $ do + let eval_opts = initEvalOpts idflags' (enableGhcStepMode execSingleStep) + evalStmt interp eval_opts (execWrap hval) let ic = hsc_IC hsc_env bindings = (ic_tythings ic, ic_gre_cache ic) @@ -282,38 +278,17 @@ them. The relevant predicate is OccName.isDerivedOccName. See #11051 for more background and examples. -} -withVirtualCWD :: GhcMonad m => m a -> m a -withVirtualCWD m = do - hsc_env <- getSession - - -- a virtual CWD is only necessary when we're running interpreted code in - -- the same process as the compiler. - case interpInstance <$> hsc_interp hsc_env of - Just (ExternalInterp {}) -> m - _ -> do - let ic = hsc_IC hsc_env - let set_cwd = do - dir <- liftIO $ getCurrentDirectory - case ic_cwd ic of - Just dir -> liftIO $ setCurrentDirectory dir - Nothing -> return () - return dir - - reset_cwd orig_dir = do - virt_dir <- liftIO $ getCurrentDirectory - hsc_env <- getSession - let old_IC = hsc_IC hsc_env - setSession hsc_env{ hsc_IC = old_IC{ ic_cwd = Just virt_dir } } - liftIO $ setCurrentDirectory orig_dir - - MC.bracket set_cwd reset_cwd $ \_ -> m - parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) parseImportDecl expr = withSession $ \hsc_env -> liftIO $ hscImport hsc_env expr emptyHistory :: Int -> BoundedList History emptyHistory size = nilBL size +-- | Turn an 'EvalStatus_' result from interpreting Haskell into a GHCi 'ExecResult'. +-- +-- This function is responsible for resuming execution at an intermediate +-- breakpoint if we don't care about that breakpoint (e.g. if using :steplocal +-- or :stepmodule, rather than :step, we only care about certain breakpoints). handleRunStatus :: GhcMonad m => SingleStep -> String -> ResumeBindings @@ -322,92 +297,107 @@ handleRunStatus :: GhcMonad m -> BoundedList History -> m ExecResult -handleRunStatus step expr bindings final_ids status history0 - | RunAndLogSteps <- step = tracing - | otherwise = not_tracing - where - tracing - | EvalBreak apStack_ref (Just eval_break) resume_ctxt _ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - let dflags = hsc_dflags hsc_env - ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break - hmi <- liftIO $ expectJust <$> - lookupHpt (hsc_HPT hsc_env) (moduleName (ibi_tick_mod ibi)) - let breaks = getModBreaks hmi - - b <- liftIO $ - breakpointStatus interp (modBreaks_flags breaks) (ibi_tick_index ibi) - if b - then not_tracing - -- This breakpoint is explicitly enabled; we want to stop - -- instead of just logging it. - else do - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi - let !history' = history1 `consBL` history0 - -- history is strict, otherwise our BoundedList is pointless. - fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - let eval_opts = initEvalOpts dflags True - status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv - handleRunStatus RunAndLogSteps expr bindings final_ids - status history' - | otherwise - = not_tracing - - not_tracing - -- Hit a breakpoint - | EvalBreak apStack_ref maybe_break resume_ctxt ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - ibi <- case maybe_break of - Nothing -> pure Nothing - Just break -> fmap Just $ liftIO $ - evalBreakpointToId (hsc_HPT hsc_env) break - (hsc_env1, names, span, decl) <- liftIO $ - bindLocalsAtBreakpoint hsc_env apStack_fhv ibi - let - resume = Resume - { resumeStmt = expr - , resumeContext = resume_ctxt_fhv - , resumeBindings = bindings - , resumeFinalIds = final_ids - , resumeApStack = apStack_fhv - , resumeBreakpointId = ibi - , resumeSpan = span - , resumeHistory = toListBL history0 - , resumeDecl = decl - , resumeCCS = ccs - , resumeHistoryIx = 0 - } - hsc_env2 = pushResume hsc_env1 resume - - setSession hsc_env2 - return (ExecBreak names ibi) +handleRunStatus step expr bindings final_ids status history0 = do + hsc_env <- getSession + let + interp = hscInterp hsc_env + dflags = hsc_dflags hsc_env + case status of -- Completed successfully - | EvalComplete allocs (EvalSuccess hvals) <- status - = do hsc_env <- getSession - let final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids - final_names = map getName final_ids - interp = hscInterp hsc_env - liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) - hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} - setSession hsc_env' - return (ExecComplete (Right final_names) allocs) + EvalComplete allocs (EvalSuccess hvals) -> do + let + final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids + final_names = map getName final_ids + liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) + hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} + setSession hsc_env' + return (ExecComplete (Right final_names) allocs) -- Completed with an exception - | EvalComplete alloc (EvalException e) <- status - = return (ExecComplete (Left (fromSerializableException e)) alloc) - + EvalComplete alloc (EvalException e) -> + return (ExecComplete (Left (fromSerializableException e)) alloc) + + -- Nothing case: we stopped when an exception was raised, not at a breakpoint. + EvalBreak apStack_ref Nothing resume_ctxt ccs -> do + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + let span = mkGeneralSrcSpan (fsLit "<unknown>") + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span Nothing + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Nothing + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = "<exception thrown>" + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + + setSession hsc_env2 + return (ExecBreak names Nothing) + + -- Just case: we stopped at a breakpoint + EvalBreak apStack_ref (Just eval_break) resume_ctxt ccs -> do + ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break + tick_brks <- liftIO $ readModBreaks hsc_env (ibi_tick_mod ibi) + let + span = modBreaks_locs tick_brks ! ibi_tick_index ibi + decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi + + b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi) + + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + + -- This breakpoint is explicitly enabled; we want to stop + -- instead of just logging it. + if b || breakHere step span then do + -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break. + -- Specifically, for :steplocal or :stepmodule, don't return control + -- and simply resume execution from here until we hit a breakpoint we do want to stop at. + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Just ibi + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = decl + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + setSession hsc_env2 + return (ExecBreak names (Just ibi)) + else do + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) + status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv + history <- if not tracing then pure history0 else do + history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi + let !history' = history1 `consBL` history0 + -- history is strict, otherwise our BoundedList is pointless. + return history' + handleRunStatus step expr bindings final_ids status history + where + tracing | RunAndLogSteps <- step = True + | otherwise = False -resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> Maybe Int +resumeExec :: GhcMonad m => SingleStep -> Maybe Int -> m ExecResult -resumeExec canLogSpan step mbCnt +resumeExec step mbCnt = do hsc_env <- getSession let ic = hsc_IC hsc_env @@ -445,42 +435,41 @@ resumeExec canLogSpan step mbCnt , resumeBreakpointId = mb_brkpt , resumeSpan = span , resumeHistory = hist } -> - withVirtualCWD $ do + do -- When the user specified a break ignore count, set it -- in the interpreter case (mb_brkpt, mbCnt) of (Just brkpt, Just cnt) -> setupBreakpoint hsc_env (toBreakpointId brkpt) cnt _ -> return () - let eval_opts = initEvalOpts dflags (isStep step) + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv let prevHistoryLst = fromListBL 50 hist hist' = case mb_brkpt of Nothing -> pure prevHistoryLst Just bi - | not $ canLogSpan span -> pure prevHistoryLst - | otherwise -> do + | breakHere step span -> do hist1 <- liftIO (mkHistory hsc_env apStack bi) return $ hist1 `consBL` fromListBL 50 hist + | otherwise -> pure prevHistoryLst handleRunStatus step expr bindings final_ids status =<< hist' setupBreakpoint :: GhcMonad m => HscEnv -> BreakpointId -> Int -> m () -- #19157 setupBreakpoint hsc_env bi cnt = do let modl = bi_tick_mod bi - modBreaks <- getModBreaks . expectJust <$> - liftIO (lookupHpt (hsc_HPT hsc_env) (moduleName modl)) + modBreaks <- liftIO $ readModBreaks hsc_env modl let breakarray = modBreaks_flags modBreaks interp = hscInterp hsc_env _ <- liftIO $ GHCi.storeBreakpoint interp breakarray (bi_tick_index bi) cnt pure () -back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) back n = moveHist (+n) -forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) forward n = moveHist (subtract n) -moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan, String) +moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan) moveHist fn = do hsc_env <- getSession case ic_resume (hsc_IC hsc_env) of @@ -498,15 +487,20 @@ moveHist fn = do let update_ic apStack mb_info = do - (hsc_env1, names, span, decl) <- - liftIO $ bindLocalsAtBreakpoint hsc_env apStack mb_info + span <- case mb_info of + Nothing -> return $ mkGeneralSrcSpan (fsLit "<unknown>") + Just ibi -> liftIO $ do + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi + (hsc_env1, names) <- + liftIO $ bindLocalsAtBreakpoint hsc_env apStack span mb_info let ic = hsc_IC hsc_env1 r' = r { resumeHistoryIx = new_ix } ic' = ic { ic_resume = r':rs } setSession hsc_env1{ hsc_IC = ic' } - return (names, new_ix, span, decl) + return (names, new_ix, span) -- careful: we want apStack to be the AP_STACK itself, not a thunk -- around it, hence the cases are carefully constructed below to @@ -527,19 +521,25 @@ moveHist fn = do result_fs :: FastString result_fs = fsLit "_result" +-- | Read the 'ModBreaks' of the given home 'Module' from the 'HomeUnitGraph'. +readModBreaks :: HscEnv -> Module -> IO ModBreaks +readModBreaks hsc_env mod = + getModBreaks . expectJust <$> + HUG.lookupHugByModule mod (hsc_HUG hsc_env) + bindLocalsAtBreakpoint :: HscEnv -> ForeignHValue + -> SrcSpan -> Maybe InternalBreakpointId - -> IO (HscEnv, [Name], SrcSpan, String) + -> IO (HscEnv, [Name]) -- Nothing case: we stopped when an exception was raised, not at a -- breakpoint. We have no location information or local variables to -- bind, all we can do is bind a local variable to the exception -- value. -bindLocalsAtBreakpoint hsc_env apStack Nothing = do +bindLocalsAtBreakpoint hsc_env apStack span Nothing = do let exn_occ = mkVarOccFS (fsLit "_exception") - span = mkGeneralSrcSpan (fsLit "<unknown>") exn_name <- newInteractiveBinder hsc_env exn_occ span let e_fs = fsLit "e" @@ -552,32 +552,21 @@ bindLocalsAtBreakpoint hsc_env apStack Nothing = do interp = hscInterp hsc_env -- Loader.extendLoadedEnv interp [(exn_name, apStack)] - return (hsc_env{ hsc_IC = ictxt1 }, [exn_name], span, "<exception thrown>") + return (hsc_env{ hsc_IC = ictxt1 }, [exn_name]) -- Just case: we stopped at a breakpoint, we have information about the location -- of the breakpoint and the free variables of the expression. -bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do - let - interp = hscInterp hsc_env - - info_mod = ibi_info_mod ibi - info_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName info_mod) - let - info_brks = getModBreaks info_hmi - info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) - - tick_mod = ibi_tick_mod ibi - tick_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName tick_mod) - let - tick_brks = getModBreaks tick_hmi - occs = modBreaks_vars tick_brks ! ibi_tick_index ibi - span = modBreaks_locs tick_brks ! ibi_tick_index ibi - decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi +bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do + info_brks <- readModBreaks hsc_env (ibi_info_mod ibi) + tick_brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + let info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) + interp = hscInterp hsc_env + occs = modBreaks_vars tick_brks ! ibi_tick_index ibi -- Rehydrate to understand the breakpoint info relative to the current environment. -- This design is critical to preventing leaks (#22530) (mbVars, result_ty) <- initIfaceLoad hsc_env - $ initIfaceLcl info_mod (text "debugger") NotBoot + $ initIfaceLcl (ibi_info_mod ibi) (text "debugger") NotBoot $ hydrateCgBreakInfo info let @@ -624,7 +613,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do Loader.extendLoadedEnv interp (zip names fhvs) when result_ok $ Loader.extendLoadedEnv interp [(result_name, apStack_fhv)] hsc_env1 <- rttiEnvironment hsc_env{ hsc_IC = ictxt1 } - return (hsc_env1, if result_ok then result_name:names else names, span, decl) + return (hsc_env1, if result_ok then result_name:names else names) where -- We need a fresh Unique for each Id we bind, because the linker -- state is single-threaded and otherwise we'd spam old bindings @@ -848,21 +837,25 @@ mkTopLevEnv hsc_env modl Nothing -> pure $ Left "not a home module" Just details -> case mi_top_env (hm_iface details) of - Nothing -> pure $ Left "not interpreted" - Just (IfaceTopEnv exports imports) -> do + (IfaceTopEnv exports imports) -> do imports_env <- runInteractiveHsc hsc_env $ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv) $ forM imports $ \iface_import -> do - let ImpUserSpec spec details = tcIfaceImport hsc_env iface_import + let ImpUserSpec spec details = tcIfaceImport iface_import iface <- loadSrcInterface (text "imported by GHCi") (moduleName $ is_mod spec) (is_isboot spec) (is_pkg_qual spec) pure $ case details of ImpUserAll -> importsFromIface hsc_env iface spec Nothing ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns) - ImpUserExplicit x -> x - let get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm - let exports_env = hydrateGlobalRdrEnv get_GRE_info exports + ImpUserExplicit x -> + -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y). + -- It is only used for error messages. It seems dubious even to add an import context to these GREs as + -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that + -- the test case produce the same output as before. + let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } } + in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x + let exports_env = mkGlobalRdrEnv $ gresFromAvails hsc_env Nothing (getDetOrdAvails exports) pure $ Right $ plusGlobalRdrEnv imports_env exports_env where hpt = hsc_HPT hsc_env @@ -880,8 +873,8 @@ moduleIsInterpreted :: GhcMonad m => Module -> m Bool moduleIsInterpreted modl = withSession $ \h -> if notHomeModule (hsc_home_unit h) modl then return False - else liftIO (lookupHpt (hsc_HPT h) (moduleName modl)) >>= \case - Just details -> return (isJust (mi_top_env (hm_iface details))) + else liftIO (HUG.lookupHugByModule modl (hsc_HUG h)) >>= \case + Just hmi -> return (isJust $ homeModInfoByteCode hmi) _not_a_home_module -> return False -- | Looks up an identifier in the current interactive context (for :info) ===================================== compiler/GHC/Runtime/Eval/Types.hs ===================================== @@ -9,7 +9,8 @@ module GHC.Runtime.Eval.Types ( Resume(..), ResumeBindings, IcGlobalRdrEnv(..), History(..), ExecResult(..), - SingleStep(..), isStep, ExecOptions(..) + SingleStep(..), enableGhcStepMode, breakHere, + ExecOptions(..) ) where import GHC.Prelude @@ -35,21 +36,59 @@ data ExecOptions , execWrap :: ForeignHValue -> EvalExpr ForeignHValue } +-- | What kind of stepping are we doing? data SingleStep = RunToCompletion - | SingleStep + + -- | :trace [expr] | RunAndLogSteps -isStep :: SingleStep -> Bool -isStep RunToCompletion = False -isStep _ = True + -- | :step [expr] + | SingleStep + + -- | :steplocal [expr] + | LocalStep + { breakAt :: SrcSpan } + + -- | :stepmodule [expr] + | ModuleStep + { breakAt :: SrcSpan } + +-- | Whether this 'SingleStep' mode requires instructing the interpreter to +-- step at every breakpoint. +enableGhcStepMode :: SingleStep -> Bool +enableGhcStepMode RunToCompletion = False +enableGhcStepMode _ = True + +-- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return +-- @True@ if based on the step-mode alone we should stop at this breakpoint. +-- +-- In particular, this will always be @False@ for @'RunToCompletion'@ and +-- @'RunAndLogSteps'@. We'd need further information e.g. about the user +-- breakpoints to determine whether to break in those modes. +breakHere :: SingleStep -> SrcSpan -> Bool +breakHere step break_span = case step of + RunToCompletion -> False + RunAndLogSteps -> False + SingleStep -> True + LocalStep span -> break_span `isSubspanOf` span + ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span data ExecResult + + -- | Execution is complete = ExecComplete { execResult :: Either SomeException [Name] , execAllocation :: Word64 } - | ExecBreak + + -- | Execution stopped at a breakpoint. + -- + -- Note: `ExecBreak` is only returned by `handleRunStatus` when GHCi should + -- definitely stop at this breakpoint. GHCi is /not/ responsible for + -- subsequently deciding whether to really stop here. + -- `ExecBreak` always means GHCi breaks. + | ExecBreak { breakNames :: [Name] , breakPointId :: Maybe InternalBreakpointId } ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -124,7 +124,7 @@ import GHC.Serialized import GHC.Unit.Finder import GHC.Unit.Module import GHC.Unit.Module.ModIface -import GHC.Unit.Module.Deps +import GHC.Iface.Syntax import GHC.Utils.Misc import GHC.Utils.Panic as Panic @@ -2887,16 +2887,12 @@ reifyModule (TH.Module (TH.PkgName pkgString) (TH.ModName mString)) = do reifyFromIface reifMod = do iface <- loadInterfaceForModule (text "reifying module from TH for" <+> ppr reifMod) reifMod - let usages = [modToTHMod m | usage <- mi_usages iface, - Just m <- [usageToModule (moduleUnit reifMod) usage] ] + let IfaceTopEnv _ imports = mi_top_env iface + -- Convert IfaceImport to module names + usages = [modToTHMod (ifImpModule imp) | imp <- imports] return $ TH.ModuleInfo usages - usageToModule :: Unit -> Usage -> Maybe Module - usageToModule _ (UsageFile {}) = Nothing - usageToModule this_pkg (UsageHomeModule { usg_mod_name = mn }) = Just $ mkModule this_pkg mn - usageToModule _ (UsagePackageModule { usg_mod = m }) = Just m - usageToModule _ (UsageMergedRequirement { usg_mod = m }) = Just m - usageToModule this_pkg (UsageHomeModuleInterface { usg_mod_name = mn }) = Just $ mkModule this_pkg mn + ------------------------------ mkThAppTs :: TH.Type -> [TH.Type] -> TH.Type ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -206,7 +206,7 @@ data ImportUserSpec data ImpUserList = ImpUserAll -- ^ no user import list - | ImpUserExplicit !GlobalRdrEnv + | ImpUserExplicit ![AvailInfo] | ImpUserEverythingBut !NameSet -- | A 'NameShape' is a substitution on 'Name's that can be used ===================================== compiler/GHC/Types/Avail.hs ===================================== @@ -22,7 +22,8 @@ module GHC.Types.Avail ( filterAvails, nubAvails, sortAvails, - DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails) + DetOrdAvails(DetOrdAvails, getDetOrdAvails, DefinitelyDeterministicAvails), + emptyDetOrdAvails ) where import GHC.Prelude @@ -74,7 +75,7 @@ type Avails = [AvailInfo] -- We guarantee a deterministic order by either using the order explicitly -- given by the user (e.g. in an explicit constructor export list) or instead -- by sorting the avails with 'sortAvails'. -newtype DetOrdAvails = DefinitelyDeterministicAvails Avails +newtype DetOrdAvails = DefinitelyDeterministicAvails { getDetOrdAvails :: Avails } deriving newtype (Binary, Outputable, NFData) -- | It's always safe to match on 'DetOrdAvails' @@ -245,3 +246,7 @@ instance Binary AvailInfo where instance NFData AvailInfo where rnf (Avail n) = rnf n rnf (AvailTC a b) = rnf a `seq` rnf b + +-- | Create an empty DetOrdAvails +emptyDetOrdAvails :: DetOrdAvails +emptyDetOrdAvails = DefinitelyDeterministicAvails [] ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -133,6 +133,7 @@ import GHC.Unit.Module import GHC.Utils.Misc as Utils import GHC.Utils.Outputable import GHC.Utils.Panic +import GHC.Utils.Binary import Control.DeepSeq import Control.Monad ( guard ) @@ -1946,6 +1947,22 @@ data ImpDeclSpec instance NFData ImpDeclSpec where rnf = rwhnf -- Already strict in all fields +instance Binary ImpDeclSpec where + put_ bh (ImpDeclSpec mod as pkg_qual qual _dloc isboot) = do + put_ bh mod + put_ bh as + put_ bh pkg_qual + put_ bh qual + put_ bh isboot + + get bh = do + mod <- get bh + as <- get bh + pkg_qual <- get bh + qual <- get bh + isboot <- get bh + return (ImpDeclSpec mod as pkg_qual qual noSrcSpan isboot) + -- | Import Item Specification -- -- Describes import info a particular Name ===================================== compiler/GHC/Types/PkgQual.hs ===================================== @@ -6,6 +6,7 @@ module GHC.Types.PkgQual where import GHC.Prelude import GHC.Types.SourceText import GHC.Unit.Types +import GHC.Utils.Binary import GHC.Utils.Outputable import Data.Data @@ -38,4 +39,22 @@ instance Outputable PkgQual where ThisPkg u -> doubleQuotes (ppr u) OtherPkg u -> doubleQuotes (ppr u) +instance Binary PkgQual where + put_ bh NoPkgQual = putByte bh 0 + put_ bh (ThisPkg u) = do + putByte bh 1 + put_ bh u + put_ bh (OtherPkg u) = do + putByte bh 2 + put_ bh u + + get bh = do + tag <- getByte bh + case tag of + 0 -> return NoPkgQual + 1 -> do u <- get bh + return (ThisPkg u) + 2 -> do u <- get bh + return (OtherPkg u) + _ -> fail "instance Binary PkgQual: Invalid tag" ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -111,7 +111,6 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name -import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -299,20 +298,13 @@ data ModIface_ (phase :: ModIfacePhase) mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: !(Maybe IfaceTopEnv), + mi_top_env_ :: IfaceTopEnv, -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which -- may contains declarations for things not actually -- defined by the user). Used for GHCi and for inspecting -- the contents of modules via the GHC API only. - -- - -- (We need the source file to figure out the - -- top-level environment, if we didn't compile this module - -- from source then this field contains @Nothing@). - -- - -- Strictly speaking this field should live in the - -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -365,13 +357,23 @@ data ModIface_ (phase :: ModIfacePhase) -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !IfGlobalRdrEnv -- ^ all top level things in this module, including unexported stuff + { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where rnf (IfaceTopEnv a b) = rnf a `seq` rnf b +instance Binary IfaceTopEnv where + put_ bh (IfaceTopEnv exports imports) = do + put_ bh exports + put_ bh imports + get bh = do + exports <- get bh + imports <- get bh + return (IfaceTopEnv exports imports) + + {- Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -479,6 +481,7 @@ instance Binary ModIface where mi_trust_ = trust, mi_trust_pkg_ = trust_pkg, mi_complete_matches_ = complete_matches, + mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header @@ -526,6 +529,7 @@ instance Binary ModIface where put_ bh trust put_ bh trust_pkg put_ bh complete_matches + lazyPut bh top_env lazyPutMaybe bh docs get bh = do @@ -560,6 +564,7 @@ instance Binary ModIface where trust <- get bh trust_pkg <- get bh complete_matches <- get bh + top_env <- lazyGet bh docs <- lazyGetMaybe bh return (PrivateModIface { mi_module_ = mod, @@ -582,7 +587,6 @@ instance Binary ModIface where mi_decls_ = decls, mi_extra_decls_ = extra_decls, mi_foreign_ = foreign_, - mi_top_env_ = Nothing, mi_defaults_ = defaults, mi_insts_ = insts, mi_fam_insts_ = fam_insts, @@ -593,6 +597,7 @@ instance Binary ModIface where -- And build the cached values mi_complete_matches_ = complete_matches, mi_docs_ = docs, + mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read mi_final_exts_ = ModIfaceBackend { @@ -613,8 +618,6 @@ instance Binary ModIface where }}) --- | The original names declared of a certain module that are exported -type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod @@ -638,7 +641,7 @@ emptyPartialModIface mod mi_decls_ = [], mi_extra_decls_ = Nothing, mi_foreign_ = emptyIfaceForeign, - mi_top_env_ = Nothing, + mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , mi_hpc_ = False, mi_trust_ = noIfaceTrustInfo, mi_trust_pkg_ = False, @@ -810,15 +813,14 @@ addSourceFingerprint val iface = iface { mi_src_hash_ = val } -- | Copy fields that aren't serialised to disk to the new 'ModIface_'. -- This includes especially hashes that are usually stored in the interface --- file header and 'mi_top_env'. +-- file header. -- -- We need this function after calling 'shareIface', to make sure the -- 'ModIface_' doesn't lose any information. This function does not discard -- the in-memory byte array buffer 'mi_hi_bytes'. restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase restoreFromOldModIface old new = new - { mi_top_env_ = mi_top_env_ old - , mi_hsc_src_ = mi_hsc_src_ old + { mi_hsc_src_ = mi_hsc_src_ old , mi_src_hash_ = mi_src_hash_ old } @@ -879,7 +881,7 @@ set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } -set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase @@ -996,7 +998,7 @@ pattern ModIface :: [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> ModIface_ phase ===================================== ghc/GHCi/UI.hs ===================================== @@ -1310,7 +1310,7 @@ runStmt input step = do m_result <- GhciMonad.runStmt stmt input step case m_result of Nothing -> return Nothing - Just result -> Just <$> afterRunStmt (const True) result + Just result -> Just <$> afterRunStmt step result -- `x = y` (a declaration) should be treated as `let x = y` (a statement). -- The reason is because GHCi wasn't designed to support `x = y`, but then @@ -1342,7 +1342,7 @@ runStmt input step = do _ <- liftIO $ tryIO $ hFlushAll stdin m_result <- GhciMonad.runDecls' decls forM m_result $ \result -> - afterRunStmt (const True) (GHC.ExecComplete (Right result) 0) + afterRunStmt step (GHC.ExecComplete (Right result) 0) mk_stmt :: SrcSpan -> HsBind GhcPs -> GhciLStmt GhcPs mk_stmt loc bind = @@ -1359,9 +1359,9 @@ runStmt input step = do modStr = moduleNameString $ moduleName $ icInteractiveModule $ ic -- | Clean up the GHCi environment after a statement has run -afterRunStmt :: GhciMonad m - => (SrcSpan -> Bool) -> GHC.ExecResult -> m GHC.ExecResult -afterRunStmt step_here run_result = do +afterRunStmt :: GhciMonad m => SingleStep {-^ Type of step we took just before -} + -> GHC.ExecResult -> m GHC.ExecResult +afterRunStmt step run_result = do resumes <- GHC.getResumeContext case run_result of GHC.ExecComplete{..} -> @@ -1372,9 +1372,7 @@ afterRunStmt step_here run_result = do when show_types $ printTypeOfNames names GHC.ExecBreak names mb_info | first_resume : _ <- resumes - , isNothing mb_info || - step_here (GHC.resumeSpan first_resume) -> do - mb_id_loc <- toBreakIdAndLocation mb_info + -> do mb_id_loc <- toBreakIdAndLocation mb_info let bCmd = maybe "" ( \(_,l) -> onBreakCmd l ) mb_id_loc if (null bCmd) then printStoppedAtBreakInfo first_resume names @@ -1383,8 +1381,9 @@ afterRunStmt step_here run_result = do st <- getGHCiState enqueueCommands [stop st] return () - | otherwise -> resume step_here GHC.SingleStep Nothing >>= - afterRunStmt step_here >> return () + + | otherwise -> resume step Nothing >>= + afterRunStmt step >> return () flushInterpBuffers withSignalHandlers $ do @@ -3810,7 +3809,7 @@ forceCmd = pprintClosureCommand False True stepCmd :: GhciMonad m => String -> m () stepCmd arg = withSandboxOnly ":step" $ step arg where - step [] = doContinue (const True) GHC.SingleStep + step [] = doContinue GHC.SingleStep step expression = runStmt expression GHC.SingleStep >> return () stepLocalCmd :: GhciMonad m => String -> m () @@ -3829,7 +3828,7 @@ stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg Just loc -> do md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule current_toplevel_decl <- enclosingTickSpan md loc - doContinue (`isSubspanOf` RealSrcSpan current_toplevel_decl Strict.Nothing) GHC.SingleStep + doContinue (GHC.LocalStep (RealSrcSpan current_toplevel_decl Strict.Nothing)) stepModuleCmd :: GhciMonad m => String -> m () stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg @@ -3840,9 +3839,7 @@ stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg mb_span <- getCurrentBreakSpan case mb_span of Nothing -> stepCmd [] - Just pan -> do - let f some_span = srcSpanFileName_maybe pan == srcSpanFileName_maybe some_span - doContinue f GHC.SingleStep + Just pan -> doContinue (GHC.ModuleStep pan) -- | Returns the span of the largest tick containing the srcspan given enclosingTickSpan :: GhciMonad m => Module -> SrcSpan -> m RealSrcSpan @@ -3863,14 +3860,14 @@ traceCmd :: GhciMonad m => String -> m () traceCmd arg = withSandboxOnly ":trace" $ tr arg where - tr [] = doContinue (const True) GHC.RunAndLogSteps + tr [] = doContinue GHC.RunAndLogSteps tr expression = runStmt expression GHC.RunAndLogSteps >> return () continueCmd :: GhciMonad m => String -> m () -- #19157 continueCmd argLine = withSandboxOnly ":continue" $ case contSwitch (words argLine) of Left sdoc -> printForUser sdoc - Right mbCnt -> doContinue' (const True) GHC.RunToCompletion mbCnt + Right mbCnt -> doContinue' GHC.RunToCompletion mbCnt where contSwitch :: [String] -> Either SDoc (Maybe Int) contSwitch [ ] = Right Nothing @@ -3878,13 +3875,13 @@ continueCmd argLine = withSandboxOnly ":continue" $ contSwitch _ = Left $ text "After ':continue' only one ignore count is allowed" -doContinue :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> m () -doContinue pre step = doContinue' pre step Nothing +doContinue :: GhciMonad m => SingleStep -> m () +doContinue step = doContinue' step Nothing -doContinue' :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m () -doContinue' pre step mbCnt= do - runResult <- resume pre step mbCnt - _ <- afterRunStmt pre runResult +doContinue' :: GhciMonad m => SingleStep -> Maybe Int -> m () +doContinue' step mbCnt= do + runResult <- resume step mbCnt + _ <- afterRunStmt step runResult return () abandonCmd :: GhciMonad m => String -> m () @@ -4036,7 +4033,7 @@ backCmd arg | otherwise = liftIO $ putStrLn "Syntax: :back [num]" where back num = withSandboxOnly ":back" $ do - (names, _, pan, _) <- GHC.back num + (names, _, pan) <- GHC.back num printForUser $ text "Logged breakpoint at" <+> ppr pan printTypeOfNames names -- run the command set with ":set stop <cmd>" @@ -4050,7 +4047,7 @@ forwardCmd arg | otherwise = liftIO $ putStrLn "Syntax: :forward [num]" where forward num = withSandboxOnly ":forward" $ do - (names, ix, pan, _) <- GHC.forward num + (names, ix, pan) <- GHC.forward num printForUser $ (if (ix == 0) then text "Stopped at" else text "Logged breakpoint at") <+> ppr pan ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -401,14 +401,14 @@ runDecls' decls = do return Nothing) (Just <$> GHC.runParsedDecls decls) -resume :: GhciMonad m => (SrcSpan -> Bool) -> GHC.SingleStep -> Maybe Int -> m GHC.ExecResult -resume canLogSpan step mbIgnoreCnt = do +resume :: GhciMonad m => GHC.SingleStep -> Maybe Int -> m GHC.ExecResult +resume step mbIgnoreCnt = do st <- getGHCiState reifyGHCi $ \x -> withProgName (progname st) $ withArgs (args st) $ reflectGHCi x $ do - GHC.resumeExec canLogSpan step mbIgnoreCnt + GHC.resumeExec step mbIgnoreCnt -- -------------------------------------------------------------------------- -- timing & statistics ===================================== hadrian/src/Rules/Test.hs ===================================== @@ -1,8 +1,6 @@ {-# OPTIONS_GHC -Wno-unused-top-binds #-} module Rules.Test (testRules) where -import System.Environment - import Base import CommandLine import Expression @@ -171,7 +169,6 @@ testRules = do root -/- timeoutPath %> \_ -> timeoutProgBuilder "test" ~> do - args <- userSetting defaultTestArgs let testCompilerArg = testCompiler args let stg = fromMaybe Stage2 $ stageOf testCompilerArg @@ -185,92 +182,98 @@ testRules = do let ok_to_build = filter (isOkToBuild args) extra_targets putVerbose $ " | ExtraTargets: " ++ intercalate ", " extra_targets putVerbose $ " | ExtraTargets (ok-to-build): " ++ intercalate ", " ok_to_build - need ok_to_build - - -- Prepare Ghc configuration file for input compiler. - need [root -/- timeoutPath] - - cross <- flag CrossCompiling - - -- get relative path for the given program in the given stage - let relative_path_stage s p = programPath =<< programContext s p - let make_absolute rel_path = do - abs_path <- liftIO (makeAbsolute rel_path) - fixAbsolutePathOnWindows abs_path - - rel_ghc_pkg <- relative_path_stage Stage1 ghcPkg - rel_hsc2hs <- relative_path_stage Stage1 hsc2hs - rel_hp2ps <- relative_path_stage Stage1 hp2ps - rel_haddock <- relative_path_stage (Stage0 InTreeLibs) haddock - rel_hpc <- relative_path_stage (Stage0 InTreeLibs) hpc - rel_runghc <- relative_path_stage (Stage0 InTreeLibs) runGhc + need $ ok_to_build ++ [root -/- timeoutPath] -- force stage0 program building for cross - when cross $ need [rel_hpc, rel_haddock, rel_runghc] - - prog_ghc_pkg <- make_absolute rel_ghc_pkg - prog_hsc2hs <- make_absolute rel_hsc2hs - prog_hp2ps <- make_absolute rel_hp2ps - prog_haddock <- make_absolute rel_haddock - prog_hpc <- make_absolute rel_hpc - prog_runghc <- make_absolute rel_runghc - - ghcPath <- getCompilerPath testCompilerArg - - makePath <- builderPath $ Make "" - top <- topDirectory - ghcFlags <- runTestGhcFlags - let ghciFlags = ghcFlags ++ unwords - [ "--interactive", "-v0", "-ignore-dot-ghci" - , "-fno-ghci-history", "-fprint-error-index-links=never" - ] - ccPath <- queryTargetTarget (Toolchain.prgPath . Toolchain.ccProgram . Toolchain.tgtCCompiler) - ccFlags <- queryTargetTarget (unwords . Toolchain.prgFlags . Toolchain.ccProgram . Toolchain.tgtCCompiler) - - pythonPath <- builderPath Python + cross <- flag CrossCompiling + when cross $ mapM (relativePathStage (Stage0 InTreeLibs)) [hpc, haddock, runGhc] >>= need -- Set environment variables for test's Makefile. - -- TODO: Ideally we would define all those env vars in 'env', so that - -- Shake can keep track of them, but it is not as easy as it seems - -- to get that to work. - liftIO $ do - -- Many of those env vars are used by Makefiles in the - -- test infrastructure, or from tests or their - -- Makefiles. - setEnv "MAKE" makePath - setEnv "PYTHON" pythonPath - setEnv "TEST_HC" ghcPath - setEnv "TEST_HC_OPTS" ghcFlags - setEnv "TEST_HC_OPTS_INTERACTIVE" ghciFlags - setEnv "TEST_CC" ccPath - setEnv "TEST_CC_OPTS" ccFlags - - when cross $ do - setEnv "GHC_PKG" prog_ghc_pkg - setEnv "HSC2HS" prog_hsc2hs - setEnv "HP2PS_ABS" prog_hp2ps - setEnv "HPC" prog_hpc - setEnv "HADDOCK" prog_haddock - setEnv "RUNGHC" prog_runghc - - setEnv "CHECK_PPR" (top -/- root -/- checkPprProgPath) - setEnv "CHECK_EXACT" (top -/- root -/- checkExactProgPath) - setEnv "DUMP_DECLS" (top -/- root -/- dumpDeclsProgPath) - setEnv "COUNT_DEPS" (top -/- root -/- countDepsProgPath) - setEnv "LINT_NOTES" (top -/- root -/- noteLinterProgPath) - setEnv "LINT_CODES" (top -/- root -/- codeLinterProgPath) - setEnv "LINT_WHITESPACE" (top -/- root -/- whitespaceLinterProgPath) - - -- This lets us bypass the need to generate a config - -- through Make, which happens in testsuite/mk/boilerplate.mk - -- which is in turn included by all test 'Makefile's. - setEnv "ghc_config_mk" (top -/- root -/- ghcConfigPath) - + env <- testEnv -- Execute the test target. -- We override the verbosity setting to make sure the user can see -- the test output: https://gitlab.haskell.org/ghc/ghc/issues/15951. - withVerbosity Diagnostic $ buildWithCmdOptions [] $ test_target RunTest + withVerbosity Diagnostic $ buildWithCmdOptions [AddEnv k v | (k,v) <- env] $ test_target RunTest + +testEnv :: Action [(String, String)] +testEnv = do + cross <- flag CrossCompiling + makePath <- builderPath $ Make "" + prog_ghc_pkg <- absolutePathStage Stage1 ghcPkg + prog_hsc2hs <- absolutePathStage Stage1 hsc2hs + prog_hp2ps <- absolutePathStage Stage1 hp2ps + prog_haddock <- absolutePathStage (Stage0 InTreeLibs) haddock + prog_hpc <- absolutePathStage (Stage0 InTreeLibs) hpc + prog_runghc <- absolutePathStage (Stage0 InTreeLibs) runGhc + + root <- buildRoot + args <- userSetting defaultTestArgs + let testCompilerArg = testCompiler args + ghcPath <- getCompilerPath testCompilerArg + + top <- topDirectory + pythonPath <- builderPath Python + ccPath <- queryTargetTarget (Toolchain.prgPath . Toolchain.ccProgram . Toolchain.tgtCCompiler) + ccFlags <- queryTargetTarget (unwords . Toolchain.prgFlags . Toolchain.ccProgram . Toolchain.tgtCCompiler) + ghcFlags <- runTestGhcFlags + let ghciFlags = ghcFlags ++ unwords + [ "--interactive", "-v0", "-ignore-dot-ghci" + , "-fno-ghci-history", "-fprint-error-index-links=never" + ] + + -- Many of those env vars are used by Makefiles in the + -- test infrastructure, or from tests or their + -- Makefiles. + return $ + [ "MAKE" .= makePath + , "PYTHON" .= pythonPath + , "TEST_HC" .= ghcPath + , "TEST_HC_OPTS" .= ghcFlags + , "TEST_HC_OPTS_INTERACTIVE" .= ghciFlags + , "TEST_CC" .= ccPath + , "TEST_CC_OPTS" .= ccFlags + , "CHECK_PPR" .= (top -/- root -/- checkPprProgPath) + , "CHECK_EXACT" .= (top -/- root -/- checkExactProgPath) + , "DUMP_DECLS" .= (top -/- root -/- dumpDeclsProgPath) + , "COUNT_DEPS" .= (top -/- root -/- countDepsProgPath) + , "LINT_NOTES" .= (top -/- root -/- noteLinterProgPath) + , "LINT_CODES" .= (top -/- root -/- codeLinterProgPath) + , "LINT_WHITESPACE" .= (top -/- root -/- whitespaceLinterProgPath) + -- This lets us bypass the need to generate a config + -- through Make, which happens in testsuite/mk/boilerplate.mk + -- which is in turn included by all test 'Makefile's. + , "ghc_config_mk" .= (top -/- root -/- ghcConfigPath) + ] ++ + if_ cross + [ "GHC_PKG" .= prog_ghc_pkg + , "HSC2HS" .= prog_hsc2hs + , "HP2PS_ABS" .= prog_hp2ps + , "HPC" .= prog_hpc + , "HADDOCK" .= prog_haddock + , "RUNGHC" .= prog_runghc + ] + where + if_ :: Bool -> [a] -> [a] + if_ True xs = xs + if_ False _ = [] + + (.=) = (,) + +needProgramStage :: Stage -> Package -> Action () +needProgramStage s p = relativePathStage s p >>= need . (:[]) + +-- | Get relative path for the given program in the given stage. +relativePathStage :: Stage -> Package -> Action FilePath +relativePathStage s p = programPath =<< programContext s p + +absolutePathStage :: Stage -> Package -> Action FilePath +absolutePathStage s p = + relativePathStage s p >>= make_absolute + where + make_absolute rel_path = do + abs_path <- liftIO (makeAbsolute rel_path) + fixAbsolutePathOnWindows abs_path -- | Given a test compiler and a hadrian dependency (target), check if we -- can build the target with the compiler ===================================== libraries/ghc-internal/src/GHC/Internal/Pack.hs ===================================== @@ -12,95 +12,20 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- ⚠Warning: Starting @base-4.18@, this module is being deprecated. --- See https://gitlab.haskell.org/ghc/ghc/-/issues/21461 for more information. --- --- --- --- This module provides a small set of low-level functions for packing --- and unpacking a chunk of bytes. Used by code emitted by the compiler --- plus the prelude libraries. --- --- The programmer level view of packed strings is provided by a GHC --- system library PackedString. +-- This function is just used by `rts_mkString` -- ----------------------------------------------------------------------------- module GHC.Internal.Pack ( - -- (**) - emitted by compiler. - - packCString#, unpackCString, - unpackCString#, - unpackNBytes#, - unpackFoldrCString#, -- (**) - unpackAppendCString#, -- (**) ) where import GHC.Internal.Base -import GHC.Internal.List ( length ) -import GHC.Internal.ST import GHC.Internal.Ptr -data ByteArray ix = ByteArray ix ix ByteArray# -data MutableByteArray s ix = MutableByteArray ix ix (MutableByteArray# s) - unpackCString :: Ptr a -> [Char] unpackCString a@(Ptr addr) | a == nullPtr = [] | otherwise = unpackCString# addr - -packCString# :: [Char] -> ByteArray# -packCString# str = case (packString str) of { ByteArray _ _ bytes -> bytes } - -packString :: [Char] -> ByteArray Int -packString str = runST (packStringST str) - -packStringST :: [Char] -> ST s (ByteArray Int) -packStringST str = - let len = length str in - packNBytesST len str - -packNBytesST :: Int -> [Char] -> ST s (ByteArray Int) -packNBytesST (I# length#) str = - {- - allocate an array that will hold the string - (not forgetting the NUL byte at the end) - -} - new_ps_array (length# +# 1#) >>= \ ch_array -> - -- fill in packed string from "str" - fill_in ch_array 0# str >> - -- freeze the puppy: - freeze_ps_array ch_array length# - where - fill_in :: MutableByteArray s Int -> Int# -> [Char] -> ST s () - fill_in arr_in# idx [] = - write_ps_array arr_in# idx (chr# 0#) >> - return () - - fill_in arr_in# idx (C# c : cs) = - write_ps_array arr_in# idx c >> - fill_in arr_in# (idx +# 1#) cs - --- (Very :-) ``Specialised'' versions of some CharArray things... - -new_ps_array :: Int# -> ST s (MutableByteArray s Int) -write_ps_array :: MutableByteArray s Int -> Int# -> Char# -> ST s () -freeze_ps_array :: MutableByteArray s Int -> Int# -> ST s (ByteArray Int) - -new_ps_array size = ST $ \ s -> - case (newByteArray# size s) of { (# s2#, barr# #) -> - (# s2#, MutableByteArray bot bot barr# #) } - where - bot = errorWithoutStackTrace "new_ps_array" - -write_ps_array (MutableByteArray _ _ barr#) n ch = ST $ \ s# -> - case writeCharArray# barr# n ch s# of { s2# -> - (# s2#, () #) } - --- same as unsafeFreezeByteArray -freeze_ps_array (MutableByteArray _ _ arr#) len# = ST $ \ s# -> - case unsafeFreezeByteArray# arr# s# of { (# s2#, frozen# #) -> - (# s2#, ByteArray 0 (I# len#) frozen# #) } ===================================== testsuite/tests/ghci/should_run/Makefile ===================================== @@ -7,3 +7,9 @@ T3171: echo "do Control.Concurrent.threadDelay 3000000; putStrLn \"threadDelay was not interrupted\"" | \ "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) & \ sleep 2; kill -INT $$!; wait + +TopEnvIface: + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface + # Second compilation starts from interface files, but still can print "a" + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface + ===================================== testsuite/tests/ghci/should_run/TopEnvIface.hs ===================================== @@ -0,0 +1,4 @@ +module TopEnvIface where + +import TopEnvIface2 + ===================================== testsuite/tests/ghci/should_run/TopEnvIface.stdout ===================================== @@ -0,0 +1,8 @@ +[1 of 2] Compiling TopEnvIface2 ( TopEnvIface2.hs, interpreted ) +[2 of 2] Compiling TopEnvIface ( TopEnvIface.hs, interpreted ) +Ok, two modules loaded. +"I should be printed twice" +Leaving GHCi. +Ok, two modules loaded. +"I should be printed twice" +Leaving GHCi. ===================================== testsuite/tests/ghci/should_run/TopEnvIface2.hs ===================================== @@ -0,0 +1,3 @@ +module TopEnvIface2 where + +a = "I should be printed twice" ===================================== testsuite/tests/ghci/should_run/all.T ===================================== @@ -96,3 +96,4 @@ test('LargeBCO', [extra_files(['LargeBCO_A.hs']), req_interp, extra_hc_opts("-O test('T24115', just_ghci + [extra_run_opts("-e ':add T24115.hs'")], ghci_script, ['T24115.script']) test('T10920', [only_ways(ghci_ways), extra_files(['LocalPrelude/Prelude.hs'])], ghci_script, ['T10920.script']) +test('TopEnvIface', [only_ways(ghci_ways)], makefile_test, []) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3ac8222607ba91e0de2eb22577b3c491d20b818b...6e0710bcbccb97b2555c6664bcfaed9aeac636a0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3ac8222607ba91e0de2eb22577b3c491d20b818b...6e0710bcbccb97b2555c6664bcfaed9aeac636a0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/99616552/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 22:34:57 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 03 Mar 2025 17:34:57 -0500 Subject: [Git][ghc/ghc][wip/az/sync-ghc-exactprint] 5 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67c62e913b4dc_2eef5d7518cc182cb@gitlab.mail> Alan Zimmerman pushed to branch wip/az/sync-ghc-exactprint at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - 8d6bbd8d by Alan Zimmerman at 2025-03-03T22:34:41+00:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - b89deb21 by Alan Zimmerman at 2025-03-03T22:34:41+00:00 Apply 1 suggestion(s) to 1 file(s) Co-authored-by: Brandon S. Allbery <allbery.b at gmail.com> - - - - - 9 changed files: - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs Changes: ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -18,7 +18,7 @@ module GHC.Runtime.Eval ( abandon, abandonAll, getResumeContext, getHistorySpan, - getModBreaks, + getModBreaks, readModBreaks, getHistoryModule, setupBreakpoint, back, forward, @@ -130,14 +130,12 @@ import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) import GHC.IfaceToCore import Control.Monad -import Control.Monad.Catch as MC import Data.Array import Data.Dynamic import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.List (find,intercalate) import Data.List.NonEmpty (NonEmpty) -import System.Directory import Unsafe.Coerce ( unsafeCoerce ) import qualified GHC.Unit.Home.Graph as HUG @@ -156,9 +154,8 @@ getHistoryModule = ibi_tick_mod . historyBreakpointId getHistorySpan :: HscEnv -> History -> IO SrcSpan getHistorySpan hsc_env hist = do let ibi = historyBreakpointId hist - HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) >>= pure . \case - Just hmi -> modBreaks_locs (getModBreaks hmi) ! ibi_tick_index ibi - _ -> panic "getHistorySpan" + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi {- | Finds the enclosing top level function name -} -- ToDo: a better way to do this would be to keep hold of the decl_path computed @@ -166,9 +163,8 @@ getHistorySpan hsc_env hist = do -- for each tick. findEnclosingDecls :: HscEnv -> InternalBreakpointId -> IO [String] findEnclosingDecls hsc_env ibi = do - hmi <- expectJust <$> HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) - return $ - modBreaks_decls (getModBreaks hmi) ! ibi_tick_index ibi + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_decls brks ! ibi_tick_index ibi -- | Update fixity environment in the current interactive context. updateFixityEnv :: GhcMonad m => FixityEnv -> m () @@ -232,10 +228,9 @@ execStmt' stmt stmt_text ExecOptions{..} = do updateFixityEnv fix_env status <- - withVirtualCWD $ - liftIO $ do - let eval_opts = initEvalOpts idflags' (isStep execSingleStep) - evalStmt interp eval_opts (execWrap hval) + liftIO $ do + let eval_opts = initEvalOpts idflags' (enableGhcStepMode execSingleStep) + evalStmt interp eval_opts (execWrap hval) let ic = hsc_IC hsc_env bindings = (ic_tythings ic, ic_gre_cache ic) @@ -282,38 +277,17 @@ them. The relevant predicate is OccName.isDerivedOccName. See #11051 for more background and examples. -} -withVirtualCWD :: GhcMonad m => m a -> m a -withVirtualCWD m = do - hsc_env <- getSession - - -- a virtual CWD is only necessary when we're running interpreted code in - -- the same process as the compiler. - case interpInstance <$> hsc_interp hsc_env of - Just (ExternalInterp {}) -> m - _ -> do - let ic = hsc_IC hsc_env - let set_cwd = do - dir <- liftIO $ getCurrentDirectory - case ic_cwd ic of - Just dir -> liftIO $ setCurrentDirectory dir - Nothing -> return () - return dir - - reset_cwd orig_dir = do - virt_dir <- liftIO $ getCurrentDirectory - hsc_env <- getSession - let old_IC = hsc_IC hsc_env - setSession hsc_env{ hsc_IC = old_IC{ ic_cwd = Just virt_dir } } - liftIO $ setCurrentDirectory orig_dir - - MC.bracket set_cwd reset_cwd $ \_ -> m - parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) parseImportDecl expr = withSession $ \hsc_env -> liftIO $ hscImport hsc_env expr emptyHistory :: Int -> BoundedList History emptyHistory size = nilBL size +-- | Turn an 'EvalStatus_' result from interpreting Haskell into a GHCi 'ExecResult'. +-- +-- This function is responsible for resuming execution at an intermediate +-- breakpoint if we don't care about that breakpoint (e.g. if using :steplocal +-- or :stepmodule, rather than :step, we only care about certain breakpoints). handleRunStatus :: GhcMonad m => SingleStep -> String -> ResumeBindings @@ -322,92 +296,107 @@ handleRunStatus :: GhcMonad m -> BoundedList History -> m ExecResult -handleRunStatus step expr bindings final_ids status history0 - | RunAndLogSteps <- step = tracing - | otherwise = not_tracing - where - tracing - | EvalBreak apStack_ref (Just eval_break) resume_ctxt _ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - let dflags = hsc_dflags hsc_env - ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break - hmi <- liftIO $ expectJust <$> - lookupHpt (hsc_HPT hsc_env) (moduleName (ibi_tick_mod ibi)) - let breaks = getModBreaks hmi - - b <- liftIO $ - breakpointStatus interp (modBreaks_flags breaks) (ibi_tick_index ibi) - if b - then not_tracing - -- This breakpoint is explicitly enabled; we want to stop - -- instead of just logging it. - else do - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi - let !history' = history1 `consBL` history0 - -- history is strict, otherwise our BoundedList is pointless. - fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - let eval_opts = initEvalOpts dflags True - status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv - handleRunStatus RunAndLogSteps expr bindings final_ids - status history' - | otherwise - = not_tracing - - not_tracing - -- Hit a breakpoint - | EvalBreak apStack_ref maybe_break resume_ctxt ccs <- status - = do - hsc_env <- getSession - let interp = hscInterp hsc_env - resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt - apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref - ibi <- case maybe_break of - Nothing -> pure Nothing - Just break -> fmap Just $ liftIO $ - evalBreakpointToId (hsc_HPT hsc_env) break - (hsc_env1, names, span, decl) <- liftIO $ - bindLocalsAtBreakpoint hsc_env apStack_fhv ibi - let - resume = Resume - { resumeStmt = expr - , resumeContext = resume_ctxt_fhv - , resumeBindings = bindings - , resumeFinalIds = final_ids - , resumeApStack = apStack_fhv - , resumeBreakpointId = ibi - , resumeSpan = span - , resumeHistory = toListBL history0 - , resumeDecl = decl - , resumeCCS = ccs - , resumeHistoryIx = 0 - } - hsc_env2 = pushResume hsc_env1 resume - - setSession hsc_env2 - return (ExecBreak names ibi) +handleRunStatus step expr bindings final_ids status history0 = do + hsc_env <- getSession + let + interp = hscInterp hsc_env + dflags = hsc_dflags hsc_env + case status of -- Completed successfully - | EvalComplete allocs (EvalSuccess hvals) <- status - = do hsc_env <- getSession - let final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids - final_names = map getName final_ids - interp = hscInterp hsc_env - liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) - hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} - setSession hsc_env' - return (ExecComplete (Right final_names) allocs) + EvalComplete allocs (EvalSuccess hvals) -> do + let + final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids + final_names = map getName final_ids + liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals) + hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic} + setSession hsc_env' + return (ExecComplete (Right final_names) allocs) -- Completed with an exception - | EvalComplete alloc (EvalException e) <- status - = return (ExecComplete (Left (fromSerializableException e)) alloc) - + EvalComplete alloc (EvalException e) -> + return (ExecComplete (Left (fromSerializableException e)) alloc) + + -- Nothing case: we stopped when an exception was raised, not at a breakpoint. + EvalBreak apStack_ref Nothing resume_ctxt ccs -> do + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + let span = mkGeneralSrcSpan (fsLit "<unknown>") + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span Nothing + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Nothing + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = "<exception thrown>" + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + + setSession hsc_env2 + return (ExecBreak names Nothing) + + -- Just case: we stopped at a breakpoint + EvalBreak apStack_ref (Just eval_break) resume_ctxt ccs -> do + ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break + tick_brks <- liftIO $ readModBreaks hsc_env (ibi_tick_mod ibi) + let + span = modBreaks_locs tick_brks ! ibi_tick_index ibi + decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi + + b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi) + + apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref + resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt + + -- This breakpoint is explicitly enabled; we want to stop + -- instead of just logging it. + if b || breakHere step span then do + -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break. + -- Specifically, for :steplocal or :stepmodule, don't return control + -- and simply resume execution from here until we hit a breakpoint we do want to stop at. + (hsc_env1, names) <- liftIO $ + bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) + let + resume = Resume + { resumeStmt = expr + , resumeContext = resume_ctxt_fhv + , resumeBindings = bindings + , resumeFinalIds = final_ids + , resumeApStack = apStack_fhv + , resumeBreakpointId = Just ibi + , resumeSpan = span + , resumeHistory = toListBL history0 + , resumeDecl = decl + , resumeCCS = ccs + , resumeHistoryIx = 0 + } + hsc_env2 = pushResume hsc_env1 resume + setSession hsc_env2 + return (ExecBreak names (Just ibi)) + else do + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) + status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv + history <- if not tracing then pure history0 else do + history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi + let !history' = history1 `consBL` history0 + -- history is strict, otherwise our BoundedList is pointless. + return history' + handleRunStatus step expr bindings final_ids status history + where + tracing | RunAndLogSteps <- step = True + | otherwise = False -resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> Maybe Int +resumeExec :: GhcMonad m => SingleStep -> Maybe Int -> m ExecResult -resumeExec canLogSpan step mbCnt +resumeExec step mbCnt = do hsc_env <- getSession let ic = hsc_IC hsc_env @@ -445,42 +434,41 @@ resumeExec canLogSpan step mbCnt , resumeBreakpointId = mb_brkpt , resumeSpan = span , resumeHistory = hist } -> - withVirtualCWD $ do + do -- When the user specified a break ignore count, set it -- in the interpreter case (mb_brkpt, mbCnt) of (Just brkpt, Just cnt) -> setupBreakpoint hsc_env (toBreakpointId brkpt) cnt _ -> return () - let eval_opts = initEvalOpts dflags (isStep step) + let eval_opts = initEvalOpts dflags (enableGhcStepMode step) status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv let prevHistoryLst = fromListBL 50 hist hist' = case mb_brkpt of Nothing -> pure prevHistoryLst Just bi - | not $ canLogSpan span -> pure prevHistoryLst - | otherwise -> do + | breakHere step span -> do hist1 <- liftIO (mkHistory hsc_env apStack bi) return $ hist1 `consBL` fromListBL 50 hist + | otherwise -> pure prevHistoryLst handleRunStatus step expr bindings final_ids status =<< hist' setupBreakpoint :: GhcMonad m => HscEnv -> BreakpointId -> Int -> m () -- #19157 setupBreakpoint hsc_env bi cnt = do let modl = bi_tick_mod bi - modBreaks <- getModBreaks . expectJust <$> - liftIO (lookupHpt (hsc_HPT hsc_env) (moduleName modl)) + modBreaks <- liftIO $ readModBreaks hsc_env modl let breakarray = modBreaks_flags modBreaks interp = hscInterp hsc_env _ <- liftIO $ GHCi.storeBreakpoint interp breakarray (bi_tick_index bi) cnt pure () -back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) back n = moveHist (+n) -forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String) +forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan) forward n = moveHist (subtract n) -moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan, String) +moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan) moveHist fn = do hsc_env <- getSession case ic_resume (hsc_IC hsc_env) of @@ -498,15 +486,20 @@ moveHist fn = do let update_ic apStack mb_info = do - (hsc_env1, names, span, decl) <- - liftIO $ bindLocalsAtBreakpoint hsc_env apStack mb_info + span <- case mb_info of + Nothing -> return $ mkGeneralSrcSpan (fsLit "<unknown>") + Just ibi -> liftIO $ do + brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + return $ modBreaks_locs brks ! ibi_tick_index ibi + (hsc_env1, names) <- + liftIO $ bindLocalsAtBreakpoint hsc_env apStack span mb_info let ic = hsc_IC hsc_env1 r' = r { resumeHistoryIx = new_ix } ic' = ic { ic_resume = r':rs } setSession hsc_env1{ hsc_IC = ic' } - return (names, new_ix, span, decl) + return (names, new_ix, span) -- careful: we want apStack to be the AP_STACK itself, not a thunk -- around it, hence the cases are carefully constructed below to @@ -527,19 +520,25 @@ moveHist fn = do result_fs :: FastString result_fs = fsLit "_result" +-- | Read the 'ModBreaks' of the given home 'Module' from the 'HomeUnitGraph'. +readModBreaks :: HscEnv -> Module -> IO ModBreaks +readModBreaks hsc_env mod = + getModBreaks . expectJust <$> + HUG.lookupHugByModule mod (hsc_HUG hsc_env) + bindLocalsAtBreakpoint :: HscEnv -> ForeignHValue + -> SrcSpan -> Maybe InternalBreakpointId - -> IO (HscEnv, [Name], SrcSpan, String) + -> IO (HscEnv, [Name]) -- Nothing case: we stopped when an exception was raised, not at a -- breakpoint. We have no location information or local variables to -- bind, all we can do is bind a local variable to the exception -- value. -bindLocalsAtBreakpoint hsc_env apStack Nothing = do +bindLocalsAtBreakpoint hsc_env apStack span Nothing = do let exn_occ = mkVarOccFS (fsLit "_exception") - span = mkGeneralSrcSpan (fsLit "<unknown>") exn_name <- newInteractiveBinder hsc_env exn_occ span let e_fs = fsLit "e" @@ -552,32 +551,21 @@ bindLocalsAtBreakpoint hsc_env apStack Nothing = do interp = hscInterp hsc_env -- Loader.extendLoadedEnv interp [(exn_name, apStack)] - return (hsc_env{ hsc_IC = ictxt1 }, [exn_name], span, "<exception thrown>") + return (hsc_env{ hsc_IC = ictxt1 }, [exn_name]) -- Just case: we stopped at a breakpoint, we have information about the location -- of the breakpoint and the free variables of the expression. -bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do - let - interp = hscInterp hsc_env - - info_mod = ibi_info_mod ibi - info_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName info_mod) - let - info_brks = getModBreaks info_hmi - info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) - - tick_mod = ibi_tick_mod ibi - tick_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName tick_mod) - let - tick_brks = getModBreaks tick_hmi - occs = modBreaks_vars tick_brks ! ibi_tick_index ibi - span = modBreaks_locs tick_brks ! ibi_tick_index ibi - decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi +bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do + info_brks <- readModBreaks hsc_env (ibi_info_mod ibi) + tick_brks <- readModBreaks hsc_env (ibi_tick_mod ibi) + let info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks) + interp = hscInterp hsc_env + occs = modBreaks_vars tick_brks ! ibi_tick_index ibi -- Rehydrate to understand the breakpoint info relative to the current environment. -- This design is critical to preventing leaks (#22530) (mbVars, result_ty) <- initIfaceLoad hsc_env - $ initIfaceLcl info_mod (text "debugger") NotBoot + $ initIfaceLcl (ibi_info_mod ibi) (text "debugger") NotBoot $ hydrateCgBreakInfo info let @@ -624,7 +612,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do Loader.extendLoadedEnv interp (zip names fhvs) when result_ok $ Loader.extendLoadedEnv interp [(result_name, apStack_fhv)] hsc_env1 <- rttiEnvironment hsc_env{ hsc_IC = ictxt1 } - return (hsc_env1, if result_ok then result_name:names else names, span, decl) + return (hsc_env1, if result_ok then result_name:names else names) where -- We need a fresh Unique for each Id we bind, because the linker -- state is single-threaded and otherwise we'd spam old bindings ===================================== compiler/GHC/Runtime/Eval/Types.hs ===================================== @@ -9,7 +9,8 @@ module GHC.Runtime.Eval.Types ( Resume(..), ResumeBindings, IcGlobalRdrEnv(..), History(..), ExecResult(..), - SingleStep(..), isStep, ExecOptions(..) + SingleStep(..), enableGhcStepMode, breakHere, + ExecOptions(..) ) where import GHC.Prelude @@ -35,21 +36,59 @@ data ExecOptions , execWrap :: ForeignHValue -> EvalExpr ForeignHValue } +-- | What kind of stepping are we doing? data SingleStep = RunToCompletion - | SingleStep + + -- | :trace [expr] | RunAndLogSteps -isStep :: SingleStep -> Bool -isStep RunToCompletion = False -isStep _ = True + -- | :step [expr] + | SingleStep + + -- | :steplocal [expr] + | LocalStep + { breakAt :: SrcSpan } + + -- | :stepmodule [expr] + | ModuleStep + { breakAt :: SrcSpan } + +-- | Whether this 'SingleStep' mode requires instructing the interpreter to +-- step at every breakpoint. +enableGhcStepMode :: SingleStep -> Bool +enableGhcStepMode RunToCompletion = False +enableGhcStepMode _ = True + +-- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return +-- @True@ if based on the step-mode alone we should stop at this breakpoint. +-- +-- In particular, this will always be @False@ for @'RunToCompletion'@ and +-- @'RunAndLogSteps'@. We'd need further information e.g. about the user +-- breakpoints to determine whether to break in those modes. +breakHere :: SingleStep -> SrcSpan -> Bool +breakHere step break_span = case step of + RunToCompletion -> False + RunAndLogSteps -> False + SingleStep -> True + LocalStep span -> break_span `isSubspanOf` span + ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span data ExecResult + + -- | Execution is complete = ExecComplete { execResult :: Either SomeException [Name] , execAllocation :: Word64 } - | ExecBreak + + -- | Execution stopped at a breakpoint. + -- + -- Note: `ExecBreak` is only returned by `handleRunStatus` when GHCi should + -- definitely stop at this breakpoint. GHCi is /not/ responsible for + -- subsequently deciding whether to really stop here. + -- `ExecBreak` always means GHCi breaks. + | ExecBreak { breakNames :: [Name] , breakPointId :: Maybe InternalBreakpointId } ===================================== ghc/GHCi/UI.hs ===================================== @@ -1310,7 +1310,7 @@ runStmt input step = do m_result <- GhciMonad.runStmt stmt input step case m_result of Nothing -> return Nothing - Just result -> Just <$> afterRunStmt (const True) result + Just result -> Just <$> afterRunStmt step result -- `x = y` (a declaration) should be treated as `let x = y` (a statement). -- The reason is because GHCi wasn't designed to support `x = y`, but then @@ -1342,7 +1342,7 @@ runStmt input step = do _ <- liftIO $ tryIO $ hFlushAll stdin m_result <- GhciMonad.runDecls' decls forM m_result $ \result -> - afterRunStmt (const True) (GHC.ExecComplete (Right result) 0) + afterRunStmt step (GHC.ExecComplete (Right result) 0) mk_stmt :: SrcSpan -> HsBind GhcPs -> GhciLStmt GhcPs mk_stmt loc bind = @@ -1359,9 +1359,9 @@ runStmt input step = do modStr = moduleNameString $ moduleName $ icInteractiveModule $ ic -- | Clean up the GHCi environment after a statement has run -afterRunStmt :: GhciMonad m - => (SrcSpan -> Bool) -> GHC.ExecResult -> m GHC.ExecResult -afterRunStmt step_here run_result = do +afterRunStmt :: GhciMonad m => SingleStep {-^ Type of step we took just before -} + -> GHC.ExecResult -> m GHC.ExecResult +afterRunStmt step run_result = do resumes <- GHC.getResumeContext case run_result of GHC.ExecComplete{..} -> @@ -1372,9 +1372,7 @@ afterRunStmt step_here run_result = do when show_types $ printTypeOfNames names GHC.ExecBreak names mb_info | first_resume : _ <- resumes - , isNothing mb_info || - step_here (GHC.resumeSpan first_resume) -> do - mb_id_loc <- toBreakIdAndLocation mb_info + -> do mb_id_loc <- toBreakIdAndLocation mb_info let bCmd = maybe "" ( \(_,l) -> onBreakCmd l ) mb_id_loc if (null bCmd) then printStoppedAtBreakInfo first_resume names @@ -1383,8 +1381,9 @@ afterRunStmt step_here run_result = do st <- getGHCiState enqueueCommands [stop st] return () - | otherwise -> resume step_here GHC.SingleStep Nothing >>= - afterRunStmt step_here >> return () + + | otherwise -> resume step Nothing >>= + afterRunStmt step >> return () flushInterpBuffers withSignalHandlers $ do @@ -3810,7 +3809,7 @@ forceCmd = pprintClosureCommand False True stepCmd :: GhciMonad m => String -> m () stepCmd arg = withSandboxOnly ":step" $ step arg where - step [] = doContinue (const True) GHC.SingleStep + step [] = doContinue GHC.SingleStep step expression = runStmt expression GHC.SingleStep >> return () stepLocalCmd :: GhciMonad m => String -> m () @@ -3829,7 +3828,7 @@ stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg Just loc -> do md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule current_toplevel_decl <- enclosingTickSpan md loc - doContinue (`isSubspanOf` RealSrcSpan current_toplevel_decl Strict.Nothing) GHC.SingleStep + doContinue (GHC.LocalStep (RealSrcSpan current_toplevel_decl Strict.Nothing)) stepModuleCmd :: GhciMonad m => String -> m () stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg @@ -3840,9 +3839,7 @@ stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg mb_span <- getCurrentBreakSpan case mb_span of Nothing -> stepCmd [] - Just pan -> do - let f some_span = srcSpanFileName_maybe pan == srcSpanFileName_maybe some_span - doContinue f GHC.SingleStep + Just pan -> doContinue (GHC.ModuleStep pan) -- | Returns the span of the largest tick containing the srcspan given enclosingTickSpan :: GhciMonad m => Module -> SrcSpan -> m RealSrcSpan @@ -3863,14 +3860,14 @@ traceCmd :: GhciMonad m => String -> m () traceCmd arg = withSandboxOnly ":trace" $ tr arg where - tr [] = doContinue (const True) GHC.RunAndLogSteps + tr [] = doContinue GHC.RunAndLogSteps tr expression = runStmt expression GHC.RunAndLogSteps >> return () continueCmd :: GhciMonad m => String -> m () -- #19157 continueCmd argLine = withSandboxOnly ":continue" $ case contSwitch (words argLine) of Left sdoc -> printForUser sdoc - Right mbCnt -> doContinue' (const True) GHC.RunToCompletion mbCnt + Right mbCnt -> doContinue' GHC.RunToCompletion mbCnt where contSwitch :: [String] -> Either SDoc (Maybe Int) contSwitch [ ] = Right Nothing @@ -3878,13 +3875,13 @@ continueCmd argLine = withSandboxOnly ":continue" $ contSwitch _ = Left $ text "After ':continue' only one ignore count is allowed" -doContinue :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> m () -doContinue pre step = doContinue' pre step Nothing +doContinue :: GhciMonad m => SingleStep -> m () +doContinue step = doContinue' step Nothing -doContinue' :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m () -doContinue' pre step mbCnt= do - runResult <- resume pre step mbCnt - _ <- afterRunStmt pre runResult +doContinue' :: GhciMonad m => SingleStep -> Maybe Int -> m () +doContinue' step mbCnt= do + runResult <- resume step mbCnt + _ <- afterRunStmt step runResult return () abandonCmd :: GhciMonad m => String -> m () @@ -4036,7 +4033,7 @@ backCmd arg | otherwise = liftIO $ putStrLn "Syntax: :back [num]" where back num = withSandboxOnly ":back" $ do - (names, _, pan, _) <- GHC.back num + (names, _, pan) <- GHC.back num printForUser $ text "Logged breakpoint at" <+> ppr pan printTypeOfNames names -- run the command set with ":set stop <cmd>" @@ -4050,7 +4047,7 @@ forwardCmd arg | otherwise = liftIO $ putStrLn "Syntax: :forward [num]" where forward num = withSandboxOnly ":forward" $ do - (names, ix, pan, _) <- GHC.forward num + (names, ix, pan) <- GHC.forward num printForUser $ (if (ix == 0) then text "Stopped at" else text "Logged breakpoint at") <+> ppr pan ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -401,14 +401,14 @@ runDecls' decls = do return Nothing) (Just <$> GHC.runParsedDecls decls) -resume :: GhciMonad m => (SrcSpan -> Bool) -> GHC.SingleStep -> Maybe Int -> m GHC.ExecResult -resume canLogSpan step mbIgnoreCnt = do +resume :: GhciMonad m => GHC.SingleStep -> Maybe Int -> m GHC.ExecResult +resume step mbIgnoreCnt = do st <- getGHCiState reifyGHCi $ \x -> withProgName (progname st) $ withArgs (args st) $ reflectGHCi x $ do - GHC.resumeExec canLogSpan step mbIgnoreCnt + GHC.resumeExec step mbIgnoreCnt -- -------------------------------------------------------------------------- -- timing & statistics ===================================== libraries/ghc-internal/src/GHC/Internal/Pack.hs ===================================== @@ -12,95 +12,20 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- ⚠Warning: Starting @base-4.18@, this module is being deprecated. --- See https://gitlab.haskell.org/ghc/ghc/-/issues/21461 for more information. --- --- --- --- This module provides a small set of low-level functions for packing --- and unpacking a chunk of bytes. Used by code emitted by the compiler --- plus the prelude libraries. --- --- The programmer level view of packed strings is provided by a GHC --- system library PackedString. +-- This function is just used by `rts_mkString` -- ----------------------------------------------------------------------------- module GHC.Internal.Pack ( - -- (**) - emitted by compiler. - - packCString#, unpackCString, - unpackCString#, - unpackNBytes#, - unpackFoldrCString#, -- (**) - unpackAppendCString#, -- (**) ) where import GHC.Internal.Base -import GHC.Internal.List ( length ) -import GHC.Internal.ST import GHC.Internal.Ptr -data ByteArray ix = ByteArray ix ix ByteArray# -data MutableByteArray s ix = MutableByteArray ix ix (MutableByteArray# s) - unpackCString :: Ptr a -> [Char] unpackCString a@(Ptr addr) | a == nullPtr = [] | otherwise = unpackCString# addr - -packCString# :: [Char] -> ByteArray# -packCString# str = case (packString str) of { ByteArray _ _ bytes -> bytes } - -packString :: [Char] -> ByteArray Int -packString str = runST (packStringST str) - -packStringST :: [Char] -> ST s (ByteArray Int) -packStringST str = - let len = length str in - packNBytesST len str - -packNBytesST :: Int -> [Char] -> ST s (ByteArray Int) -packNBytesST (I# length#) str = - {- - allocate an array that will hold the string - (not forgetting the NUL byte at the end) - -} - new_ps_array (length# +# 1#) >>= \ ch_array -> - -- fill in packed string from "str" - fill_in ch_array 0# str >> - -- freeze the puppy: - freeze_ps_array ch_array length# - where - fill_in :: MutableByteArray s Int -> Int# -> [Char] -> ST s () - fill_in arr_in# idx [] = - write_ps_array arr_in# idx (chr# 0#) >> - return () - - fill_in arr_in# idx (C# c : cs) = - write_ps_array arr_in# idx c >> - fill_in arr_in# (idx +# 1#) cs - --- (Very :-) ``Specialised'' versions of some CharArray things... - -new_ps_array :: Int# -> ST s (MutableByteArray s Int) -write_ps_array :: MutableByteArray s Int -> Int# -> Char# -> ST s () -freeze_ps_array :: MutableByteArray s Int -> Int# -> ST s (ByteArray Int) - -new_ps_array size = ST $ \ s -> - case (newByteArray# size s) of { (# s2#, barr# #) -> - (# s2#, MutableByteArray bot bot barr# #) } - where - bot = errorWithoutStackTrace "new_ps_array" - -write_ps_array (MutableByteArray _ _ barr#) n ch = ST $ \ s# -> - case writeCharArray# barr# n ch s# of { s2# -> - (# s2#, () #) } - --- same as unsafeFreezeByteArray -freeze_ps_array (MutableByteArray _ _ arr#) len# = ST $ \ s# -> - case unsafeFreezeByteArray# arr# s# of { (# s2#, frozen# #) -> - (# s2#, ByteArray 0 (I# len#) frozen# #) } ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE BlockArguments #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} @@ -7,15 +8,14 @@ {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE StandaloneDeriving #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeSynonymInstances #-} -{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -{-# LANGUAGE BlockArguments #-} +{-# LANGUAGE TypeSynonymInstances #-} +{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE UndecidableInstances #-} -- For the (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ExactPrint instance {-# OPTIONS_GHC -Wno-incomplete-uni-patterns -Wno-incomplete-record-updates #-} @@ -38,6 +38,7 @@ import GHC.Base (NonEmpty(..)) import GHC.Core.Coercion.Axiom (Role(..)) import qualified GHC.Data.BooleanFormula as BF import GHC.Data.FastString +import qualified GHC.Data.Strict as Strict import GHC.TypeLits import GHC.Types.Basic hiding (EP) import GHC.Types.Fixity @@ -106,16 +107,19 @@ runEP epReader action = do defaultEPState :: EPState defaultEPState = EPState - { epPos = (1,1) - , dLHS = 0 - , pMarkLayout = False - , pLHS = 0 - , dMarkLayout = False - , dPriorEndPosition = (1,1) - , uAnchorSpan = badRealSrcSpan + { uAnchorSpan = badRealSrcSpan , uExtraDP = Nothing , uExtraDPReturn = Nothing , pAcceptSpan = False + + , epPos = (1,1) + , pMarkLayout = False + , pLHS = LayoutStartCol 1 + + , dPriorEndPosition = (1,1) + , dMarkLayout = False + , dLHS = LayoutStartCol 1 + , epComments = [] , epCommentsApplied = [] , epEof = Nothing @@ -165,7 +169,7 @@ data EPState = EPState -- Annotation , uExtraDP :: !(Maybe EpaLocation) -- ^ Used to anchor a -- list - , uExtraDPReturn :: !(Maybe DeltaPos) + , uExtraDPReturn :: !(Maybe (SrcSpan, DeltaPos)) -- ^ Used to return Delta version of uExtraDP , pAcceptSpan :: Bool -- ^ When we have processed an -- entry of EpaDelta, accept the @@ -452,7 +456,6 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do -- delta phase variables ----------------------------------- -- Calculate offset required to get to the start of the SrcSPan !off <- getLayoutOffsetD - let spanStart = ss2pos curAnchor priorEndAfterComments <- getPriorEndD let edp' = adjustDeltaForOffset -- Use the propagated offset if one is set @@ -471,7 +474,7 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do Just (EpaDelta _ dp _) -> (dp, Nothing) -- Replace original with desired one. Allows all -- list entry values to be DP (1,0) - Just (EpaSpan (RealSrcSpan r _)) -> (dp, Just dp) + Just (EpaSpan ss@(RealSrcSpan r _)) -> (dp, Just (ss, dp)) where dp = adjustDeltaForOffset off (ss2delta priorEndAfterComments r) @@ -480,6 +483,7 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do when (isJust medr) $ setExtraDPReturn medr -- --------------------------------------------- -- Preparation complete, perform the action + let spanStart = ss2pos curAnchor when (priorEndAfterComments < spanStart) (do debugM $ "enterAnn.dPriorEndPosition:spanStart=" ++ show spanStart modify (\s -> s { dPriorEndPosition = spanStart } )) @@ -512,8 +516,8 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do Just (pos, prior) -> do let dp = if pos == prior then (DifferentLine 1 0) - else origDelta pos prior - debugM $ "EOF:(pos,posEnd,prior,dp) =" ++ showGhc (ss2pos pos, ss2posEnd pos, ss2pos prior, dp) + else adjustDeltaForOffset off (origDelta pos prior) + debugM $ "EOF:(pos,posend,prior,off,dp) =" ++ show (ss2pos pos, ss2posEnd pos, ss2pos prior, off, dp) printStringAtLsDelta dp "" setEofPos Nothing -- Only do this once @@ -542,12 +546,13 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do return after else return [] !trailing' <- markTrailing trailing_anns - -- mapM_ printOneComment (concatMap tokComment $ following) addCommentsA following -- Update original anchor, comments based on the printing process -- TODO:AZ: probably need to put something appropriate in instead of noSrcSpan - let newAnchor = EpaDelta noSrcSpan edp [] + let newAnchor = case anchor' of + EpaSpan s -> EpaDelta s edp [] + _ -> EpaDelta noSrcSpan edp [] let r = case canUpdateAnchor of CanUpdateAnchor -> setAnnotationAnchor a' newAnchor trailing' (mkEpaComments priorCs postCs) CanUpdateAnchorOnly -> setAnnotationAnchor a' newAnchor [] emptyComments @@ -695,7 +700,7 @@ printStringAtRsC capture pa str = do debugM $ "printStringAtRsC:p'=" ++ showAst p' debugM $ "printStringAtRsC: (EpaDelta p' [])=" ++ showAst (EpaDelta noSrcSpan p' NoComments) debugM $ "printStringAtRsC: (EpaDelta p' (map comment2LEpaComment cs'))=" ++ showAst (EpaDelta noSrcSpan p' (map comment2LEpaComment cs')) - return (EpaDelta noSrcSpan p' (map comment2LEpaComment cs')) + return (EpaDelta (RealSrcSpan pa Strict.Nothing) p' (map comment2LEpaComment cs')) printStringAtRs' :: (Monad m, Monoid w) => RealSrcSpan -> String -> EP w m () printStringAtRs' pa str = printStringAtRsC NoCaptureComments pa str >> return () @@ -1385,7 +1390,7 @@ printOneComment c@(Comment _str loc _r _mo) = do dp' <- case mep of Just (EpaDelta _ edp _) -> do debugM $ "printOneComment:edp=" ++ show edp - adjustDeltaForOffsetM edp + return edp _ -> return dp -- Start of debug printing LayoutStartCol dOff <- getLayoutOffsetD @@ -1398,28 +1403,10 @@ updateAndApplyComment :: (Monad m, Monoid w) => Comment -> DeltaPos -> EP w m () updateAndApplyComment (Comment str anc pp mo) dp = do applyComment (Comment str anc' pp mo) where - (r,c) = ss2posEnd pp - dp'' = case anc of - EpaDelta _ dp1 _ -> dp1 - EpaSpan (RealSrcSpan la _) -> - if r == 0 - then (ss2delta (r,c+0) la) - else (ss2delta (r,c) la) - EpaSpan (UnhelpfulSpan _) -> SameLine 0 - dp' = case anc of - EpaSpan (RealSrcSpan r1 _) -> - if pp == r1 - then dp - else dp'' - _ -> dp'' - op' = case dp' of - SameLine n -> if n >= 0 - then EpaDelta noSrcSpan dp' NoComments - else EpaDelta noSrcSpan dp NoComments - _ -> EpaDelta noSrcSpan dp' NoComments - anc' = if str == "" && op' == EpaDelta noSrcSpan (SameLine 0) NoComments -- EOF comment - then EpaDelta noSrcSpan dp NoComments - else EpaDelta noSrcSpan dp NoComments + ss = case anc of + EpaSpan ss' -> ss' + _ -> noSrcSpan + anc' = EpaDelta ss dp NoComments -- --------------------------------------------------------------------- @@ -1459,11 +1446,6 @@ commentAllocationIn ss = do markAnnotatedWithLayout :: (Monad m, Monoid w) => ExactPrint ast => ast -> EP w m ast markAnnotatedWithLayout a = setLayoutBoth $ markAnnotated a --- --------------------------------------------------------------------- - -markTopLevelList :: (Monad m, Monoid w) => ExactPrint ast => [ast] -> EP w m [ast] -markTopLevelList ls = mapM (\a -> setLayoutTopLevelP $ markAnnotated a) ls - -- --------------------------------------------------------------------- -- End of utility functions -- --------------------------------------------------------------------- @@ -1540,11 +1522,11 @@ instance ExactPrint (HsModule GhcPs) where an0 <- markLensTok an lam_mod m' <- markAnnotated m - mdeprec' <- setLayoutTopLevelP $ markAnnotated mdeprec + mdeprec' <- markAnnotated mdeprec - mexports' <- setLayoutTopLevelP $ markAnnotated mexports + mexports' <- markAnnotated mexports - an1 <- setLayoutTopLevelP $ markLensTok an0 lam_where + an1 <- markLensTok an0 lam_where return (an1, Just m', mdeprec', mexports') @@ -1595,8 +1577,8 @@ instance ExactPrint HsModuleImpDecls where setAnnotationAnchor mid _anc _ cs = mid { id_cs = priorComments cs ++ getFollowingComments cs } `debug` ("HsModuleImpDecls.setAnnotationAnchor:cs=" ++ showAst cs) exact (HsModuleImpDecls cs imports decls) = do - imports' <- markTopLevelList imports - decls' <- markTopLevelList (filter notDocDecl decls) + imports' <- mapM markAnnotated imports + decls' <- mapM markAnnotated (filter notDocDecl decls) return (HsModuleImpDecls cs imports' decls') @@ -2535,8 +2517,7 @@ instance ExactPrint (HsLocalBinds GhcPs) where setAnnotationAnchor a _ _ _ = a exact (HsValBinds an valbinds) = do - debugM $ "exact HsValBinds: an=" ++ showAst an - an0 <- markLensFun' an lal_rest markEpToken + an0 <- markLensFun' an lal_rest markEpToken -- 'where' case al_anchor $ anns an of Just anc -> do @@ -2548,9 +2529,9 @@ instance ExactPrint (HsLocalBinds GhcPs) where medr <- getExtraDPReturn an2 <- case medr of Nothing -> return an1 - Just dp -> do + Just (ss,dp) -> do setExtraDPReturn Nothing - return $ an1 { anns = (anns an1) { al_anchor = Just (EpaDelta noSrcSpan dp []) }} + return $ an1 { anns = (anns an1) { al_anchor = Just (EpaDelta ss dp []) }} return (HsValBinds an2 valbinds') exact (HsIPBinds an bs) = do @@ -4246,7 +4227,7 @@ printUnicode anc n = do -- TODO: unicode support? "forall" -> if spanLength (epaLocationRealSrcSpan anc) == 1 then "∀" else "forall" s -> s - loc <- printStringAtAAC NoCaptureComments (EpaDelta noSrcSpan (SameLine 0) []) str + loc <- printStringAtAAC NoCaptureComments (EpaDelta (getHasLoc anc) (SameLine 0) []) str case loc of EpaSpan _ -> return anc EpaDelta ss dp [] -> return $ EpaDelta ss dp [] @@ -4901,18 +4882,6 @@ setLayoutBoth k = do , pLHS = oldAnchorOffset} ) k <* reset --- Use 'local', designed for this -setLayoutTopLevelP :: (Monad m, Monoid w) => EP w m a -> EP w m a -setLayoutTopLevelP k = do - debugM $ "setLayoutTopLevelP entered" - oldAnchorOffset <- getLayoutOffsetP - modify (\a -> a { pMarkLayout = False - , pLHS = 0} ) - r <- k - debugM $ "setLayoutTopLevelP:resetting" - setLayoutOffsetP oldAnchorOffset - return r - ------------------------------------------------------------------------ getPosP :: (Monad m, Monoid w) => EP w m Pos @@ -4931,10 +4900,10 @@ setExtraDP md = do debugM $ "setExtraDP:" ++ show md modify (\s -> s {uExtraDP = md}) -getExtraDPReturn :: (Monad m, Monoid w) => EP w m (Maybe DeltaPos) +getExtraDPReturn :: (Monad m, Monoid w) => EP w m (Maybe (SrcSpan, DeltaPos)) getExtraDPReturn = gets uExtraDPReturn -setExtraDPReturn :: (Monad m, Monoid w) => Maybe DeltaPos -> EP w m () +setExtraDPReturn :: (Monad m, Monoid w) => Maybe (SrcSpan, DeltaPos) -> EP w m () setExtraDPReturn md = do debugM $ "setExtraDPReturn:" ++ show md modify (\s -> s {uExtraDPReturn = md}) ===================================== utils/check-exact/Main.hs ===================================== @@ -533,7 +533,7 @@ changeLocalDecls libdir (L l p) = do os' = setEntryDP os (DifferentLine 2 0) let sortKey = captureOrderBinds decls let (EpAnn anc (AnnList (Just _) a b c dd) cs) = van - let van' = (EpAnn anc (AnnList (Just (EpaDelta noSrcSpan (DifferentLine 1 5) [])) a b c dd) cs) + let van' = (EpAnn anc (AnnList (Just (EpaDelta noSrcSpan (DifferentLine 1 4) [])) a b c dd) cs) let binds' = (HsValBinds van' (ValBinds sortKey (decl':oldBinds) (sig':os':oldSigs))) @@ -557,8 +557,8 @@ changeLocalDecls2 libdir (L l p) = do replaceLocalBinds :: LMatch GhcPs (LHsExpr GhcPs) -> Transform (LMatch GhcPs (LHsExpr GhcPs)) replaceLocalBinds (L lm (Match ma mln pats (GRHSs _ rhs EmptyLocalBinds{}))) = do - let anc = (EpaDelta noSrcSpan (DifferentLine 1 3) []) - let anc2 = (EpaDelta noSrcSpan (DifferentLine 1 5) []) + let anc = (EpaDelta noSrcSpan (DifferentLine 1 2) []) + let anc2 = (EpaDelta noSrcSpan (DifferentLine 1 4) []) let an = EpAnn anc (AnnList (Just anc2) ListNone [] @@ -937,13 +937,13 @@ addClassMethod :: Changer addClassMethod libdir lp = do Right sig <- withDynFlags libdir (\df -> parseDecl df "sig" "nn :: Int") Right decl <- withDynFlags libdir (\df -> parseDecl df "decl" "nn = 2") - let decl' = setEntryDP decl (DifferentLine 1 3) - let sig' = setEntryDP sig (DifferentLine 2 3) + let decl' = setEntryDP decl (DifferentLine 1 2) + let sig' = setEntryDP sig (DifferentLine 2 2) let doAddMethod = do let [cd] = hsDecls lp (f1:f2s:f2d:_) = hsDecls cd - f2s' = setEntryDP f2s (DifferentLine 2 3) + f2s' = setEntryDP f2s (DifferentLine 2 2) cd' = replaceDecls cd [f1, sig', decl', f2s', f2d] lp' = replaceDecls lp [cd'] return lp' ===================================== utils/check-exact/Transform.hs ===================================== @@ -258,12 +258,15 @@ setEntryDP (L (EpAnn (EpaSpan ss) an (EpaComments [])) a) dp setEntryDP (L (EpAnn (EpaDelta ss d csd) an cs) a) dp = L (EpAnn (EpaDelta ss d' csd') an cs') a where + -- I suspect we should assume the comments are already in the + -- right place, and just set the entry DP for this case. This + -- avoids surprises from the caller. (d', csd', cs') = case cs of EpaComments (h:t) -> let (dp0,c') = go h in - (dp0, c':t++csd, EpaComments []) + (dp0, csd, EpaComments (c':t)) EpaComments [] -> (dp, csd, cs) EpaCommentsBalanced (h:t) ts -> @@ -299,7 +302,9 @@ setEntryDP (L (EpAnn (EpaSpan ss@(RealSrcSpan r _)) an cs) a) dp line = getDeltaLine delta col = deltaColumn delta edp' = if line == 0 then SameLine col - else DifferentLine line col + else DifferentLine line (col - 1) + -- At the top level the layout offset is 1, adjust for it + -- TODO: what about the layout offset for nested items? edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ epaLocationRealSrcSpan $ getLoc lc), r)) @@ -330,17 +335,23 @@ setEntryDPFromAnchor off (EpaSpan (RealSrcSpan anc _)) ll@(L la _) = setEntryDP -- --------------------------------------------------------------------- --- |Take the annEntryDelta associated with the first item and associate it with the second. --- Also transfer any comments occurring before it. +-- |Take the annEntryDelta associated with the first item and +-- associate it with the second. Also transfer any comments occurring +-- before it. transferEntryDP :: (Typeable t1, Typeable t2) => LocatedAn t1 a -> LocatedAn t2 b -> (LocatedAn t2 b) -transferEntryDP (L (EpAnn anc1 an1 cs1) _) (L (EpAnn _anc2 an2 cs2) b) = +transferEntryDP (L (EpAnn anc1 an1 cs1) _) (L (EpAnn anc2 an2 cs2) b) = + -- Note: the EpaDelta version of an EpaLocation contains the original + -- SrcSpan. We must preserve that. + let anc1' = case (anc1,anc2) of + (EpaDelta _ dp cs, EpaDelta ss2 _ _) -> EpaDelta ss2 dp cs + (_, _) -> anc1 -- Problem: if the original had preceding comments, blindly -- transferring the location is not correct - case priorComments cs1 of - [] -> (L (EpAnn anc1 (combine an1 an2) cs2) b) + in case priorComments cs1 of + [] -> (L (EpAnn anc1' (combine an1 an2) cs2) b) -- TODO: what happens if the receiving side already has comments? - (L _ _:_) -> (L (EpAnn anc1 (combine an1 an2) (cs1 <> cs2)) b) + (L _ _:_) -> (L (EpAnn anc1' (combine an1 an2) (cs1 <> cs2)) b) -- |If a and b are the same type return first arg, else return second @@ -519,7 +530,7 @@ balanceCommentsA la1 la2 = (la1', la2') anc2 = comments an2 (p1,m1,f1) = splitComments (anchorFromLocatedA la1) anc1 - cs1p = priorCommentsDeltas (anchorFromLocatedA la1) p1 + cs1p = priorCommentsDeltas (anchorFromLocatedA la1) p1 -- Split cs1 following comments into those before any -- TrailingAnn's on an1, and any after @@ -1103,8 +1114,8 @@ oldWhereAnnotation (EpAnn anc an cs) ww _oldSpan = an' newWhereAnnotation :: WithWhere -> (EpAnn (AnnList (EpToken "where"))) newWhereAnnotation ww = an where - anc = EpaDelta noSrcSpan (DifferentLine 1 3) [] - anc2 = EpaDelta noSrcSpan (DifferentLine 1 5) [] + anc = EpaDelta noSrcSpan (DifferentLine 1 2) [] + anc2 = EpaDelta noSrcSpan (DifferentLine 1 4) [] w = case ww of WithWhere -> EpTok (EpaDelta noSrcSpan (SameLine 0) []) WithoutWhere -> NoEpTok ===================================== utils/check-exact/Utils.hs ===================================== @@ -141,7 +141,7 @@ undelta (l,_) (DifferentLine dl dc) (LayoutStartCol co) = (fl,fc) -- --------------------------------------------------------------------- adjustDeltaForOffset :: LayoutStartCol -> DeltaPos -> DeltaPos -adjustDeltaForOffset _colOffset dp@(SameLine _) = dp +adjustDeltaForOffset _colOffset dp@(SameLine _) = dp adjustDeltaForOffset (LayoutStartCol colOffset) (DifferentLine l c) = DifferentLine l (c - colOffset) @@ -196,14 +196,17 @@ isPointSrcSpan ss = spanLength ss == 0 -- does not already have one. commentOrigDelta :: LEpaComment -> LEpaComment commentOrigDelta (L (EpaSpan ss@(RealSrcSpan la _)) (GHC.EpaComment t pp)) - = (L (EpaDelta ss dp NoComments) (GHC.EpaComment t pp)) - `debug` ("commentOrigDelta: (la, pp, r,c, dp)=" ++ showAst (la, pp, r,c, dp)) + = (L (EpaDelta ss dp' NoComments) (GHC.EpaComment t pp)) + `debug` ("commentOrigDelta: (la, pp, r,c, dp, dp')=" ++ showAst (la, pp, r,c, dp, dp')) where (r,c) = ss2posEnd pp dp = if r == 0 then (ss2delta (r,c+1) la) else (ss2delta (r,c) la) + dp' = case dp of + SameLine _ -> dp + DifferentLine l cc -> DifferentLine l (cc - 1) commentOrigDelta c = c origDelta :: RealSrcSpan -> RealSrcSpan -> DeltaPos View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/531b275c8b980b03fe7f2085aa3eae694a840741...b89deb214cce933df9ed91d12938f29270798bbf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/531b275c8b980b03fe7f2085aa3eae694a840741...b89deb214cce933df9ed91d12938f29270798bbf You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/4dcc2e47/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 3 22:36:49 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 03 Mar 2025 17:36:49 -0500 Subject: [Git][ghc/ghc][wip/az/sync-ghc-exactprint] [EPA] Sync with the ghc-exactprint repo Message-ID: <67c62f00efbf2_2eef5d7cc6301885a@gitlab.mail> Alan Zimmerman pushed to branch wip/az/sync-ghc-exactprint at Glasgow Haskell Compiler / GHC Commits: 60d75003 by Alan Zimmerman at 2025-03-03T22:36:33+00:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 4 changed files: - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs Changes: ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE BlockArguments #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} @@ -7,15 +8,14 @@ {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE StandaloneDeriving #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeSynonymInstances #-} -{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -{-# LANGUAGE BlockArguments #-} +{-# LANGUAGE TypeSynonymInstances #-} +{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE UndecidableInstances #-} -- For the (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ExactPrint instance {-# OPTIONS_GHC -Wno-incomplete-uni-patterns -Wno-incomplete-record-updates #-} @@ -38,6 +38,7 @@ import GHC.Base (NonEmpty(..)) import GHC.Core.Coercion.Axiom (Role(..)) import qualified GHC.Data.BooleanFormula as BF import GHC.Data.FastString +import qualified GHC.Data.Strict as Strict import GHC.TypeLits import GHC.Types.Basic hiding (EP) import GHC.Types.Fixity @@ -106,16 +107,19 @@ runEP epReader action = do defaultEPState :: EPState defaultEPState = EPState - { epPos = (1,1) - , dLHS = 0 - , pMarkLayout = False - , pLHS = 0 - , dMarkLayout = False - , dPriorEndPosition = (1,1) - , uAnchorSpan = badRealSrcSpan + { uAnchorSpan = badRealSrcSpan , uExtraDP = Nothing , uExtraDPReturn = Nothing , pAcceptSpan = False + + , epPos = (1,1) + , pMarkLayout = False + , pLHS = LayoutStartCol 1 + + , dPriorEndPosition = (1,1) + , dMarkLayout = False + , dLHS = LayoutStartCol 1 + , epComments = [] , epCommentsApplied = [] , epEof = Nothing @@ -165,7 +169,7 @@ data EPState = EPState -- Annotation , uExtraDP :: !(Maybe EpaLocation) -- ^ Used to anchor a -- list - , uExtraDPReturn :: !(Maybe DeltaPos) + , uExtraDPReturn :: !(Maybe (SrcSpan, DeltaPos)) -- ^ Used to return Delta version of uExtraDP , pAcceptSpan :: Bool -- ^ When we have processed an -- entry of EpaDelta, accept the @@ -452,7 +456,6 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do -- delta phase variables ----------------------------------- -- Calculate offset required to get to the start of the SrcSPan !off <- getLayoutOffsetD - let spanStart = ss2pos curAnchor priorEndAfterComments <- getPriorEndD let edp' = adjustDeltaForOffset -- Use the propagated offset if one is set @@ -471,7 +474,7 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do Just (EpaDelta _ dp _) -> (dp, Nothing) -- Replace original with desired one. Allows all -- list entry values to be DP (1,0) - Just (EpaSpan (RealSrcSpan r _)) -> (dp, Just dp) + Just (EpaSpan ss@(RealSrcSpan r _)) -> (dp, Just (ss, dp)) where dp = adjustDeltaForOffset off (ss2delta priorEndAfterComments r) @@ -480,6 +483,7 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do when (isJust medr) $ setExtraDPReturn medr -- --------------------------------------------- -- Preparation complete, perform the action + let spanStart = ss2pos curAnchor when (priorEndAfterComments < spanStart) (do debugM $ "enterAnn.dPriorEndPosition:spanStart=" ++ show spanStart modify (\s -> s { dPriorEndPosition = spanStart } )) @@ -512,8 +516,8 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do Just (pos, prior) -> do let dp = if pos == prior then (DifferentLine 1 0) - else origDelta pos prior - debugM $ "EOF:(pos,posEnd,prior,dp) =" ++ showGhc (ss2pos pos, ss2posEnd pos, ss2pos prior, dp) + else adjustDeltaForOffset off (origDelta pos prior) + debugM $ "EOF:(pos,posend,prior,off,dp) =" ++ show (ss2pos pos, ss2posEnd pos, ss2pos prior, off, dp) printStringAtLsDelta dp "" setEofPos Nothing -- Only do this once @@ -542,12 +546,13 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do return after else return [] !trailing' <- markTrailing trailing_anns - -- mapM_ printOneComment (concatMap tokComment $ following) addCommentsA following -- Update original anchor, comments based on the printing process -- TODO:AZ: probably need to put something appropriate in instead of noSrcSpan - let newAnchor = EpaDelta noSrcSpan edp [] + let newAnchor = case anchor' of + EpaSpan s -> EpaDelta s edp [] + _ -> EpaDelta noSrcSpan edp [] let r = case canUpdateAnchor of CanUpdateAnchor -> setAnnotationAnchor a' newAnchor trailing' (mkEpaComments priorCs postCs) CanUpdateAnchorOnly -> setAnnotationAnchor a' newAnchor [] emptyComments @@ -695,7 +700,7 @@ printStringAtRsC capture pa str = do debugM $ "printStringAtRsC:p'=" ++ showAst p' debugM $ "printStringAtRsC: (EpaDelta p' [])=" ++ showAst (EpaDelta noSrcSpan p' NoComments) debugM $ "printStringAtRsC: (EpaDelta p' (map comment2LEpaComment cs'))=" ++ showAst (EpaDelta noSrcSpan p' (map comment2LEpaComment cs')) - return (EpaDelta noSrcSpan p' (map comment2LEpaComment cs')) + return (EpaDelta (RealSrcSpan pa Strict.Nothing) p' (map comment2LEpaComment cs')) printStringAtRs' :: (Monad m, Monoid w) => RealSrcSpan -> String -> EP w m () printStringAtRs' pa str = printStringAtRsC NoCaptureComments pa str >> return () @@ -1385,7 +1390,7 @@ printOneComment c@(Comment _str loc _r _mo) = do dp' <- case mep of Just (EpaDelta _ edp _) -> do debugM $ "printOneComment:edp=" ++ show edp - adjustDeltaForOffsetM edp + return edp _ -> return dp -- Start of debug printing LayoutStartCol dOff <- getLayoutOffsetD @@ -1398,28 +1403,10 @@ updateAndApplyComment :: (Monad m, Monoid w) => Comment -> DeltaPos -> EP w m () updateAndApplyComment (Comment str anc pp mo) dp = do applyComment (Comment str anc' pp mo) where - (r,c) = ss2posEnd pp - dp'' = case anc of - EpaDelta _ dp1 _ -> dp1 - EpaSpan (RealSrcSpan la _) -> - if r == 0 - then (ss2delta (r,c+0) la) - else (ss2delta (r,c) la) - EpaSpan (UnhelpfulSpan _) -> SameLine 0 - dp' = case anc of - EpaSpan (RealSrcSpan r1 _) -> - if pp == r1 - then dp - else dp'' - _ -> dp'' - op' = case dp' of - SameLine n -> if n >= 0 - then EpaDelta noSrcSpan dp' NoComments - else EpaDelta noSrcSpan dp NoComments - _ -> EpaDelta noSrcSpan dp' NoComments - anc' = if str == "" && op' == EpaDelta noSrcSpan (SameLine 0) NoComments -- EOF comment - then EpaDelta noSrcSpan dp NoComments - else EpaDelta noSrcSpan dp NoComments + ss = case anc of + EpaSpan ss' -> ss' + _ -> noSrcSpan + anc' = EpaDelta ss dp NoComments -- --------------------------------------------------------------------- @@ -1459,11 +1446,6 @@ commentAllocationIn ss = do markAnnotatedWithLayout :: (Monad m, Monoid w) => ExactPrint ast => ast -> EP w m ast markAnnotatedWithLayout a = setLayoutBoth $ markAnnotated a --- --------------------------------------------------------------------- - -markTopLevelList :: (Monad m, Monoid w) => ExactPrint ast => [ast] -> EP w m [ast] -markTopLevelList ls = mapM (\a -> setLayoutTopLevelP $ markAnnotated a) ls - -- --------------------------------------------------------------------- -- End of utility functions -- --------------------------------------------------------------------- @@ -1540,11 +1522,11 @@ instance ExactPrint (HsModule GhcPs) where an0 <- markLensTok an lam_mod m' <- markAnnotated m - mdeprec' <- setLayoutTopLevelP $ markAnnotated mdeprec + mdeprec' <- markAnnotated mdeprec - mexports' <- setLayoutTopLevelP $ markAnnotated mexports + mexports' <- markAnnotated mexports - an1 <- setLayoutTopLevelP $ markLensTok an0 lam_where + an1 <- markLensTok an0 lam_where return (an1, Just m', mdeprec', mexports') @@ -1595,8 +1577,8 @@ instance ExactPrint HsModuleImpDecls where setAnnotationAnchor mid _anc _ cs = mid { id_cs = priorComments cs ++ getFollowingComments cs } `debug` ("HsModuleImpDecls.setAnnotationAnchor:cs=" ++ showAst cs) exact (HsModuleImpDecls cs imports decls) = do - imports' <- markTopLevelList imports - decls' <- markTopLevelList (filter notDocDecl decls) + imports' <- mapM markAnnotated imports + decls' <- mapM markAnnotated (filter notDocDecl decls) return (HsModuleImpDecls cs imports' decls') @@ -2535,8 +2517,7 @@ instance ExactPrint (HsLocalBinds GhcPs) where setAnnotationAnchor a _ _ _ = a exact (HsValBinds an valbinds) = do - debugM $ "exact HsValBinds: an=" ++ showAst an - an0 <- markLensFun' an lal_rest markEpToken + an0 <- markLensFun' an lal_rest markEpToken -- 'where' case al_anchor $ anns an of Just anc -> do @@ -2548,9 +2529,9 @@ instance ExactPrint (HsLocalBinds GhcPs) where medr <- getExtraDPReturn an2 <- case medr of Nothing -> return an1 - Just dp -> do + Just (ss,dp) -> do setExtraDPReturn Nothing - return $ an1 { anns = (anns an1) { al_anchor = Just (EpaDelta noSrcSpan dp []) }} + return $ an1 { anns = (anns an1) { al_anchor = Just (EpaDelta ss dp []) }} return (HsValBinds an2 valbinds') exact (HsIPBinds an bs) = do @@ -4246,7 +4227,7 @@ printUnicode anc n = do -- TODO: unicode support? "forall" -> if spanLength (epaLocationRealSrcSpan anc) == 1 then "∀" else "forall" s -> s - loc <- printStringAtAAC NoCaptureComments (EpaDelta noSrcSpan (SameLine 0) []) str + loc <- printStringAtAAC NoCaptureComments (EpaDelta (getHasLoc anc) (SameLine 0) []) str case loc of EpaSpan _ -> return anc EpaDelta ss dp [] -> return $ EpaDelta ss dp [] @@ -4901,18 +4882,6 @@ setLayoutBoth k = do , pLHS = oldAnchorOffset} ) k <* reset --- Use 'local', designed for this -setLayoutTopLevelP :: (Monad m, Monoid w) => EP w m a -> EP w m a -setLayoutTopLevelP k = do - debugM $ "setLayoutTopLevelP entered" - oldAnchorOffset <- getLayoutOffsetP - modify (\a -> a { pMarkLayout = False - , pLHS = 0} ) - r <- k - debugM $ "setLayoutTopLevelP:resetting" - setLayoutOffsetP oldAnchorOffset - return r - ------------------------------------------------------------------------ getPosP :: (Monad m, Monoid w) => EP w m Pos @@ -4931,10 +4900,10 @@ setExtraDP md = do debugM $ "setExtraDP:" ++ show md modify (\s -> s {uExtraDP = md}) -getExtraDPReturn :: (Monad m, Monoid w) => EP w m (Maybe DeltaPos) +getExtraDPReturn :: (Monad m, Monoid w) => EP w m (Maybe (SrcSpan, DeltaPos)) getExtraDPReturn = gets uExtraDPReturn -setExtraDPReturn :: (Monad m, Monoid w) => Maybe DeltaPos -> EP w m () +setExtraDPReturn :: (Monad m, Monoid w) => Maybe (SrcSpan, DeltaPos) -> EP w m () setExtraDPReturn md = do debugM $ "setExtraDPReturn:" ++ show md modify (\s -> s {uExtraDPReturn = md}) ===================================== utils/check-exact/Main.hs ===================================== @@ -533,7 +533,7 @@ changeLocalDecls libdir (L l p) = do os' = setEntryDP os (DifferentLine 2 0) let sortKey = captureOrderBinds decls let (EpAnn anc (AnnList (Just _) a b c dd) cs) = van - let van' = (EpAnn anc (AnnList (Just (EpaDelta noSrcSpan (DifferentLine 1 5) [])) a b c dd) cs) + let van' = (EpAnn anc (AnnList (Just (EpaDelta noSrcSpan (DifferentLine 1 4) [])) a b c dd) cs) let binds' = (HsValBinds van' (ValBinds sortKey (decl':oldBinds) (sig':os':oldSigs))) @@ -557,8 +557,8 @@ changeLocalDecls2 libdir (L l p) = do replaceLocalBinds :: LMatch GhcPs (LHsExpr GhcPs) -> Transform (LMatch GhcPs (LHsExpr GhcPs)) replaceLocalBinds (L lm (Match ma mln pats (GRHSs _ rhs EmptyLocalBinds{}))) = do - let anc = (EpaDelta noSrcSpan (DifferentLine 1 3) []) - let anc2 = (EpaDelta noSrcSpan (DifferentLine 1 5) []) + let anc = (EpaDelta noSrcSpan (DifferentLine 1 2) []) + let anc2 = (EpaDelta noSrcSpan (DifferentLine 1 4) []) let an = EpAnn anc (AnnList (Just anc2) ListNone [] @@ -937,13 +937,13 @@ addClassMethod :: Changer addClassMethod libdir lp = do Right sig <- withDynFlags libdir (\df -> parseDecl df "sig" "nn :: Int") Right decl <- withDynFlags libdir (\df -> parseDecl df "decl" "nn = 2") - let decl' = setEntryDP decl (DifferentLine 1 3) - let sig' = setEntryDP sig (DifferentLine 2 3) + let decl' = setEntryDP decl (DifferentLine 1 2) + let sig' = setEntryDP sig (DifferentLine 2 2) let doAddMethod = do let [cd] = hsDecls lp (f1:f2s:f2d:_) = hsDecls cd - f2s' = setEntryDP f2s (DifferentLine 2 3) + f2s' = setEntryDP f2s (DifferentLine 2 2) cd' = replaceDecls cd [f1, sig', decl', f2s', f2d] lp' = replaceDecls lp [cd'] return lp' ===================================== utils/check-exact/Transform.hs ===================================== @@ -258,12 +258,15 @@ setEntryDP (L (EpAnn (EpaSpan ss) an (EpaComments [])) a) dp setEntryDP (L (EpAnn (EpaDelta ss d csd) an cs) a) dp = L (EpAnn (EpaDelta ss d' csd') an cs') a where + -- I suspect we should assume the comments are already in the + -- right place, and just set the entry DP for this case. This + -- avoids surprises from the caller. (d', csd', cs') = case cs of EpaComments (h:t) -> let (dp0,c') = go h in - (dp0, c':t++csd, EpaComments []) + (dp0, csd, EpaComments (c':t)) EpaComments [] -> (dp, csd, cs) EpaCommentsBalanced (h:t) ts -> @@ -299,7 +302,9 @@ setEntryDP (L (EpAnn (EpaSpan ss@(RealSrcSpan r _)) an cs) a) dp line = getDeltaLine delta col = deltaColumn delta edp' = if line == 0 then SameLine col - else DifferentLine line col + else DifferentLine line (col - 1) + -- At the top level the layout offset is 1, adjust for it + -- TODO: what about the layout offset for nested items? edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ epaLocationRealSrcSpan $ getLoc lc), r)) @@ -330,17 +335,23 @@ setEntryDPFromAnchor off (EpaSpan (RealSrcSpan anc _)) ll@(L la _) = setEntryDP -- --------------------------------------------------------------------- --- |Take the annEntryDelta associated with the first item and associate it with the second. --- Also transfer any comments occurring before it. +-- |Take the annEntryDelta associated with the first item and +-- associate it with the second. Also transfer any comments occurring +-- before it. transferEntryDP :: (Typeable t1, Typeable t2) => LocatedAn t1 a -> LocatedAn t2 b -> (LocatedAn t2 b) -transferEntryDP (L (EpAnn anc1 an1 cs1) _) (L (EpAnn _anc2 an2 cs2) b) = +transferEntryDP (L (EpAnn anc1 an1 cs1) _) (L (EpAnn anc2 an2 cs2) b) = + -- Note: the EpaDelta version of an EpaLocation contains the original + -- SrcSpan. We must preserve that. + let anc1' = case (anc1,anc2) of + (EpaDelta _ dp cs, EpaDelta ss2 _ _) -> EpaDelta ss2 dp cs + (_, _) -> anc1 -- Problem: if the original had preceding comments, blindly -- transferring the location is not correct - case priorComments cs1 of - [] -> (L (EpAnn anc1 (combine an1 an2) cs2) b) + in case priorComments cs1 of + [] -> (L (EpAnn anc1' (combine an1 an2) cs2) b) -- TODO: what happens if the receiving side already has comments? - (L _ _:_) -> (L (EpAnn anc1 (combine an1 an2) (cs1 <> cs2)) b) + (L _ _:_) -> (L (EpAnn anc1' (combine an1 an2) (cs1 <> cs2)) b) -- |If a and b are the same type return first arg, else return second @@ -519,7 +530,7 @@ balanceCommentsA la1 la2 = (la1', la2') anc2 = comments an2 (p1,m1,f1) = splitComments (anchorFromLocatedA la1) anc1 - cs1p = priorCommentsDeltas (anchorFromLocatedA la1) p1 + cs1p = priorCommentsDeltas (anchorFromLocatedA la1) p1 -- Split cs1 following comments into those before any -- TrailingAnn's on an1, and any after @@ -1103,8 +1114,8 @@ oldWhereAnnotation (EpAnn anc an cs) ww _oldSpan = an' newWhereAnnotation :: WithWhere -> (EpAnn (AnnList (EpToken "where"))) newWhereAnnotation ww = an where - anc = EpaDelta noSrcSpan (DifferentLine 1 3) [] - anc2 = EpaDelta noSrcSpan (DifferentLine 1 5) [] + anc = EpaDelta noSrcSpan (DifferentLine 1 2) [] + anc2 = EpaDelta noSrcSpan (DifferentLine 1 4) [] w = case ww of WithWhere -> EpTok (EpaDelta noSrcSpan (SameLine 0) []) WithoutWhere -> NoEpTok ===================================== utils/check-exact/Utils.hs ===================================== @@ -141,7 +141,7 @@ undelta (l,_) (DifferentLine dl dc) (LayoutStartCol co) = (fl,fc) -- --------------------------------------------------------------------- adjustDeltaForOffset :: LayoutStartCol -> DeltaPos -> DeltaPos -adjustDeltaForOffset _colOffset dp@(SameLine _) = dp +adjustDeltaForOffset _colOffset dp@(SameLine _) = dp adjustDeltaForOffset (LayoutStartCol colOffset) (DifferentLine l c) = DifferentLine l (c - colOffset) @@ -196,14 +196,17 @@ isPointSrcSpan ss = spanLength ss == 0 -- does not already have one. commentOrigDelta :: LEpaComment -> LEpaComment commentOrigDelta (L (EpaSpan ss@(RealSrcSpan la _)) (GHC.EpaComment t pp)) - = (L (EpaDelta ss dp NoComments) (GHC.EpaComment t pp)) - `debug` ("commentOrigDelta: (la, pp, r,c, dp)=" ++ showAst (la, pp, r,c, dp)) + = (L (EpaDelta ss dp' NoComments) (GHC.EpaComment t pp)) + `debug` ("commentOrigDelta: (la, pp, r,c, dp, dp')=" ++ showAst (la, pp, r,c, dp, dp')) where (r,c) = ss2posEnd pp dp = if r == 0 then (ss2delta (r,c+1) la) else (ss2delta (r,c) la) + dp' = case dp of + SameLine _ -> dp + DifferentLine l cc -> DifferentLine l (cc - 1) commentOrigDelta c = c origDelta :: RealSrcSpan -> RealSrcSpan -> DeltaPos View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60d75003576e087facee408c6884decd4afb2cba -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60d75003576e087facee408c6884decd4afb2cba You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/e6629216/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 02:07:15 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Mon, 03 Mar 2025 21:07:15 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/int-index/vdq-emptycase-errmsg Message-ID: <67c660533c304_3349789fa13c93548@gitlab.mail> Vladislav Zavialov pushed new branch wip/int-index/vdq-emptycase-errmsg at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/int-index/vdq-emptycase-errmsg You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/d55aad02/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 4 02:07:44 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Mon, 03 Mar 2025 21:07:44 -0500 Subject: [Git][ghc/ghc][wip/int-index/vdq-emptycase-errmsg] Error message with EmptyCase and RequiredTypeArguments (#25004) Message-ID: <67c66070fbb0_3349789c3bdc9379a@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/vdq-emptycase-errmsg at Glasgow Haskell Compiler / GHC Commits: 177148f7 by Vladislav Zavialov at 2025-03-04T05:07:27+03:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * XMG GhcRn now carries HsMatchContextRn, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 16 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -1538,10 +1538,16 @@ instance (OutputableBndrId p) => Outputable (HsCmdTop (GhcPass p)) where ************************************************************************ -} -type instance XMG GhcPs b = Origin -type instance XMG GhcRn b = Origin -- See Note [Generated code and pattern-match checking] +type instance XMG GhcPs b = Origin -- See Note [Generated code and pattern-match checking] +type instance XMG GhcRn b = MatchGroupRn type instance XMG GhcTc b = MatchGroupTc +data MatchGroupRn + = MatchGroupRn + { mg_rn_ctxt :: HsMatchContextRn + , mg_rn_origin :: Origin -- Origin (Generated vs FromSource) + } + data MatchGroupTc = MatchGroupTc { mg_arg_tys :: [Scaled Type] -- Types of the arguments, t1..tn ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -400,6 +400,8 @@ deriving instance Data HsArrowMatchContext deriving instance Data fn => Data (HsStmtContext fn) deriving instance Data fn => Data (HsMatchContext fn) +deriving instance Data MatchGroupRn + -- deriving instance (DataIdLR p p) => Data (HsUntypedSplice p) deriving instance Data (HsUntypedSplice GhcPs) deriving instance Data (HsUntypedSplice GhcRn) ===================================== compiler/GHC/Hs/Utils.hs ===================================== @@ -268,14 +268,18 @@ mkHsAppType e t = addCLocA t_body e (HsAppType noExtField e paren_wct) mkHsAppTypes :: LHsExpr GhcRn -> [LHsWcType GhcRn] -> LHsExpr GhcRn mkHsAppTypes = foldl' mkHsAppType -mkHsLam :: (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ Origin) +mkHsLam :: forall p. (IsPass p, p ~ NoGhcTcPass p) => LocatedE [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) mkHsLam (L l pats) body = mkHsPar (L (getLoc body) (HsLam noAnn LamSingle matches)) where - matches = mkMatchGroup (Generated OtherExpansion SkipPmc) - (noLocA [mkSimpleMatch (LamAlt LamSingle) (L l pats') body]) + ctxt = LamAlt LamSingle + origin = Generated OtherExpansion SkipPmc + mg_ext = case ghcPass @p of + GhcPs -> origin + GhcRn -> MatchGroupRn ctxt origin + matches = MG { mg_ext, mg_alts = noLocA [mkSimpleMatch ctxt (L l pats') body] } pats' = map (parenthesizePat appPrec) pats mkHsLams :: [TyVar] -> [EvVar] -> LHsExpr GhcTc -> LHsExpr GhcTc @@ -837,7 +841,8 @@ mkTopFunBind :: Origin -> LocatedN Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn -- ^ In Name-land, with empty bind_fvs mkTopFunBind origin fn ms = FunBind { fun_id = fn - , fun_matches = mkMatchGroup origin (noLocA ms) + , fun_matches = MG { mg_ext = MatchGroupRn (mkPrefixFunRhs fn noAnn) origin + , mg_alts = noLocA ms } , fun_ext = emptyNameSet -- NB: closed -- binding } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -910,7 +910,7 @@ instance ( HiePass p , toHie alts ] where origin = case hiePass @p of - HieRn -> mg_ext mg + HieRn -> mg_rn_origin $ mg_ext mg HieTc -> mg_origin $ mg_ext mg setOrigin :: Origin -> NodeOrigin -> NodeOrigin ===================================== compiler/GHC/Rename/Bind.hs ===================================== @@ -1323,14 +1323,24 @@ rnMatchGroup :: (Outputable (body GhcPs), AnnoBody body) => HsMatchContextRn -> RnM (MatchGroup GhcRn (LocatedA (body GhcRn)), FreeVars) rnMatchGroup ctxt rnBody (MG { mg_alts = L lm ms, mg_ext = origin }) -- see Note [Empty MatchGroups] - = do { whenM ((null ms &&) <$> mustn't_be_empty) (addErr (TcRnEmptyCase ctxt)) + = do { when (null ms) $ checkEmptyCase ctxt ; (new_ms, ms_fvs) <- mapFvRn (rnMatch ctxt rnBody) ms - ; return (mkMatchGroup origin (L lm new_ms), ms_fvs) } + ; return (MG { mg_ext = MatchGroupRn ctxt origin + , mg_alts = L lm new_ms }, ms_fvs) } + +checkEmptyCase :: HsMatchContextRn -> RnM () +checkEmptyCase ctxt + | disallowed_ctxt = + addErr (TcRnEmptyCase ctxt EmptyCaseDisallowedCtxt) + | otherwise = + unlessXOptM LangExt.EmptyCase $ + addErr (TcRnEmptyCase ctxt EmptyCaseWithoutFlag) where - mustn't_be_empty = case ctxt of - LamAlt LamCases -> return True - ArrowMatchCtxt (ArrowLamAlt LamCases) -> return True - _ -> not <$> xoptM LangExt.EmptyCase + disallowed_ctxt = + case ctxt of + LamAlt LamCases -> True + ArrowMatchCtxt (ArrowLamAlt LamCases) -> True + _ -> False rnMatch :: AnnoBody body => HsMatchContextRn ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -770,22 +770,30 @@ genFunBind :: LocatedN Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn genFunBind fn ms = FunBind { fun_id = fn - , fun_matches = mkMatchGroup (Generated OtherExpansion SkipPmc) (wrapGenSpan ms) + , fun_matches = MG { mg_ext = MatchGroupRn ctxt origin + , mg_alts = wrapGenSpan ms } , fun_ext = emptyNameSet } + where + ctxt = mkPrefixFunRhs fn noAnn + origin = Generated OtherExpansion SkipPmc genHsLet :: HsLocalBindsLR GhcRn GhcRn -> LHsExpr GhcRn -> HsExpr GhcRn genHsLet bindings body = HsLet noExtField bindings body -genHsLamDoExp :: (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ Origin) +genHsLamDoExp :: forall p. (IsPass p, p ~ NoGhcTcPass p) => HsDoFlavour -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) genHsLamDoExp doFlav pats body = mkHsPar (wrapGenSpan $ HsLam noAnn LamSingle matches) where - matches = mkMatchGroup (doExpansionOrigin doFlav) - (wrapGenSpan [genSimpleMatch (StmtCtxt (HsDoStmt doFlav)) pats' body]) + ctxt = StmtCtxt (HsDoStmt doFlav) + origin = doExpansionOrigin doFlav + mg_ext = case ghcPass @p of + GhcPs -> origin + GhcRn -> MatchGroupRn ctxt origin + matches = MG { mg_ext, mg_alts = wrapGenSpan [genSimpleMatch ctxt pats' body] } pats' = map (parenthesizePat appPrec) pats ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -62,7 +62,7 @@ import GHC.Core.FamInstEnv ( FamInst(..), famInstAxiom, pprFamInst ) import GHC.Core.InstEnv import GHC.Core.TyCo.Rep (Type(..)) import GHC.Core.TyCo.Ppr (pprWithInvisibleBitsWhen, pprSourceTyCon, - pprTyVars, pprWithTYPE, pprTyVar, pprTidiedType) + pprTyVars, pprWithTYPE, pprTyVar, pprTidiedType, pprForAll) import GHC.Core.PatSyn ( patSynName, pprPatSynType ) import GHC.Core.Predicate import GHC.Core.Type @@ -1359,24 +1359,27 @@ instance Diagnostic TcRnMessage where text "Orphan COMPLETE pragmas not supported" $$ text "A COMPLETE pragma must mention at least one data constructor" $$ text "or pattern synonym defined in the same module." - TcRnEmptyCase ctxt -> mkSimpleDecorated message - where - pp_ctxt = case ctxt of - CaseAlt -> text "case expression" - LamAlt LamCase -> text "\\case expression" - ArrowMatchCtxt (ArrowLamAlt LamSingle) -> text "kappa abstraction" - ArrowMatchCtxt (ArrowLamAlt LamCase) -> text "\\case command" - ArrowMatchCtxt ArrowCaseAlt -> text "case command" - _ -> text "(unexpected)" - <+> pprMatchContextNoun ctxt - - message = case ctxt of - LamAlt LamCases -> lcases_msg <+> text "expression" - ArrowMatchCtxt (ArrowLamAlt LamCases) -> lcases_msg <+> text "command" - _ -> text "Empty list of alternatives in" <+> pp_ctxt - - lcases_msg = - text "Empty list of alternatives is not allowed in \\cases" + TcRnEmptyCase ctxt reason -> mkSimpleDecorated $ + case reason of + EmptyCaseWithoutFlag -> + text "Empty list of alternatives in" <+> pp_ctxt + EmptyCaseDisallowedCtxt -> + text "Empty list of alternatives is not allowed in" <+> pp_ctxt + EmptyCaseForall tvb -> + vcat [ text "Empty list of alternatives in" <+> pp_ctxt + , hang (text "checked against a forall-type:") + 2 (pprForAll [tvb] <+> text "...") + ] + where + pp_ctxt = case ctxt of + CaseAlt -> text "case expression" + LamAlt LamCase -> text "\\case expression" + LamAlt LamCases -> text "\\cases expression" + ArrowMatchCtxt (ArrowLamAlt LamSingle) -> text "kappa abstraction" + ArrowMatchCtxt (ArrowLamAlt LamCase) -> text "\\case command" + ArrowMatchCtxt (ArrowLamAlt LamCases) -> text "\\cases command" + ArrowMatchCtxt ArrowCaseAlt -> text "case command" + ctxt -> text "(unexpected)" <+> pprMatchContextNoun ctxt TcRnNonStdGuards (NonStandardGuards guards) -> mkSimpleDecorated $ text "accepting non-standard pattern guards" $$ nest 4 (interpp'SP guards) @@ -3062,10 +3065,11 @@ instance Diagnostic TcRnMessage where -> noHints TcRnOrphanCompletePragma{} -> noHints - TcRnEmptyCase ctxt -> case ctxt of - LamAlt LamCases -> noHints -- cases syntax doesn't support empty case. - ArrowMatchCtxt (ArrowLamAlt LamCases) -> noHints - _ -> [suggestExtension LangExt.EmptyCase] + TcRnEmptyCase _ reason -> + case reason of + EmptyCaseWithoutFlag{} -> [suggestExtension LangExt.EmptyCase] + EmptyCaseDisallowedCtxt{} -> noHints + EmptyCaseForall{} -> noHints TcRnNonStdGuards{} -> [suggestExtension LangExt.PatternGuards] TcRnDuplicateSigDecl{} ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -103,6 +103,7 @@ module GHC.Tc.Errors.Types ( , DisabledClassExtension(..) , TyFamsDisabledReason(..) , BadInvisPatReason(..) + , BadEmptyCaseReason(..) , HsTypeOrSigType(..) , HsTyVarBndrExistentialFlag(..) , TySynCycleTyCons @@ -223,7 +224,7 @@ import GHC.Core.InstEnv (LookupInstanceErrReason, ClsInst, DFunId) import GHC.Core.PatSyn (PatSyn) import GHC.Core.Predicate (EqRel, predTypeEqRel) import GHC.Core.TyCon (TyCon, Role, FamTyConFlav, AlgTyConRhs) -import GHC.Core.Type (Kind, Type, ThetaType, PredType, ErrorMsgType, ForAllTyFlag) +import GHC.Core.Type (Kind, Type, ThetaType, PredType, ErrorMsgType, ForAllTyFlag, ForAllTyBinder) import GHC.Driver.Backend (Backend) @@ -3086,8 +3087,11 @@ data TcRnMessage where case () of Test cases: rename/should_fail/RnEmptyCaseFail + testsuite/tests/typecheck/should_fail/T25004 -} - TcRnEmptyCase :: HsMatchContextRn -> TcRnMessage + TcRnEmptyCase :: !HsMatchContextRn + -> !BadEmptyCaseReason + -> TcRnMessage {-| TcRnNonStdGuards is a warning thrown when a user uses non-standard guards (e.g. patterns in guards) without @@ -6183,6 +6187,12 @@ data BadInvisPatReason | InvisPatMisplaced deriving (Generic) +-- | Why was the empty case rejected? +data BadEmptyCaseReason + = EmptyCaseWithoutFlag + | EmptyCaseDisallowedCtxt + | EmptyCaseForall ForAllTyBinder + -- | Either `HsType p` or `HsSigType p`. -- -- Used for reporting errors in `TcRnIllegalKind`. ===================================== compiler/GHC/Tc/Gen/Arrow.hs ===================================== @@ -331,7 +331,7 @@ tcCmdMatchLambda :: CmdEnv -> CmdType -> TcM (HsWrapper, MatchGroup GhcTc (LHsCmd GhcTc)) tcCmdMatchLambda env ctxt arity - mg at MG { mg_alts = L l matches, mg_ext = origin } + mg at MG { mg_alts = L l matches, mg_ext = MatchGroupRn _ origin } (cmd_stk, res_ty) = do { (co, arg_tys, cmd_stk') <- matchExpectedCmdArgs arity cmd_stk ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -214,7 +214,8 @@ mk_failable_expr doFlav pat@(L loc _) expr fail_op = mk_fail_block :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = do dflags <- getDynFlags - return $ HsLam noAnn LamCases $ mkMatchGroup (doExpansionOrigin doFlav) -- \ + return $ HsLam noAnn LamCases $ MG + (MatchGroupRn (LamAlt LamCases) (doExpansionOrigin doFlav)) -- \ (wrapGenSpan [ genHsCaseAltDoExp doFlav pat e -- pat -> expr , fail_alt_case dflags pat fail_op -- _ -> fail "fail pattern" ]) ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1456,7 +1456,8 @@ expandRecordUpd record_expr possible_parents rbnds res_ty case_expr :: HsExpr GhcRn case_expr = HsCase RecUpd record_expr - $ mkMatchGroup (Generated OtherExpansion DoPmc) (wrapGenSpan matches) + $ MG (MatchGroupRn CaseAlt (Generated OtherExpansion DoPmc)) + (wrapGenSpan matches) matches :: [LMatch GhcRn (LHsExpr GhcRn)] matches = map make_pat (NE.toList relevant_cons) ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -164,7 +164,7 @@ tcLambdaMatches e lam_variant matches invis_pat_tys res_ty herald = ExpectedFunTyLam lam_variant e -- See Note [Herald for matchExpectedFunTys] in GHC.Tc.Utils.Unify - tc_body | isDoExpansionGenerated (mg_ext matches) + tc_body | isDoExpansionGenerated (mg_rn_origin $ mg_ext matches) -- See Part 3. B. of Note [Expanding HsDo with XXExprGhcRn] in -- `GHC.Tc.Gen.Do`. Testcase: Typeable1 = tcBodyNC -- NB: Do not add any error contexts @@ -229,16 +229,21 @@ tcMatches :: (AnnoBody body, Outputable (body GhcTc)) -> TcM (MatchGroup GhcTc (LocatedA (body GhcTc))) tcMatches tc_body pat_tys rhs_ty (MG { mg_alts = L l matches - , mg_ext = origin }) + , mg_ext = MatchGroupRn ctxt origin }) | null matches -- Deal with case e of {} -- Since there are no branches, no one else will fill in rhs_ty -- when in inference mode, so we must do it ourselves, -- here, using expTypeToType = do { tcEmitBindingUsage bottomUE - ; pat_tys <- mapM scaledExpTypeToType (filter_out_forall_pat_tys pat_tys) + ; pat_ty <- case pat_tys of + [ExpFunPatTy t] -> scaledExpTypeToType t + [ExpForAllPatTy tvb] -> failWithTc $ TcRnEmptyCase ctxt (EmptyCaseForall tvb) + -- It should be impossible to trigger the panics because the renamer rejects \cases{} + [] -> panic "tcMatches: no arguments in EmptyCase" + _t1:(_t2:_ts) -> panic "tcMatches: multiple arguments in EmptyCase" ; rhs_ty <- expTypeToType rhs_ty ; return (MG { mg_alts = L l [] - , mg_ext = MatchGroupTc pat_tys rhs_ty origin + , mg_ext = MatchGroupTc [pat_ty] rhs_ty origin }) } | otherwise ===================================== compiler/GHC/Tc/TyCl/PatSyn.hs ===================================== @@ -943,11 +943,13 @@ tcPatSynBuilderBind prag_fn (PSB { psb_id = ps_lname@(L loc ps_name) Unidirectional -> panic "tcPatSynBuilderBind" mk_mg :: LHsExpr GhcRn -> MatchGroup GhcRn (LHsExpr GhcRn) - mk_mg body = mkMatchGroup (Generated OtherExpansion SkipPmc) (noLocA [builder_match]) + mk_mg body = MG (MatchGroupRn ctxt origin) (noLocA [builder_match]) where + ctxt = mkPrefixFunRhs ps_lname noAnn + origin = Generated OtherExpansion SkipPmc builder_args = noLocA [(L (l2l loc) (VarPat noExtField (L loc n))) | L loc n <- args] - builder_match = mkMatch (mkPrefixFunRhs ps_lname noAnn) + builder_match = mkMatch ctxt builder_args body (EmptyLocalBinds noExtField) ===================================== testsuite/tests/typecheck/should_fail/T25004.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE RequiredTypeArguments, EmptyCase, LambdaCase #-} +{-# OPTIONS -Wincomplete-patterns #-} + +module T25004 where + +import Data.Kind + +f :: forall (xs :: Type) -> () +f = \case {} ===================================== testsuite/tests/typecheck/should_fail/T25004.stderr ===================================== @@ -0,0 +1,6 @@ +T25004.hs:9:5: error: [GHC-48010] + • Empty list of alternatives in \case expression + checked against a forall-type: forall xs -> ... + • In the expression: \case + In an equation for ‘f’: f = \case + ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -730,3 +730,4 @@ test('T23739c', normal, compile_fail, ['']) test('T24868', normal, compile_fail, ['']) test('T24938', normal, compile_fail, ['']) test('T25325', normal, compile_fail, ['']) +test('T25004', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/177148f778c4a3fc6f7b566aab145c0f7203ba27 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/177148f778c4a3fc6f7b566aab145c0f7203ba27 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/e4c566fa/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 07:21:09 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 02:21:09 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: rts: fix top handler closure type signatures Message-ID: <67c6a9e57a86e_36af2419bd4d4226d0@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - 156a8c52 by Cheng Shao at 2025-03-04T02:20:55-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - b9c67842 by Matthew Pickering at 2025-03-04T02:20:56-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - e5baf396 by Matthew Pickering at 2025-03-04T02:20:56-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 113952cd by Ben Gamari at 2025-03-04T02:20:56-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 83c1e2ee by Alan Zimmerman at 2025-03-04T02:20:57-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 36 changed files: - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModIface.hs - docs/users_guide/wasm.rst - hadrian/src/Rules/Test.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/include/RtsAPI.h - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6e0710bcbccb97b2555c6664bcfaed9aeac636a0...83c1e2eed937b2daaddb0803e14b6f44823e117a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6e0710bcbccb97b2555c6664bcfaed9aeac636a0...83c1e2eed937b2daaddb0803e14b6f44823e117a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/3b41e9af/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 4 08:51:36 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Tue, 04 Mar 2025 03:51:36 -0500 Subject: [Git][ghc/ghc][wip/andreask/interpreter_primops] Fix lint warning Message-ID: <67c6bf183ff38_36af24241fa6c3518b@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/interpreter_primops at Glasgow Haskell Compiler / GHC Commits: 41256981 by Andreas Klebinger at 2025-03-04T09:29:29+01:00 Fix lint warning - - - - - 1 changed file: - compiler/GHC/ByteCode/Asm.hs Changes: ===================================== compiler/GHC/ByteCode/Asm.hs ===================================== @@ -360,37 +360,6 @@ inspectAsm platform long_jumps initial_offset largeArgInstr :: Word16 -> Word16 largeArgInstr bci = bci_FLAG_LARGE_ARGS .|. bci -sizedInstr :: Platform -> Word16 -> PrimRep -> Word16 -sizedInstr platform bci rep = - bci .|. ((interpreterWidth rep) `shiftL` 13) - where - -- For operations currently not used or supported by the interpreter. - not_supported = panic "sizedInstr: Trying to get width for rep not supported by interpreter" - -- For performance reasons 64bit wide operations should always use fixed width operations. - err_w64 = panic "sizedInstr: Trying to get width for a W64 rep, these should use fixed rep instructions instead" - interpreterWidth rep = - case rep of - Int8Rep -> 0 - Int16Rep -> 1 - Int32Rep -> 2 - Int64Rep -> err_w64 - IntRep -> case platformWordSize platform of - PW4 -> 2 - PW8 -> err_w64 - Word8Rep -> 0 - Word16Rep -> 1 - Word32Rep -> 2 - Word64Rep -> err_w64 - WordRep -> case platformWordSize platform of - PW4 -> 2 - PW8 -> err_w64 - AddrRep -> err_w64 - FloatRep -> not_supported - DoubleRep -> not_supported - VecRep{} -> not_supported - BoxedRep{} -> not_supported - - largeArg :: Platform -> Word64 -> [Word16] largeArg platform w = case platformWordSize platform of PW8 -> [fromIntegral (w `shiftR` 48), View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/41256981ab5348698207e2d1d59f548f7331e293 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/41256981ab5348698207e2d1d59f548f7331e293 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/d7ecd5bc/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 09:19:47 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 04:19:47 -0500 Subject: [Git][ghc/ghc][wip/fix-in-scope-simple-opt-expr] 22 commits: LLVM: account for register type in funPrologue Message-ID: <67c6c5b3e531e_3ff90138adec51048@gitlab.mail> Matthew Pickering pushed to branch wip/fix-in-scope-simple-opt-expr at Glasgow Haskell Compiler / GHC Commits: 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - b7ab4fcf by Matthew Pickering at 2025-03-04T09:19:30+00:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 162 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - distrib/configure.ac.in - ghc/GHCi/UI.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Default.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - m4/fp_settings.m4 - rts/Interpreter.c - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/haddock/doc/conf.py The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad232a00f90b7f158324a7f22d55248875f15b47...b7ab4fcf85cf04b286833d1de49dc37b4346f39a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad232a00f90b7f158324a7f22d55248875f15b47...b7ab4fcf85cf04b286833d1de49dc37b4346f39a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/29dcdc82/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 09:47:07 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 04 Mar 2025 04:47:07 -0500 Subject: [Git][ghc/ghc][wip/T25657] 2 commits: Remove unnecessary import Message-ID: <67c6cc1be67f2_128b519c14883392@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25657 at Glasgow Haskell Compiler / GHC Commits: f9116373 by Simon Peyton Jones at 2025-03-04T09:22:39+00:00 Remove unnecessary import - - - - - 6cca10b8 by Simon Peyton Jones at 2025-03-04T09:46:31+00:00 Comments - - - - - 2 changed files: - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -724,16 +724,21 @@ data MaybeApartReason | MARTypeVsConstraint -- ^ matching Type ~? Constraint or the arrow types -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim + | MARCast -- ^ Very obscure. + -- See (KCU2) in Note [Kind coercions in Unify] + instance Outputable MaybeApartReason where ppr MARTypeFamily = text "MARTypeFamily" ppr MARInfinite = text "MARInfinite" ppr MARTypeVsConstraint = text "MARTypeVsConstraint" + ppr MARCast = text "MARCast" instance Semigroup MaybeApartReason where - -- see end of Note [Unification result] for why - MARTypeFamily <> r = r - MARInfinite <> _ = MARInfinite + -- See end of Note [Unification result] for why + MARInfinite <> _ = MARInfinite -- MARInfinite wins + MARTypeFamily <> r = r -- Otherwise it doesn't really matter MARTypeVsConstraint <> r = r + MARCast <> r = r instance Applicative UnifyResultM where pure = Unifiable @@ -1165,13 +1170,35 @@ Preserving (UKINV) takes a bit of work, governed by the `match_kis` flag in Wrinkles -(KCU1) We never need to apply the RnEnv2 renaming to the accumulating `kco` argument. - Why not? Because - * The `kco` arg is used /only/ when extending +(KCU1) We ensure that the `kco` argument never mentions variables in the + domain of either RnEnvL or RnEnvR. Why? + + * `kco` is used only to build the final well-kinded substitution + a :-> ty |> kco + The range of the substitution never mentions forall-bound variables, + so `kco` cannot either. + + * `kco` mixes up types from both left and right arguments of + `unify_ty`, which have different renamings in the RnEnv2. + + The easiest thing is to insist that `kco` does not need renaming with + the RnEnv2; it mentions no forall-bound variables. + + To achieve this we do a `mentionsForAllBoundTyVars` test in the + `CastTy` cases of `unify_ty`. + +(KCU2) Suppose we are unifying + (forall a. x |> (...F a b...) ~ (forall a. y) + We can't bind y :-> x |> (...F a b...), becuase of that free `a`. + + But if we later learn that b=Int, and F a Int = Bool, + that free `a` might disappear, so we could unify with + y :-> x |> (...Bool...) - xxx working here xxx + Conclusion: if there is a free forall-bound variable in a cast, + return MaybeApart, with a MaybeApartReason of MARCast. -(KCU2) We thought, at one point, that this was all unnecessary: why should +(KCU3) We thought, at one point, that this was all unnecessary: why should casts be in types in the first place? But they are sometimes. In dependent/should_compile/KindEqualities2, we see, for example the constraint Num (Int |> (blah ; sym blah)). We naturally want to find @@ -1373,9 +1400,8 @@ unify_ty env ty1 ty2 kco unify_ty env (CastTy ty1 co1) ty2 kco | mentionsForAllBoundTyVarsL env (tyCoVarsOfCo co1) - = surelyApart - -- xxx todo ... MaybeApart perhaps? F a b, where b is forall-bound, but a is not - -- and F Int b = Int + -- See (KCU1) in Note [Kind coercions in Unify] + = maybeApart MARCast -- See (KCU2) | um_unif env = unify_ty env ty1 ty2 (co1 `mkTransCo` kco) @@ -1390,7 +1416,8 @@ unify_ty env (CastTy ty1 co1) ty2 kco unify_ty env ty1 (CastTy ty2 co2) kco | mentionsForAllBoundTyVarsR env (tyCoVarsOfCo co2) - = surelyApart + -- See (KCU1) in Note [Kind coercions in Unify] + = maybeApart MARCast -- See (KCU2) | otherwise = unify_ty env ty1 ty2 (kco `mkTransCo` mkSymCo co2) -- ToDo: what if co2 mentions forall-bound variables? ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -88,7 +88,7 @@ import GHC.Core.TyCo.Ppr( debugPprType {- pprTyVar -} ) import GHC.Core.TyCon import GHC.Core.Coercion import GHC.Core.Unify -import GHC.Core.Predicate( EqRel(..), CanEqLHS(..), mkEqPredRole, mkNomEqPred ) +import GHC.Core.Predicate( EqRel(..), mkEqPredRole, mkNomEqPred ) import GHC.Core.Multiplicity import GHC.Core.Reduction View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6e0326d8af2dbcad227b55db2c234c213f2c70b5...6cca10b868d07d8b846b4a83480ca3f016e672c3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6e0326d8af2dbcad227b55db2c234c213f2c70b5...6cca10b868d07d8b846b4a83480ca3f016e672c3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/bef6593d/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 11:50:56 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 06:50:56 -0500 Subject: [Git][ghc/ghc][wip/22188] 2 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67c6e920a47fd_6036c3efdf0136e0@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: 6083a96d by Matthew Pickering at 2025-03-04T11:49:21+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-self-recomp-info which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. In addition to this, the change alerted me to the incorrect implemenation of the reifyModule function. See #8489 for more discussion about how to fix this if anyone was so inclined. For now I just added a warning `-Wreify-module-missing-info` which triggers if the module you are trying to reify doesn't have a suitable interface. Interfaces which are unsuitable include: * The GHC.Prim interface, which is a fake interface * Interfaces compiled with -fno-write-self-recomp-info The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 71616702 by Matthew Pickering at 2025-03-04T11:49:21+00:00 Disable self recomp in release flavour - - - - - 27 changed files: - compiler/GHC.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -104,10 +104,8 @@ module GHC ( mi_module, mi_sig_of, mi_hsc_src, - mi_src_hash, mi_hi_bytes, mi_deps, - mi_usages, mi_exports, mi_used_th, mi_fixities, ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1178,7 +1178,8 @@ defaultFlags settings Opt_ShowErrorContext, Opt_SuppressStgReps, Opt_UnoptimizedCoreForInterpreter, - Opt_SpecialiseIncoherents + Opt_SpecialiseIncoherents, + Opt_WriteSelfRecompInfo ] ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns] ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -692,6 +692,7 @@ data GeneralFlag | Opt_ExposeOverloadedUnfoldings | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code + | Opt_WriteSelfRecompInfo | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1243,11 +1243,11 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h (cg_guts, details) <- liftIO $ hscTidy hsc_env simplified_guts - let !partial_iface = + !partial_iface <- liftIO $ {-# SCC "GHC.Driver.Main.mkPartialIface" #-} -- This `force` saves 2M residency in test T10370 -- See Note [Avoiding space leaks in toIface*] for details. - force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) + fmap force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) return HscRecomp { hscs_guts = cg_guts, hscs_mod_location = ms_location summary, ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -875,10 +875,10 @@ pruneCache hpt summ modl = miKey iface linkable' | Just ms <- M.lookup modl ms_map - , mi_src_hash iface /= ms_hs_hash ms - = emptyHomeModInfoLinkable - | otherwise + , mi_src_hash iface == Just (ms_hs_hash ms) = linkable + | otherwise + = emptyHomeModInfoLinkable -- Using UFM Module is safe for determinism because the map is just used for a transient lookup. The cache should be unique and a key clash is an error. ms_map = M.fromListWith ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,6 +2528,7 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, + flagSpec "write-self-recomp-info" Opt_WriteSelfRecompInfo, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -22,14 +22,12 @@ import GHC.Driver.DynFlags import GHC.Driver.Config import GHC.Driver.Config.Core.Lint ( endPassHscEnvIO ) import GHC.Driver.Config.HsToCore.Ticks -import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env import GHC.Driver.Backend import GHC.Driver.Plugins import GHC.Hs -import GHC.HsToCore.Usage import GHC.HsToCore.Monad import GHC.HsToCore.Errors.Types import GHC.HsToCore.Expr @@ -42,7 +40,7 @@ import GHC.HsToCore.Docs import GHC.Tc.Types import GHC.Tc.Types.Origin ( Position(..) ) -import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceLoad ) +import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances ) import GHC.Tc.Module ( runTcInteractive ) import GHC.Core.Type @@ -100,6 +98,7 @@ import GHC.Unit.Module.Deps import Data.List (partition) import Data.IORef import Data.Traversable (for) +import GHC.Iface.Make (mkRecompUsageInfo) {- ************************************************************************ @@ -127,12 +126,10 @@ deSugar hsc_env tcg_fix_env = fix_env, tcg_inst_env = inst_env, tcg_fam_inst_env = fam_inst_env, - tcg_merged = merged, tcg_warns = warns, tcg_anns = anns, tcg_binds = binds, tcg_imp_specs = imp_specs, - tcg_dependent_files = dependent_files, tcg_ev_binds = ev_binds, tcg_th_foreign_files = th_foreign_files_var, tcg_fords = fords, @@ -228,8 +225,7 @@ deSugar hsc_env ; endPassHscEnvIO hsc_env name_ppr_ctx CoreDesugarOpt ds_binds ds_rules_for_imps - ; let used_names = mkUsedNames tcg_env - pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) + ; let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) home_unit = hsc_home_unit hsc_env ; let deps = mkDependencies home_unit (tcg_mod tcg_env) @@ -237,17 +233,10 @@ deSugar hsc_env (map mi_module pluginModules) ; used_th <- readIORef tc_splice_used - ; dep_files <- readIORef dependent_files ; safe_mode <- finalSafeMode dflags tcg_env - ; (needed_mods, needed_pkgs) <- readIORef (tcg_th_needed_deps tcg_env) - - ; let uc = initUsageConfig hsc_env - ; let plugins = hsc_plugins hsc_env - ; let fc = hsc_FC hsc_env - ; let unit_env = hsc_unit_env hsc_env - ; usages <- initIfaceLoad hsc_env $ - mkUsageInfo uc plugins fc unit_env mod (imp_mods imports) used_names - dep_files merged needed_mods needed_pkgs + + ; usages <- mkRecompUsageInfo hsc_env tcg_env + -- id_mod /= mod when we are processing an hsig, but hsigs -- never desugared and compiled (there's no code!) -- Consequently, this should hold for any ModGuts that make ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -50,7 +50,6 @@ import GHC.Types.Name.Cache import GHC.Types.SrcLoc import GHC.Platform import GHC.Settings.Constants -import GHC.Utils.Fingerprint import GHC.Iface.Type (IfaceType(..), getIfaceType, putIfaceType, ifaceTypeSharedByte) import Control.Monad @@ -115,7 +114,7 @@ readBinIfaceHeader -> CheckHiWay -> TraceBinIFace -> FilePath - -> IO (Fingerprint, ReadBinHandle) + -> IO ReadBinHandle readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do let platform = profilePlatform profile @@ -157,8 +156,7 @@ readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do when (checkHiWay == CheckHiWay) $ errorOnMismatch "mismatched interface file profile tag" tag check_tag - src_hash <- get bh - pure (src_hash, bh) + pure bh -- | Read an interface file. -- @@ -171,12 +169,11 @@ readBinIface -> FilePath -> IO ModIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do - (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path + bh <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path mod_iface <- getIfaceWithExtFields name_cache bh return $ mod_iface - & addSourceFingerprint src_hash getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface @@ -260,7 +257,6 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh (show hiVersion) let tag = profileBuildTag profile put_ bh tag - put_ bh (mi_src_hash mod_iface) putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1259,21 +1259,25 @@ pprModIfaceSimple unit_state iface = -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc pprModIface unit_state iface - = vcat [ text "interface" + = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) + <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash exts)) , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) + , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat + [ nest 2 (text "src_hash:" <+> ppr src) + , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "opt_hash:" <+> ppr opt_hash) + , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) + , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) + , vcat (map pprUsage usages) + ] , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) - , nest 2 (text "flag hash:" <+> ppr (mi_flag_hash exts)) - , nest 2 (text "opt_hash:" <+> ppr (mi_opt_hash exts)) - , nest 2 (text "hpc_hash:" <+> ppr (mi_hpc_hash exts)) - , nest 2 (text "plugin_hash:" <+> ppr (mi_plugin_hash exts)) - , nest 2 (text "src_hash:" <+> ppr (mi_src_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "used TH splices:" <+> ppr (mi_used_th iface)) , nest 2 (text "where") @@ -1282,7 +1286,6 @@ pprModIface unit_state iface , text "defaults:" , nest 2 (vcat (map ppr (mi_defaults iface))) , pprDeps unit_state (mi_deps iface) - , vcat (map pprUsage (mi_usages iface)) , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] @@ -1302,6 +1305,7 @@ pprModIface unit_state iface ] where exts = mi_final_exts iface + pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -13,6 +13,7 @@ module GHC.Iface.Make ( mkPartialIface , mkFullIface , mkIfaceTc + , mkRecompUsageInfo , mkIfaceExports ) where @@ -110,7 +111,7 @@ mkPartialIface :: HscEnv -> ModSummary -> [ImportUserSpec] -> ModGuts - -> PartialModIface + -> IO PartialModIface mkPartialIface hsc_env core_prog mod_details mod_summary import_decls ModGuts{ mg_module = this_mod , mg_hsc_src = hsc_src @@ -125,8 +126,10 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_trust_pkg = self_trust , mg_docs = docs } - = mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust - safe_mode usages docs mod_summary mod_details + = do + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages + return $ mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust + safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code -- generator produced information. @@ -181,9 +184,8 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = restoreFromOldModIface mi res - forceModIface resiface - return resiface + forceModIface res + return res -- | Initial ram buffer to allocate for writing interface files. initBinMemSize :: Int @@ -236,14 +238,11 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_merged = merged, tcg_warns = warns, tcg_hpc = other_hpc_info, - tcg_th_splice_used = tc_splice_used, - tcg_dependent_files = dependent_files + tcg_th_splice_used = tc_splice_used } = do - let used_names = mkUsedNames tc_result let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) let home_unit = hsc_home_unit hsc_env let deps = mkDependencies home_unit @@ -252,48 +251,59 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (map mi_module pluginModules) let hpc_info = emptyHpcInfo other_hpc_info used_th <- readIORef tc_splice_used - dep_files <- (readIORef dependent_files) - (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) - let uc = initUsageConfig hsc_env - plugins = hsc_plugins hsc_env - fc = hsc_FC hsc_env - unit_env = hsc_unit_env hsc_env - -- Do NOT use semantic module here; this_mod in mkUsageInfo - -- is used solely to decide if we should record a dependency - -- or not. When we instantiate a signature, the semantic - -- module is something we want to record dependencies for, - -- but if you pass that in here, we'll decide it's the local - -- module and does not need to be recorded as a dependency. - -- See Note [Identity versus semantic module] - usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env this_mod (imp_mods imports) used_names - dep_files merged needed_links needed_pkgs + usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usage let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info - (imp_trust_own_pkg imports) safe_mode usages - docs mod_summary + (imp_trust_own_pkg imports) safe_mode self_recomp + docs mod_details mkFullIface hsc_env partial_iface Nothing Nothing NoStubs [] +mkRecompUsageInfo :: HscEnv -> TcGblEnv -> IO (Maybe [Usage]) +mkRecompUsageInfo hsc_env tc_result = do + let dflags = hsc_dflags hsc_env + if not (gopt Opt_WriteSelfRecompInfo dflags) + then return Nothing + else do + let used_names = mkUsedNames tc_result + dep_files <- (readIORef (tcg_dependent_files tc_result)) + (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) + let uc = initUsageConfig hsc_env + plugins = hsc_plugins hsc_env + fc = hsc_FC hsc_env + unit_env = hsc_unit_env hsc_env + + -- Do NOT use semantic module here; this_mod in mkUsageInfo + -- is used solely to decide if we should record a dependency + -- or not. When we instantiate a signature, the semantic + -- module is something we want to record dependencies for, + -- but if you pass that in here, we'll decide it's the local + -- module and does not need to be recorded as a dependency. + -- See Note [Identity versus semantic module] + usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env (tcg_mod tc_result) (imp_mods (tcg_imports tc_result)) used_names + dep_files (tcg_merged tc_result) needed_links needed_pkgs + return (Just usages) + mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Bool -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo -> Bool -> SafeHaskellMode - -> [Usage] + -> Maybe ModIfaceSelfRecomp -> Maybe Docs - -> ModSummary -> ModDetails -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode usages - docs mod_summary + hpc_info pkg_trust_req safe_mode self_recomp + docs ModDetails{ md_defaults = defaults, md_insts = insts, md_fam_insts = fam_insts, @@ -350,8 +360,8 @@ mkIface_ hsc_env then Nothing else Just semantic_mod) & set_mi_hsc_src hsc_src + & set_mi_self_recomp self_recomp & set_mi_deps deps - & set_mi_usages usages & set_mi_exports (mkIfaceExports exports) & set_mi_defaults (defaultsToIfaceDefaults defaults) @@ -376,7 +386,6 @@ mkIface_ hsc_env & set_mi_docs docs & set_mi_final_exts () & set_mi_ext_fields emptyExtensibleFields - & set_mi_src_hash (ms_hs_hash mod_summary) & set_mi_hi_bytes PartialIfaceBinHandle where ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -15,6 +15,7 @@ module GHC.Iface.Recomp , CompileReason(..) , recompileRequired , addFingerprints + , mkSelfRecomp ) where @@ -171,6 +172,7 @@ data RecompReason = UnitDepRemoved UnitId | ModulePackageChanged FastString | SourceFileChanged + | NoSelfRecompInfo | ThisUnitIdChanged | ImpurePlugin | PluginsChanged @@ -204,6 +206,7 @@ instance Outputable RecompReason where UnitDepRemoved uid -> ppr uid <+> text "removed" ModulePackageChanged s -> ftext s <+> text "package changed" SourceFileChanged -> text "Source file changed" + NoSelfRecompInfo -> text "Old interface lacks recompilation info" ThisUnitIdChanged -> text "-this-unit-id changed" ImpurePlugin -> text "Impure plugin forced recompilation" PluginsChanged -> text "Plugins changed" @@ -283,7 +286,7 @@ check_old_iface hsc_env mod_summary maybe_iface logger = hsc_logger hsc_env getIface = case maybe_iface of - Just _ -> do + Just {} -> do trace_if logger (text "We already have the old interface for" <+> ppr (ms_mod mod_summary)) return maybe_iface @@ -354,7 +357,9 @@ check_old_iface hsc_env mod_summary maybe_iface -- should check versions because some packages -- might have changed or gone away. Just iface -> - check_dyn_hi iface $ checkVersions hsc_env mod_summary iface + case mi_self_recomp_info iface of + Nothing -> return $ outOfDateItemBecause NoSelfRecompInfo Nothing + Just sr_info -> check_dyn_hi iface $ checkVersions hsc_env mod_summary iface sr_info -- | Check if a module is still the same 'version'. -- @@ -370,8 +375,9 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface + -> ModIfaceSelfRecomp -> IfG (MaybeValidated ModIface) -checkVersions hsc_env mod_summary iface +checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger (text "Considering whether compilation is required for" <+> ppr (mi_module iface) <> colon) @@ -380,23 +386,22 @@ checkVersions hsc_env mod_summary iface -- but we ALSO must make sure the instantiation matches up. See -- test case bkpcabal04! ; hsc_env <- getTopEnv - ; if mi_src_hash iface /= ms_hs_hash mod_summary + ; if mi_sr_src_hash self_recomp /= ms_hs_hash mod_summary then return $ outOfDateItemBecause SourceFileChanged Nothing else do { ; if not (isHomeModule home_unit (mi_module iface)) then return $ outOfDateItemBecause ThisUnitIdChanged Nothing else do { - ; recomp <- liftIO $ checkFlagHash hsc_env iface - `recompThen` checkOptimHash hsc_env iface - `recompThen` checkHpcHash hsc_env iface - `recompThen` checkMergedSignatures hsc_env mod_summary iface + ; recomp <- liftIO $ checkFlagHash hsc_env (mi_module iface) self_recomp + `recompThen` checkOptimHash hsc_env self_recomp + `recompThen` checkHpcHash hsc_env self_recomp + `recompThen` checkMergedSignatures hsc_env mod_summary self_recomp `recompThen` checkHsig logger home_unit mod_summary iface `recompThen` pure (checkHie dflags mod_summary) ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { ; recomp <- checkDependencies hsc_env mod_summary iface ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { - ; recomp <- checkPlugins (hsc_plugins hsc_env) iface + ; recomp <- checkPlugins (hsc_plugins hsc_env) self_recomp ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { - -- Source code unchanged and no errors yet... carry on -- -- First put the dependent-module info, read from the old @@ -411,7 +416,7 @@ checkVersions hsc_env mod_summary iface ; updateEps_ $ \eps -> eps { eps_is_boot = mkModDeps $ dep_boot_mods (mi_deps iface) } } ; recomp <- checkList [checkModUsage (hsc_FC hsc_env) u - | u <- mi_usages iface] + | u <- mi_sr_usages self_recomp] ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { ; return $ UpToDateItem iface }}}}}}} @@ -423,11 +428,11 @@ checkVersions hsc_env mod_summary iface -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIface -> IfG RecompileRequired -checkPlugins plugins iface = liftIO $ do +checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp - let old_fingerprint = mi_plugin_hash (mi_final_exts iface) + let old_fingerprint = mi_sr_plugin_hash self_recomp return $ pluginRecompileToRecompileRequired old_fingerprint new_fingerprint recomp recompPlugins :: Plugins -> IO PluginRecompile @@ -516,11 +521,11 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> ModIface -> IO RecompileRequired -checkFlagHash hsc_env iface = do +checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_flag_hash (mi_final_exts iface) - new_hash <- fingerprintDynFlags hsc_env (mi_module iface) putNameLiterally + let old_hash = mi_sr_flag_hash self_recomp + new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally case old_hash == new_hash of True -> up_to_date logger (text "Module flags unchanged") False -> out_of_date_hash logger FlagsChanged @@ -528,10 +533,10 @@ checkFlagHash hsc_env iface = do old_hash new_hash -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIface -> IO RecompileRequired +checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env - let old_hash = mi_opt_hash (mi_final_exts iface) + let old_hash = mi_sr_opt_hash iface new_hash <- fingerprintOptFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -544,10 +549,10 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIface -> IO RecompileRequired -checkHpcHash hsc_env iface = do +checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_hpc_hash (mi_final_exts iface) + let old_hash = mi_sr_hpc_hash self_recomp new_hash <- fingerprintHpcFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -561,11 +566,11 @@ checkHpcHash hsc_env iface = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIface -> IO RecompileRequired -checkMergedSignatures hsc_env mod_summary iface = do +checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env - let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_usages iface ] + let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_sr_usages self_recomp ] new_merged = case lookupUniqMap (requirementContext unit_state) (ms_mod_name mod_summary) of Nothing -> [] @@ -939,6 +944,28 @@ we use is: -} +-- | Compute the information needed for self-recompilation checking. This +-- information can be computed before the backend phase. +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp hsc_env this_mod src_hash usages = do + let dflags = hsc_dflags hsc_env + + flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + + opt_hash <- fingerprintOptFlags dflags putNameLiterally + + hpc_hash <- fingerprintHpcFlags dflags putNameLiterally + + plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + + return (ModIfaceSelfRecomp + { mi_sr_flag_hash = flag_hash + , mi_sr_hpc_hash = hpc_hash + , mi_sr_opt_hash = opt_hash + , mi_sr_plugin_hash = plugin_hash + , mi_sr_src_hash = src_hash + , mi_sr_usages = usages }) + -- | Add fingerprints for top-level declarations to a 'ModIface'. -- -- See Note [Fingerprinting IfaceDecls] @@ -1213,18 +1240,6 @@ addFingerprints hsc_env iface0 sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - -- the flag hash depends on: - -- - (some of) dflags - -- it returns two hashes, one that shouldn't change - -- the abi hash and one that should - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally - - opt_hash <- fingerprintOptFlags dflags putNameLiterally - - hpc_hash <- fingerprintHpcFlags dflags putNameLiterally - - plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) - -- the ABI hash depends on: -- - decls -- - export list @@ -1238,6 +1253,7 @@ addFingerprints hsc_env iface0 mi_warns iface0, mi_foreign iface0) + -- The interface hash depends on: -- - the ABI hash, plus -- - the source file hash, @@ -1246,21 +1262,17 @@ addFingerprints hsc_env iface0 -- - deps (home and external packages, dependent files) -- - hpc iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - mi_src_hash iface0, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_usages iface0, - sorted_deps, - mi_hpc iface0) + (mod_hash, + mi_src_hash iface0, + ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache + mi_usages iface0, + sorted_deps, + mi_hpc iface0) let final_iface_exts = ModIfaceBackend - { mi_iface_hash = iface_hash - , mi_mod_hash = mod_hash - , mi_flag_hash = flag_hash - , mi_opt_hash = opt_hash - , mi_hpc_hash = hpc_hash - , mi_plugin_hash = plugin_hash + { mi_mod_hash = mod_hash + , mi_iface_hash = iface_hash , mi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts @@ -1281,12 +1293,12 @@ addFingerprints hsc_env iface0 where this_mod = mi_module iface0 semantic_mod = mi_semantic_module iface0 - dflags = hsc_dflags hsc_env (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) ann_fn = mkIfaceAnnCache (mi_anns iface0) + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the -- current module). ===================================== compiler/GHC/Unit/Module/ModGuts.hs ===================================== @@ -53,7 +53,7 @@ data ModGuts mg_exports :: ![AvailInfo], -- ^ What it exports mg_deps :: !Dependencies, -- ^ What it depends on, directly or -- otherwise - mg_usages :: ![Usage], -- ^ What was used? Used for interfaces. + mg_usages :: !(Maybe [Usage]), -- ^ What was used? Used for interfaces. mg_used_th :: !Bool, -- ^ Did we run a TH splice? mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -15,7 +15,6 @@ module GHC.Unit.Module.ModIface , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -36,19 +35,16 @@ module GHC.Unit.Module.ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info ) , pattern ModIface - , restoreFromOldModIface - , addSourceFingerprint , set_mi_module , set_mi_sig_of , set_mi_hsc_src - , set_mi_src_hash + , set_mi_self_recomp , set_mi_hi_bytes , set_mi_deps - , set_mi_usages , set_mi_exports , set_mi_used_th , set_mi_fixities @@ -73,6 +69,8 @@ module GHC.Unit.Module.ModIface , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) + , ModIfaceSelfRecomp (..) + , withSelfRecomp , IfaceDeclExts , IfaceBackendExts , IfaceExport @@ -85,6 +83,12 @@ module GHC.Unit.Module.ModIface , mi_semantic_module , mi_free_holes , mi_mnwib + , mi_flag_hash + , mi_opt_hash + , mi_hpc_hash + , mi_plugin_hash + , mi_src_hash + , mi_usages , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,6 +110,8 @@ import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.ModIface.SelfRecomp + import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env @@ -150,19 +156,10 @@ type ModIface = ModIface_ 'ModIfaceFinal -- * Or computed just before writing the iface to disk. (Hashes) -- In order to fully instantiate it. data ModIfaceBackend = ModIfaceBackend - { mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_mod_hash :: !Fingerprint + { mi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_flag_hash :: !Fingerprint - -- ^ Hash of the important flags used when compiling the module, excluding - -- optimisation flags - , mi_opt_hash :: !Fingerprint - -- ^ Hash of optimisation flags - , mi_hpc_hash :: !Fingerprint - -- ^ Hash of hpc flags - , mi_plugin_hash :: !Fingerprint - -- ^ Hash of plugins + , mi_iface_hash :: !Fingerprint + -- ^ Hash of the whole interface , mi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans , mi_finsts :: !WhetherHasFamInst @@ -218,6 +215,50 @@ data IfaceBinHandle (phase :: ModIfacePhase) where -- (e.g., set to 'Nothing'). FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal + +withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp iface nk jk = + case mi_self_recomp_info iface of + Nothing -> nk + Just x -> jk x + +{- +Note [Self recompilation information in interface files] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +The flag -fwrite-self-recomp-info controls whether +interface files contain the information necessary to answer the +question: + + Do I need to recompile myself or is this current interface file + suitable? + +Why? Most packages are only built once either by a distribution or cabal +and then placed into an immutable store, after which we will never ask +this question. Therefore we can derive two benefits from omitting this +information. + +* Primary motivation: It vastly reduces the surface area for creating + non-deterministic interface files. See issue #10424 which motivated a + proper fix to that issue. Distributions have long contained versions + of GHC which just have broken self-recompilation checking (in order to + get deterministic interface files). + +* Secondary motivation: This reduces the size of interface files + slightly.. the `mi_usages` field can be quite big but probably this + isn't such a great benefit. + +* Third motivation: Conceptually clarity about which parts of an + interface file are used in order to **communicate** with subsequent + packages about the **interface** for a module. And which parts are + used to self-communicate during recompilation checking. + +The main tracking issue is #22188 but fixes issues such as #10424 in a +proper way. + +-} + + -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, -- and can be written out to an interface file. The 'ModDetails is after @@ -245,16 +286,6 @@ data ModIface_ (phase :: ModIfacePhase) -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages_ :: [Usage], - -- ^ Usages; kept sorted so that it's easy to decide - -- whether to write a new iface file (changing usages - -- doesn't affect the hash of this module) - -- NOT STRICT! we read this field lazily from the interface file - -- It is *only* consulted by the recompilation checker - -- - -- The elements must be *deterministically* sorted to guarantee - -- deterministic interface files - mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier @@ -352,13 +383,15 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash_ :: !Fingerprint, - -- ^ Hash of the .hs source, used for recompilation checking. - mi_hi_bytes_ :: !(IfaceBinHandle phase) + mi_hi_bytes_ :: !(IfaceBinHandle phase), -- ^ A serialised in-memory buffer of this 'ModIface'. -- If this handle is given, we can avoid serialising the 'ModIface' -- when writing this 'ModIface' to disk, and write this buffer to disk instead. -- See Note [Sharing of ModIface]. + + mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] } -- Enough information to reconstruct the top level environment for a module @@ -404,6 +437,24 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} +mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ + +mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ + +mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ + +mi_src_hash :: ModIface_ phase -> Maybe Fingerprint +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ + +mi_usages :: ModIface_ phase -> Maybe [Usage] +mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ + +mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ + -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. mi_boot :: ModIface -> IsBootInterface @@ -461,9 +512,6 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance - -- because we are going to write it - -- out separately in the actual file mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then @@ -471,7 +519,6 @@ instance Binary ModIface where -- the byte array. -- See Note [Private fields in ModIface] mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_fixities_ = fixities, @@ -493,13 +540,10 @@ instance Binary ModIface where mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file + mi_self_recomp_info_ = self_recomp, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -508,16 +552,12 @@ instance Binary ModIface where put_ bh mod put_ bh sig_of put_ bh hsc_src - put_ bh iface_hash + put_ bh self_recomp put_ bh mod_hash - put_ bh flag_hash - put_ bh opt_hash - put_ bh hpc_hash - put_ bh plugin_hash + put_ bh iface_hash put_ bh orphan put_ bh hasFamInsts lazyPut bh deps - lazyPut bh usages put_ bh exports put_ bh exp_hash put_ bh used_th @@ -543,16 +583,12 @@ instance Binary ModIface where mod <- get bh sig_of <- get bh hsc_src <- get bh - iface_hash <- get bh + self_recomp_info <- get bh mod_hash <- get bh - flag_hash <- get bh - opt_hash <- get bh - hpc_hash <- get bh - plugin_hash <- get bh + iface_hash <- get bh orphan <- get bh hasFamInsts <- get bh deps <- lazyGet bh - usages <- {-# SCC "bin_usages" #-} lazyGet bh exports <- {-# SCC "bin_exports" #-} get bh exp_hash <- get bh used_th <- get bh @@ -577,15 +613,12 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = fingerprint0, -- placeholder because this is dealt - -- with specially when the file is read mi_hi_bytes_ = -- We can't populate this field here, as we are -- missing the 'mi_ext_fields_' field, which is -- handled in 'getIfaceWithExtFields'. FullIfaceBinHandle Strict.Nothing, mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_anns_ = anns, @@ -607,13 +640,10 @@ instance Binary ModIface where mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read + mi_self_recomp_info_ = self_recomp_info, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -632,10 +662,8 @@ emptyPartialModIface mod { mi_module_ = mod, mi_sig_of_ = Nothing, mi_hsc_src_ = HsSrcFile, - mi_src_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_usages_ = [], mi_exports_ = [], mi_used_th_ = False, mi_fixities_ = [], @@ -655,21 +683,19 @@ emptyPartialModIface mod mi_complete_matches_ = [], mi_docs_ = Nothing, mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields + mi_ext_fields_ = emptyExtensibleFields, + mi_self_recomp_info_ = Nothing } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) { mi_decls_ = [] + , mi_self_recomp_info_ = Nothing , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing , mi_final_exts_ = ModIfaceBackend - { mi_iface_hash = fingerprint0, - mi_mod_hash = fingerprint0, - mi_flag_hash = fingerprint0, - mi_opt_hash = fingerprint0, - mi_hpc_hash = fingerprint0, - mi_plugin_hash = fingerprint0, + { mi_mod_hash = fingerprint0, + mi_iface_hash = fingerprint0, mi_orphan = False, mi_finsts = False, mi_exp_hash = fingerprint0, @@ -699,18 +725,17 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_, mi_src_hash_ }) + , mi_ext_fields_ }) = rnf mi_module_ `seq` rnf mi_sig_of_ `seq` mi_hsc_src_ `seq` mi_hi_bytes_ `seq` mi_deps_ - `seq` mi_usages_ `seq` mi_exports_ `seq` rnf mi_used_th_ `seq` mi_fixities_ @@ -731,20 +756,14 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_docs_ `seq` mi_final_exts_ `seq` mi_ext_fields_ - `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_iface_hash, mi_mod_hash, mi_flag_hash, mi_opt_hash - , mi_hpc_hash, mi_plugin_hash, mi_orphan, mi_finsts, mi_exp_hash + rnf (ModIfaceBackend{ mi_mod_hash + , mi_orphan, mi_finsts, mi_exp_hash , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn , mi_hash_fn}) - = rnf mi_iface_hash - `seq` rnf mi_mod_hash - `seq` rnf mi_flag_hash - `seq` rnf mi_opt_hash - `seq` rnf mi_hpc_hash - `seq` rnf mi_plugin_hash + = rnf mi_mod_hash `seq` rnf mi_orphan `seq` rnf mi_finsts `seq` rnf mi_exp_hash @@ -810,27 +829,6 @@ completePartialModIface partial decls extra_decls final_exts = partial , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing } --- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array --- buffer 'mi_hi_bytes'. --- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. --- --- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. -addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase -addSourceFingerprint val iface = iface { mi_src_hash_ = val } - --- | Copy fields that aren't serialised to disk to the new 'ModIface_'. --- This includes especially hashes that are usually stored in the interface --- file header and 'mi_top_env'. --- --- We need this function after calling 'shareIface', to make sure the --- 'ModIface_' doesn't lose any information. This function does not discard --- the in-memory byte array buffer 'mi_hi_bytes'. -restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase -restoreFromOldModIface old new = new - { mi_hsc_src_ = mi_hsc_src_ old - , mi_src_hash_ = mi_src_hash_ old - } - set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } @@ -840,8 +838,8 @@ set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } -set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase -set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } +set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -849,9 +847,6 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } -set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase -set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } - set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } @@ -976,7 +971,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} -{-# INLINE mi_usages #-} {-# INLINE mi_exports #-} {-# INLINE mi_used_th #-} {-# INLINE mi_fixities #-} @@ -996,25 +990,23 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_docs #-} {-# INLINE mi_final_exts #-} {-# INLINE mi_ext_fields #-} -{-# INLINE mi_src_hash #-} {-# INLINE mi_hi_bytes #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + Module -> Maybe Module -> HscSource -> Dependencies -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface { mi_module , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -1035,14 +1027,13 @@ pattern ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info } <- PrivateModIface { mi_module_ = mi_module , mi_sig_of_ = mi_sig_of , mi_hsc_src_ = mi_hsc_src , mi_deps_ = mi_deps - , mi_usages_ = mi_usages , mi_exports_ = mi_exports , mi_used_th_ = mi_used_th , mi_fixities_ = mi_fixities @@ -1063,6 +1054,6 @@ pattern ModIface , mi_docs_ = mi_docs , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields - , mi_src_hash_ = mi_src_hash , mi_hi_bytes_ = mi_hi_bytes + , mi_self_recomp_info_ = mi_self_recomp_info } ===================================== compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs ===================================== @@ -0,0 +1,70 @@ +module GHC.Unit.Module.ModIface.SelfRecomp where + +import GHC.Prelude +import GHC.Fingerprint +import GHC.Utils.Outputable +import GHC.Unit.Module.Deps + +import GHC.Utils.Binary + +import Control.DeepSeq + +-- | The information for a module which is only used when deciding whether to recompile +-- itself. In particular the external interface of a module is recorded by the ABI +-- hash +data ModIfaceSelfRecomp = + ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint + -- ^ Hash of the .hs source, used for recompilation checking. + , mi_sr_usages :: [Usage] + -- ^ Usages; kept sorted so that it's easy to decide + -- whether to write a new iface file (changing usages + -- doesn't affect the hash of this module) + -- NOT STRICT! we read this field lazily from the interface file + -- It is *only* consulted by the recompilation checker + + , mi_sr_flag_hash :: !Fingerprint + -- ^ Hash of the important flags used when compiling the module, excluding + -- optimisation flags + , mi_sr_opt_hash :: !Fingerprint + -- ^ Hash of optimisation flags + , mi_sr_hpc_hash :: !Fingerprint + -- ^ Hash of hpc flags + , mi_sr_plugin_hash :: !Fingerprint + -- ^ Hash of plugins + } + + +instance Binary ModIfaceSelfRecomp where + put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do + put_ bh mi_sr_src_hash + lazyPut bh mi_sr_usages + put_ bh mi_sr_flag_hash + put_ bh mi_sr_opt_hash + put_ bh mi_sr_hpc_hash + put_ bh mi_sr_plugin_hash + + get bh = do + src_hash <- get bh + usages <- lazyGet bh + flag_hash <- get bh + opt_hash <- get bh + hpc_hash <- get bh + plugin_hash <- get bh + return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + +instance Outputable ModIfaceSelfRecomp where + ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) + = vcat [text "Self-Recomp" + , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash + , text "usages:" <+> ppr (length mi_sr_usages) + , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "opt hash:" <+> ppr mi_sr_opt_hash + , text "hpc hash:" <+> ppr mi_sr_hpc_hash + , text "plugin hash:" <+> ppr mi_sr_plugin_hash + ])] + +instance NFData ModIfaceSelfRecomp where + -- MP: Note does not deeply force Usages but the old ModIface logic didn't either, so + -- I left it as a shallow force. + rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file ===================================== compiler/ghc.cabal.in ===================================== @@ -955,6 +955,7 @@ Library GHC.Unit.Module.ModDetails GHC.Unit.Module.ModGuts GHC.Unit.Module.ModIface + GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.WholeCoreBindings GHC.Unit.Module.ModSummary GHC.Unit.Module.Status ===================================== docs/users_guide/phases.rst ===================================== @@ -702,6 +702,24 @@ Options affecting code generation depend on the optimisation level. Any definitions which are already included in an interface file (via an unfolding for an exported identifier) are reused. +.. ghc-flag:: -fwrite-self-recomp-info + :shortdesc: Write information for self-recompilation checking in an interface file + :type: dynamic + :category: codegen + + :default: on + + Include information in an interface file which can be used in future to determine + whether we need to recompile a module or can reuse the existing interface. + + This is intended to be turned off in situations where you know you will never try + to recompile a module, such as when compiling a package for distribution. + The advantage is that by omitting unecessary information to do with dependencies + there is less chance of build paths leaking into the interface file and affecting + determinism. + + + .. ghc-flag:: -fobject-code :shortdesc: Generate object code ===================================== hadrian/src/Flavour.hs ===================================== @@ -16,6 +16,7 @@ module Flavour , disableProfiledLibs , enableLinting , enableHaddock + , disableSelfRecompInfo , enableHiCore , useNativeBignum , enableTextWithSIMDUTF @@ -67,6 +68,7 @@ flavourTransformers = M.fromList , "debug_stage1_ghc" =: debugGhc Stage1 , "lint" =: enableLinting , "haddock" =: enableHaddock + , "no_self_recomp" =: disableSelfRecompInfo , "hi_core" =: enableHiCore , "late_ccs" =: enableLateCCS , "boot_nonmoving_gc" =: enableBootNonmovingGc @@ -208,6 +210,17 @@ enableHaddock = [ arg "-haddock" ] +-- | Disable self recompilation information in interface files +disableSelfRecompInfo :: Flavour -> Flavour +disableSelfRecompInfo = + addArgs $ stage1 ? mconcat + [ builder (Ghc CompileHs) ? selfRecomp + ] + where + selfRecomp = mconcat + [ arg "-fno-write-self-recomp-info" + ] + -- | Build stage2 dependencies with options to emit Core into -- interface files which is sufficient to restart code generation. enableHiCore :: Flavour -> Flavour ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,8 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableHaddock performanceFlavour { name = "release" } +releaseFlavour = + -- 1. These interface files will be distributed and the source files never recompiled. + disableSelfRecompInfo + -- 2. Include documentation in the interface for tools such as haddock and HLS to use + $ enableHaddock performanceFlavour { name = "release" } ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -201,6 +201,7 @@ GHC.Unit.Module.Env GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.Warnings GHC.Unit.Module.WholeCoreBindings GHC.Unit.Parser ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -227,6 +227,7 @@ GHC.Unit.Module.Graph GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.ModNodeKey GHC.Unit.Module.ModSummary GHC.Unit.Module.Warnings ===================================== testsuite/tests/driver/self-recomp/Makefile ===================================== @@ -0,0 +1,38 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +TEST_HC_OPTS_NO_RTSOPTS = $(filter-out -rtsopts,$(TEST_HC_OPTS)) + +# ----------------------------------------------------------------------------- +# One-shot compilations, non-hierarchical modules + +# Check that modifying flags doesn't affect interface +SelfRecomp01: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface1 + rm SelfRecomp01.hi + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-self-recomp-info -Iidir -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface2 + diff iface1 iface2 + +# Check that the result of addDependentFile doesn't end up in interface +SelfRecomp02: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp02.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp02.hi > iface + [ -z $(grep iface SelfRecomp02.hs) ] + +# Check that modifying source doesn't affect interface +SelfRecomp03: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface1 + rm SelfRecomp03.hi + echo "" >> SelfRecomp03.hs + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface2 + diff iface1 iface2 + +# Check that if you don't have recompilation info then you always recompile. +SelfRecomp04: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-self-recomp-info -fhide-source-paths + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-self-recomp-info -fhide-source-paths ===================================== testsuite/tests/driver/self-recomp/SelfRecomp01.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp01 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp02.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +module SelfRecomp02 where + +import Language.Haskell.TH.Syntax + +main = $(addDependentFile "SelfRecomp02.hs" >> [| print () |]) ===================================== testsuite/tests/driver/self-recomp/SelfRecomp03.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp03 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.hs ===================================== @@ -0,0 +1 @@ +module SelfRecomp04 where ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.stdout ===================================== @@ -0,0 +1,2 @@ +[1 of 1] Compiling SelfRecomp04 +[1 of 1] Compiling SelfRecomp04 [Old interface lacks recompilation info] ===================================== testsuite/tests/driver/self-recomp/all.T ===================================== @@ -0,0 +1,4 @@ +test('SelfRecomp01', normal, makefile_test, ['SelfRecomp01']) +test('SelfRecomp02', normal, makefile_test, ['SelfRecomp02']) +test('SelfRecomp03', [copy_files], makefile_test, ['SelfRecomp03']) +test('SelfRecomp04', normal, makefile_test, ['SelfRecomp04']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a97a1e28dd5d1f0f28eb359661524aebe610c62e...7161670210e28dc554b3da6313aafe4d777901b8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a97a1e28dd5d1f0f28eb359661524aebe610c62e...7161670210e28dc554b3da6313aafe4d777901b8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/fc1efad5/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 11:52:45 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 06:52:45 -0500 Subject: [Git][ghc/ghc][wip/22188] 2 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67c6e98d185be_6036c3f24c4144fe@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: 7bc4f9e7 by Matthew Pickering at 2025-03-04T11:51:15+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-self-recomp-info which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 29c3d23e by Matthew Pickering at 2025-03-04T11:52:23+00:00 Disable self recomp in release flavour - - - - - 27 changed files: - compiler/GHC.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -104,10 +104,8 @@ module GHC ( mi_module, mi_sig_of, mi_hsc_src, - mi_src_hash, mi_hi_bytes, mi_deps, - mi_usages, mi_exports, mi_used_th, mi_fixities, ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1178,7 +1178,8 @@ defaultFlags settings Opt_ShowErrorContext, Opt_SuppressStgReps, Opt_UnoptimizedCoreForInterpreter, - Opt_SpecialiseIncoherents + Opt_SpecialiseIncoherents, + Opt_WriteSelfRecompInfo ] ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns] ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -692,6 +692,7 @@ data GeneralFlag | Opt_ExposeOverloadedUnfoldings | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code + | Opt_WriteSelfRecompInfo | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1243,11 +1243,11 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h (cg_guts, details) <- liftIO $ hscTidy hsc_env simplified_guts - let !partial_iface = + !partial_iface <- liftIO $ {-# SCC "GHC.Driver.Main.mkPartialIface" #-} -- This `force` saves 2M residency in test T10370 -- See Note [Avoiding space leaks in toIface*] for details. - force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) + fmap force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) return HscRecomp { hscs_guts = cg_guts, hscs_mod_location = ms_location summary, ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -875,10 +875,10 @@ pruneCache hpt summ modl = miKey iface linkable' | Just ms <- M.lookup modl ms_map - , mi_src_hash iface /= ms_hs_hash ms - = emptyHomeModInfoLinkable - | otherwise + , mi_src_hash iface == Just (ms_hs_hash ms) = linkable + | otherwise + = emptyHomeModInfoLinkable -- Using UFM Module is safe for determinism because the map is just used for a transient lookup. The cache should be unique and a key clash is an error. ms_map = M.fromListWith ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,6 +2528,7 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, + flagSpec "write-self-recomp-info" Opt_WriteSelfRecompInfo, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -22,14 +22,12 @@ import GHC.Driver.DynFlags import GHC.Driver.Config import GHC.Driver.Config.Core.Lint ( endPassHscEnvIO ) import GHC.Driver.Config.HsToCore.Ticks -import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env import GHC.Driver.Backend import GHC.Driver.Plugins import GHC.Hs -import GHC.HsToCore.Usage import GHC.HsToCore.Monad import GHC.HsToCore.Errors.Types import GHC.HsToCore.Expr @@ -42,7 +40,7 @@ import GHC.HsToCore.Docs import GHC.Tc.Types import GHC.Tc.Types.Origin ( Position(..) ) -import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceLoad ) +import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances ) import GHC.Tc.Module ( runTcInteractive ) import GHC.Core.Type @@ -100,6 +98,7 @@ import GHC.Unit.Module.Deps import Data.List (partition) import Data.IORef import Data.Traversable (for) +import GHC.Iface.Make (mkRecompUsageInfo) {- ************************************************************************ @@ -127,12 +126,10 @@ deSugar hsc_env tcg_fix_env = fix_env, tcg_inst_env = inst_env, tcg_fam_inst_env = fam_inst_env, - tcg_merged = merged, tcg_warns = warns, tcg_anns = anns, tcg_binds = binds, tcg_imp_specs = imp_specs, - tcg_dependent_files = dependent_files, tcg_ev_binds = ev_binds, tcg_th_foreign_files = th_foreign_files_var, tcg_fords = fords, @@ -228,8 +225,7 @@ deSugar hsc_env ; endPassHscEnvIO hsc_env name_ppr_ctx CoreDesugarOpt ds_binds ds_rules_for_imps - ; let used_names = mkUsedNames tcg_env - pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) + ; let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) home_unit = hsc_home_unit hsc_env ; let deps = mkDependencies home_unit (tcg_mod tcg_env) @@ -237,17 +233,10 @@ deSugar hsc_env (map mi_module pluginModules) ; used_th <- readIORef tc_splice_used - ; dep_files <- readIORef dependent_files ; safe_mode <- finalSafeMode dflags tcg_env - ; (needed_mods, needed_pkgs) <- readIORef (tcg_th_needed_deps tcg_env) - - ; let uc = initUsageConfig hsc_env - ; let plugins = hsc_plugins hsc_env - ; let fc = hsc_FC hsc_env - ; let unit_env = hsc_unit_env hsc_env - ; usages <- initIfaceLoad hsc_env $ - mkUsageInfo uc plugins fc unit_env mod (imp_mods imports) used_names - dep_files merged needed_mods needed_pkgs + + ; usages <- mkRecompUsageInfo hsc_env tcg_env + -- id_mod /= mod when we are processing an hsig, but hsigs -- never desugared and compiled (there's no code!) -- Consequently, this should hold for any ModGuts that make ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -50,7 +50,6 @@ import GHC.Types.Name.Cache import GHC.Types.SrcLoc import GHC.Platform import GHC.Settings.Constants -import GHC.Utils.Fingerprint import GHC.Iface.Type (IfaceType(..), getIfaceType, putIfaceType, ifaceTypeSharedByte) import Control.Monad @@ -115,7 +114,7 @@ readBinIfaceHeader -> CheckHiWay -> TraceBinIFace -> FilePath - -> IO (Fingerprint, ReadBinHandle) + -> IO ReadBinHandle readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do let platform = profilePlatform profile @@ -157,8 +156,7 @@ readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do when (checkHiWay == CheckHiWay) $ errorOnMismatch "mismatched interface file profile tag" tag check_tag - src_hash <- get bh - pure (src_hash, bh) + pure bh -- | Read an interface file. -- @@ -171,12 +169,11 @@ readBinIface -> FilePath -> IO ModIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do - (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path + bh <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path mod_iface <- getIfaceWithExtFields name_cache bh return $ mod_iface - & addSourceFingerprint src_hash getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface @@ -260,7 +257,6 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh (show hiVersion) let tag = profileBuildTag profile put_ bh tag - put_ bh (mi_src_hash mod_iface) putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1259,21 +1259,25 @@ pprModIfaceSimple unit_state iface = -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc pprModIface unit_state iface - = vcat [ text "interface" + = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) + <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash exts)) , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) + , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat + [ nest 2 (text "src_hash:" <+> ppr src) + , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "opt_hash:" <+> ppr opt_hash) + , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) + , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) + , vcat (map pprUsage usages) + ] , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) - , nest 2 (text "flag hash:" <+> ppr (mi_flag_hash exts)) - , nest 2 (text "opt_hash:" <+> ppr (mi_opt_hash exts)) - , nest 2 (text "hpc_hash:" <+> ppr (mi_hpc_hash exts)) - , nest 2 (text "plugin_hash:" <+> ppr (mi_plugin_hash exts)) - , nest 2 (text "src_hash:" <+> ppr (mi_src_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "used TH splices:" <+> ppr (mi_used_th iface)) , nest 2 (text "where") @@ -1282,7 +1286,6 @@ pprModIface unit_state iface , text "defaults:" , nest 2 (vcat (map ppr (mi_defaults iface))) , pprDeps unit_state (mi_deps iface) - , vcat (map pprUsage (mi_usages iface)) , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] @@ -1302,6 +1305,7 @@ pprModIface unit_state iface ] where exts = mi_final_exts iface + pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -13,6 +13,7 @@ module GHC.Iface.Make ( mkPartialIface , mkFullIface , mkIfaceTc + , mkRecompUsageInfo , mkIfaceExports ) where @@ -110,7 +111,7 @@ mkPartialIface :: HscEnv -> ModSummary -> [ImportUserSpec] -> ModGuts - -> PartialModIface + -> IO PartialModIface mkPartialIface hsc_env core_prog mod_details mod_summary import_decls ModGuts{ mg_module = this_mod , mg_hsc_src = hsc_src @@ -125,8 +126,10 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_trust_pkg = self_trust , mg_docs = docs } - = mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust - safe_mode usages docs mod_summary mod_details + = do + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages + return $ mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust + safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code -- generator produced information. @@ -181,9 +184,8 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = restoreFromOldModIface mi res - forceModIface resiface - return resiface + forceModIface res + return res -- | Initial ram buffer to allocate for writing interface files. initBinMemSize :: Int @@ -236,14 +238,11 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_merged = merged, tcg_warns = warns, tcg_hpc = other_hpc_info, - tcg_th_splice_used = tc_splice_used, - tcg_dependent_files = dependent_files + tcg_th_splice_used = tc_splice_used } = do - let used_names = mkUsedNames tc_result let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) let home_unit = hsc_home_unit hsc_env let deps = mkDependencies home_unit @@ -252,48 +251,59 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (map mi_module pluginModules) let hpc_info = emptyHpcInfo other_hpc_info used_th <- readIORef tc_splice_used - dep_files <- (readIORef dependent_files) - (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) - let uc = initUsageConfig hsc_env - plugins = hsc_plugins hsc_env - fc = hsc_FC hsc_env - unit_env = hsc_unit_env hsc_env - -- Do NOT use semantic module here; this_mod in mkUsageInfo - -- is used solely to decide if we should record a dependency - -- or not. When we instantiate a signature, the semantic - -- module is something we want to record dependencies for, - -- but if you pass that in here, we'll decide it's the local - -- module and does not need to be recorded as a dependency. - -- See Note [Identity versus semantic module] - usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env this_mod (imp_mods imports) used_names - dep_files merged needed_links needed_pkgs + usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usage let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info - (imp_trust_own_pkg imports) safe_mode usages - docs mod_summary + (imp_trust_own_pkg imports) safe_mode self_recomp + docs mod_details mkFullIface hsc_env partial_iface Nothing Nothing NoStubs [] +mkRecompUsageInfo :: HscEnv -> TcGblEnv -> IO (Maybe [Usage]) +mkRecompUsageInfo hsc_env tc_result = do + let dflags = hsc_dflags hsc_env + if not (gopt Opt_WriteSelfRecompInfo dflags) + then return Nothing + else do + let used_names = mkUsedNames tc_result + dep_files <- (readIORef (tcg_dependent_files tc_result)) + (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) + let uc = initUsageConfig hsc_env + plugins = hsc_plugins hsc_env + fc = hsc_FC hsc_env + unit_env = hsc_unit_env hsc_env + + -- Do NOT use semantic module here; this_mod in mkUsageInfo + -- is used solely to decide if we should record a dependency + -- or not. When we instantiate a signature, the semantic + -- module is something we want to record dependencies for, + -- but if you pass that in here, we'll decide it's the local + -- module and does not need to be recorded as a dependency. + -- See Note [Identity versus semantic module] + usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env (tcg_mod tc_result) (imp_mods (tcg_imports tc_result)) used_names + dep_files (tcg_merged tc_result) needed_links needed_pkgs + return (Just usages) + mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Bool -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo -> Bool -> SafeHaskellMode - -> [Usage] + -> Maybe ModIfaceSelfRecomp -> Maybe Docs - -> ModSummary -> ModDetails -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode usages - docs mod_summary + hpc_info pkg_trust_req safe_mode self_recomp + docs ModDetails{ md_defaults = defaults, md_insts = insts, md_fam_insts = fam_insts, @@ -350,8 +360,8 @@ mkIface_ hsc_env then Nothing else Just semantic_mod) & set_mi_hsc_src hsc_src + & set_mi_self_recomp self_recomp & set_mi_deps deps - & set_mi_usages usages & set_mi_exports (mkIfaceExports exports) & set_mi_defaults (defaultsToIfaceDefaults defaults) @@ -376,7 +386,6 @@ mkIface_ hsc_env & set_mi_docs docs & set_mi_final_exts () & set_mi_ext_fields emptyExtensibleFields - & set_mi_src_hash (ms_hs_hash mod_summary) & set_mi_hi_bytes PartialIfaceBinHandle where ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -15,6 +15,7 @@ module GHC.Iface.Recomp , CompileReason(..) , recompileRequired , addFingerprints + , mkSelfRecomp ) where @@ -171,6 +172,7 @@ data RecompReason = UnitDepRemoved UnitId | ModulePackageChanged FastString | SourceFileChanged + | NoSelfRecompInfo | ThisUnitIdChanged | ImpurePlugin | PluginsChanged @@ -204,6 +206,7 @@ instance Outputable RecompReason where UnitDepRemoved uid -> ppr uid <+> text "removed" ModulePackageChanged s -> ftext s <+> text "package changed" SourceFileChanged -> text "Source file changed" + NoSelfRecompInfo -> text "Old interface lacks recompilation info" ThisUnitIdChanged -> text "-this-unit-id changed" ImpurePlugin -> text "Impure plugin forced recompilation" PluginsChanged -> text "Plugins changed" @@ -283,7 +286,7 @@ check_old_iface hsc_env mod_summary maybe_iface logger = hsc_logger hsc_env getIface = case maybe_iface of - Just _ -> do + Just {} -> do trace_if logger (text "We already have the old interface for" <+> ppr (ms_mod mod_summary)) return maybe_iface @@ -354,7 +357,9 @@ check_old_iface hsc_env mod_summary maybe_iface -- should check versions because some packages -- might have changed or gone away. Just iface -> - check_dyn_hi iface $ checkVersions hsc_env mod_summary iface + case mi_self_recomp_info iface of + Nothing -> return $ outOfDateItemBecause NoSelfRecompInfo Nothing + Just sr_info -> check_dyn_hi iface $ checkVersions hsc_env mod_summary iface sr_info -- | Check if a module is still the same 'version'. -- @@ -370,8 +375,9 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface + -> ModIfaceSelfRecomp -> IfG (MaybeValidated ModIface) -checkVersions hsc_env mod_summary iface +checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger (text "Considering whether compilation is required for" <+> ppr (mi_module iface) <> colon) @@ -380,23 +386,22 @@ checkVersions hsc_env mod_summary iface -- but we ALSO must make sure the instantiation matches up. See -- test case bkpcabal04! ; hsc_env <- getTopEnv - ; if mi_src_hash iface /= ms_hs_hash mod_summary + ; if mi_sr_src_hash self_recomp /= ms_hs_hash mod_summary then return $ outOfDateItemBecause SourceFileChanged Nothing else do { ; if not (isHomeModule home_unit (mi_module iface)) then return $ outOfDateItemBecause ThisUnitIdChanged Nothing else do { - ; recomp <- liftIO $ checkFlagHash hsc_env iface - `recompThen` checkOptimHash hsc_env iface - `recompThen` checkHpcHash hsc_env iface - `recompThen` checkMergedSignatures hsc_env mod_summary iface + ; recomp <- liftIO $ checkFlagHash hsc_env (mi_module iface) self_recomp + `recompThen` checkOptimHash hsc_env self_recomp + `recompThen` checkHpcHash hsc_env self_recomp + `recompThen` checkMergedSignatures hsc_env mod_summary self_recomp `recompThen` checkHsig logger home_unit mod_summary iface `recompThen` pure (checkHie dflags mod_summary) ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { ; recomp <- checkDependencies hsc_env mod_summary iface ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { - ; recomp <- checkPlugins (hsc_plugins hsc_env) iface + ; recomp <- checkPlugins (hsc_plugins hsc_env) self_recomp ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { - -- Source code unchanged and no errors yet... carry on -- -- First put the dependent-module info, read from the old @@ -411,7 +416,7 @@ checkVersions hsc_env mod_summary iface ; updateEps_ $ \eps -> eps { eps_is_boot = mkModDeps $ dep_boot_mods (mi_deps iface) } } ; recomp <- checkList [checkModUsage (hsc_FC hsc_env) u - | u <- mi_usages iface] + | u <- mi_sr_usages self_recomp] ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { ; return $ UpToDateItem iface }}}}}}} @@ -423,11 +428,11 @@ checkVersions hsc_env mod_summary iface -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIface -> IfG RecompileRequired -checkPlugins plugins iface = liftIO $ do +checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp - let old_fingerprint = mi_plugin_hash (mi_final_exts iface) + let old_fingerprint = mi_sr_plugin_hash self_recomp return $ pluginRecompileToRecompileRequired old_fingerprint new_fingerprint recomp recompPlugins :: Plugins -> IO PluginRecompile @@ -516,11 +521,11 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> ModIface -> IO RecompileRequired -checkFlagHash hsc_env iface = do +checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_flag_hash (mi_final_exts iface) - new_hash <- fingerprintDynFlags hsc_env (mi_module iface) putNameLiterally + let old_hash = mi_sr_flag_hash self_recomp + new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally case old_hash == new_hash of True -> up_to_date logger (text "Module flags unchanged") False -> out_of_date_hash logger FlagsChanged @@ -528,10 +533,10 @@ checkFlagHash hsc_env iface = do old_hash new_hash -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIface -> IO RecompileRequired +checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env - let old_hash = mi_opt_hash (mi_final_exts iface) + let old_hash = mi_sr_opt_hash iface new_hash <- fingerprintOptFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -544,10 +549,10 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIface -> IO RecompileRequired -checkHpcHash hsc_env iface = do +checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_hpc_hash (mi_final_exts iface) + let old_hash = mi_sr_hpc_hash self_recomp new_hash <- fingerprintHpcFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -561,11 +566,11 @@ checkHpcHash hsc_env iface = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIface -> IO RecompileRequired -checkMergedSignatures hsc_env mod_summary iface = do +checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env - let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_usages iface ] + let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_sr_usages self_recomp ] new_merged = case lookupUniqMap (requirementContext unit_state) (ms_mod_name mod_summary) of Nothing -> [] @@ -939,6 +944,28 @@ we use is: -} +-- | Compute the information needed for self-recompilation checking. This +-- information can be computed before the backend phase. +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp hsc_env this_mod src_hash usages = do + let dflags = hsc_dflags hsc_env + + flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + + opt_hash <- fingerprintOptFlags dflags putNameLiterally + + hpc_hash <- fingerprintHpcFlags dflags putNameLiterally + + plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + + return (ModIfaceSelfRecomp + { mi_sr_flag_hash = flag_hash + , mi_sr_hpc_hash = hpc_hash + , mi_sr_opt_hash = opt_hash + , mi_sr_plugin_hash = plugin_hash + , mi_sr_src_hash = src_hash + , mi_sr_usages = usages }) + -- | Add fingerprints for top-level declarations to a 'ModIface'. -- -- See Note [Fingerprinting IfaceDecls] @@ -1213,18 +1240,6 @@ addFingerprints hsc_env iface0 sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - -- the flag hash depends on: - -- - (some of) dflags - -- it returns two hashes, one that shouldn't change - -- the abi hash and one that should - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally - - opt_hash <- fingerprintOptFlags dflags putNameLiterally - - hpc_hash <- fingerprintHpcFlags dflags putNameLiterally - - plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) - -- the ABI hash depends on: -- - decls -- - export list @@ -1238,6 +1253,7 @@ addFingerprints hsc_env iface0 mi_warns iface0, mi_foreign iface0) + -- The interface hash depends on: -- - the ABI hash, plus -- - the source file hash, @@ -1246,21 +1262,17 @@ addFingerprints hsc_env iface0 -- - deps (home and external packages, dependent files) -- - hpc iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - mi_src_hash iface0, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_usages iface0, - sorted_deps, - mi_hpc iface0) + (mod_hash, + mi_src_hash iface0, + ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache + mi_usages iface0, + sorted_deps, + mi_hpc iface0) let final_iface_exts = ModIfaceBackend - { mi_iface_hash = iface_hash - , mi_mod_hash = mod_hash - , mi_flag_hash = flag_hash - , mi_opt_hash = opt_hash - , mi_hpc_hash = hpc_hash - , mi_plugin_hash = plugin_hash + { mi_mod_hash = mod_hash + , mi_iface_hash = iface_hash , mi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts @@ -1281,12 +1293,12 @@ addFingerprints hsc_env iface0 where this_mod = mi_module iface0 semantic_mod = mi_semantic_module iface0 - dflags = hsc_dflags hsc_env (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) ann_fn = mkIfaceAnnCache (mi_anns iface0) + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the -- current module). ===================================== compiler/GHC/Unit/Module/ModGuts.hs ===================================== @@ -53,7 +53,7 @@ data ModGuts mg_exports :: ![AvailInfo], -- ^ What it exports mg_deps :: !Dependencies, -- ^ What it depends on, directly or -- otherwise - mg_usages :: ![Usage], -- ^ What was used? Used for interfaces. + mg_usages :: !(Maybe [Usage]), -- ^ What was used? Used for interfaces. mg_used_th :: !Bool, -- ^ Did we run a TH splice? mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -15,7 +15,6 @@ module GHC.Unit.Module.ModIface , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -36,19 +35,16 @@ module GHC.Unit.Module.ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info ) , pattern ModIface - , restoreFromOldModIface - , addSourceFingerprint , set_mi_module , set_mi_sig_of , set_mi_hsc_src - , set_mi_src_hash + , set_mi_self_recomp , set_mi_hi_bytes , set_mi_deps - , set_mi_usages , set_mi_exports , set_mi_used_th , set_mi_fixities @@ -73,6 +69,8 @@ module GHC.Unit.Module.ModIface , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) + , ModIfaceSelfRecomp (..) + , withSelfRecomp , IfaceDeclExts , IfaceBackendExts , IfaceExport @@ -85,6 +83,12 @@ module GHC.Unit.Module.ModIface , mi_semantic_module , mi_free_holes , mi_mnwib + , mi_flag_hash + , mi_opt_hash + , mi_hpc_hash + , mi_plugin_hash + , mi_src_hash + , mi_usages , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,6 +110,8 @@ import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.ModIface.SelfRecomp + import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env @@ -150,19 +156,10 @@ type ModIface = ModIface_ 'ModIfaceFinal -- * Or computed just before writing the iface to disk. (Hashes) -- In order to fully instantiate it. data ModIfaceBackend = ModIfaceBackend - { mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_mod_hash :: !Fingerprint + { mi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_flag_hash :: !Fingerprint - -- ^ Hash of the important flags used when compiling the module, excluding - -- optimisation flags - , mi_opt_hash :: !Fingerprint - -- ^ Hash of optimisation flags - , mi_hpc_hash :: !Fingerprint - -- ^ Hash of hpc flags - , mi_plugin_hash :: !Fingerprint - -- ^ Hash of plugins + , mi_iface_hash :: !Fingerprint + -- ^ Hash of the whole interface , mi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans , mi_finsts :: !WhetherHasFamInst @@ -218,6 +215,50 @@ data IfaceBinHandle (phase :: ModIfacePhase) where -- (e.g., set to 'Nothing'). FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal + +withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp iface nk jk = + case mi_self_recomp_info iface of + Nothing -> nk + Just x -> jk x + +{- +Note [Self recompilation information in interface files] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +The flag -fwrite-self-recomp-info controls whether +interface files contain the information necessary to answer the +question: + + Do I need to recompile myself or is this current interface file + suitable? + +Why? Most packages are only built once either by a distribution or cabal +and then placed into an immutable store, after which we will never ask +this question. Therefore we can derive two benefits from omitting this +information. + +* Primary motivation: It vastly reduces the surface area for creating + non-deterministic interface files. See issue #10424 which motivated a + proper fix to that issue. Distributions have long contained versions + of GHC which just have broken self-recompilation checking (in order to + get deterministic interface files). + +* Secondary motivation: This reduces the size of interface files + slightly.. the `mi_usages` field can be quite big but probably this + isn't such a great benefit. + +* Third motivation: Conceptually clarity about which parts of an + interface file are used in order to **communicate** with subsequent + packages about the **interface** for a module. And which parts are + used to self-communicate during recompilation checking. + +The main tracking issue is #22188 but fixes issues such as #10424 in a +proper way. + +-} + + -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, -- and can be written out to an interface file. The 'ModDetails is after @@ -245,16 +286,6 @@ data ModIface_ (phase :: ModIfacePhase) -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages_ :: [Usage], - -- ^ Usages; kept sorted so that it's easy to decide - -- whether to write a new iface file (changing usages - -- doesn't affect the hash of this module) - -- NOT STRICT! we read this field lazily from the interface file - -- It is *only* consulted by the recompilation checker - -- - -- The elements must be *deterministically* sorted to guarantee - -- deterministic interface files - mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier @@ -352,13 +383,15 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash_ :: !Fingerprint, - -- ^ Hash of the .hs source, used for recompilation checking. - mi_hi_bytes_ :: !(IfaceBinHandle phase) + mi_hi_bytes_ :: !(IfaceBinHandle phase), -- ^ A serialised in-memory buffer of this 'ModIface'. -- If this handle is given, we can avoid serialising the 'ModIface' -- when writing this 'ModIface' to disk, and write this buffer to disk instead. -- See Note [Sharing of ModIface]. + + mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] } -- Enough information to reconstruct the top level environment for a module @@ -404,6 +437,24 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} +mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ + +mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ + +mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ + +mi_src_hash :: ModIface_ phase -> Maybe Fingerprint +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ + +mi_usages :: ModIface_ phase -> Maybe [Usage] +mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ + +mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ + -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. mi_boot :: ModIface -> IsBootInterface @@ -461,9 +512,6 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance - -- because we are going to write it - -- out separately in the actual file mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then @@ -471,7 +519,6 @@ instance Binary ModIface where -- the byte array. -- See Note [Private fields in ModIface] mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_fixities_ = fixities, @@ -493,13 +540,10 @@ instance Binary ModIface where mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file + mi_self_recomp_info_ = self_recomp, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -508,16 +552,12 @@ instance Binary ModIface where put_ bh mod put_ bh sig_of put_ bh hsc_src - put_ bh iface_hash + put_ bh self_recomp put_ bh mod_hash - put_ bh flag_hash - put_ bh opt_hash - put_ bh hpc_hash - put_ bh plugin_hash + put_ bh iface_hash put_ bh orphan put_ bh hasFamInsts lazyPut bh deps - lazyPut bh usages put_ bh exports put_ bh exp_hash put_ bh used_th @@ -543,16 +583,12 @@ instance Binary ModIface where mod <- get bh sig_of <- get bh hsc_src <- get bh - iface_hash <- get bh + self_recomp_info <- get bh mod_hash <- get bh - flag_hash <- get bh - opt_hash <- get bh - hpc_hash <- get bh - plugin_hash <- get bh + iface_hash <- get bh orphan <- get bh hasFamInsts <- get bh deps <- lazyGet bh - usages <- {-# SCC "bin_usages" #-} lazyGet bh exports <- {-# SCC "bin_exports" #-} get bh exp_hash <- get bh used_th <- get bh @@ -577,15 +613,12 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = fingerprint0, -- placeholder because this is dealt - -- with specially when the file is read mi_hi_bytes_ = -- We can't populate this field here, as we are -- missing the 'mi_ext_fields_' field, which is -- handled in 'getIfaceWithExtFields'. FullIfaceBinHandle Strict.Nothing, mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_anns_ = anns, @@ -607,13 +640,10 @@ instance Binary ModIface where mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read + mi_self_recomp_info_ = self_recomp_info, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -632,10 +662,8 @@ emptyPartialModIface mod { mi_module_ = mod, mi_sig_of_ = Nothing, mi_hsc_src_ = HsSrcFile, - mi_src_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_usages_ = [], mi_exports_ = [], mi_used_th_ = False, mi_fixities_ = [], @@ -655,21 +683,19 @@ emptyPartialModIface mod mi_complete_matches_ = [], mi_docs_ = Nothing, mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields + mi_ext_fields_ = emptyExtensibleFields, + mi_self_recomp_info_ = Nothing } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) { mi_decls_ = [] + , mi_self_recomp_info_ = Nothing , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing , mi_final_exts_ = ModIfaceBackend - { mi_iface_hash = fingerprint0, - mi_mod_hash = fingerprint0, - mi_flag_hash = fingerprint0, - mi_opt_hash = fingerprint0, - mi_hpc_hash = fingerprint0, - mi_plugin_hash = fingerprint0, + { mi_mod_hash = fingerprint0, + mi_iface_hash = fingerprint0, mi_orphan = False, mi_finsts = False, mi_exp_hash = fingerprint0, @@ -699,18 +725,17 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_, mi_src_hash_ }) + , mi_ext_fields_ }) = rnf mi_module_ `seq` rnf mi_sig_of_ `seq` mi_hsc_src_ `seq` mi_hi_bytes_ `seq` mi_deps_ - `seq` mi_usages_ `seq` mi_exports_ `seq` rnf mi_used_th_ `seq` mi_fixities_ @@ -731,20 +756,14 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_docs_ `seq` mi_final_exts_ `seq` mi_ext_fields_ - `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_iface_hash, mi_mod_hash, mi_flag_hash, mi_opt_hash - , mi_hpc_hash, mi_plugin_hash, mi_orphan, mi_finsts, mi_exp_hash + rnf (ModIfaceBackend{ mi_mod_hash + , mi_orphan, mi_finsts, mi_exp_hash , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn , mi_hash_fn}) - = rnf mi_iface_hash - `seq` rnf mi_mod_hash - `seq` rnf mi_flag_hash - `seq` rnf mi_opt_hash - `seq` rnf mi_hpc_hash - `seq` rnf mi_plugin_hash + = rnf mi_mod_hash `seq` rnf mi_orphan `seq` rnf mi_finsts `seq` rnf mi_exp_hash @@ -810,27 +829,6 @@ completePartialModIface partial decls extra_decls final_exts = partial , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing } --- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array --- buffer 'mi_hi_bytes'. --- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. --- --- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. -addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase -addSourceFingerprint val iface = iface { mi_src_hash_ = val } - --- | Copy fields that aren't serialised to disk to the new 'ModIface_'. --- This includes especially hashes that are usually stored in the interface --- file header and 'mi_top_env'. --- --- We need this function after calling 'shareIface', to make sure the --- 'ModIface_' doesn't lose any information. This function does not discard --- the in-memory byte array buffer 'mi_hi_bytes'. -restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase -restoreFromOldModIface old new = new - { mi_hsc_src_ = mi_hsc_src_ old - , mi_src_hash_ = mi_src_hash_ old - } - set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } @@ -840,8 +838,8 @@ set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } -set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase -set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } +set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -849,9 +847,6 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } -set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase -set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } - set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } @@ -976,7 +971,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} -{-# INLINE mi_usages #-} {-# INLINE mi_exports #-} {-# INLINE mi_used_th #-} {-# INLINE mi_fixities #-} @@ -996,25 +990,23 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_docs #-} {-# INLINE mi_final_exts #-} {-# INLINE mi_ext_fields #-} -{-# INLINE mi_src_hash #-} {-# INLINE mi_hi_bytes #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + Module -> Maybe Module -> HscSource -> Dependencies -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface { mi_module , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -1035,14 +1027,13 @@ pattern ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info } <- PrivateModIface { mi_module_ = mi_module , mi_sig_of_ = mi_sig_of , mi_hsc_src_ = mi_hsc_src , mi_deps_ = mi_deps - , mi_usages_ = mi_usages , mi_exports_ = mi_exports , mi_used_th_ = mi_used_th , mi_fixities_ = mi_fixities @@ -1063,6 +1054,6 @@ pattern ModIface , mi_docs_ = mi_docs , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields - , mi_src_hash_ = mi_src_hash , mi_hi_bytes_ = mi_hi_bytes + , mi_self_recomp_info_ = mi_self_recomp_info } ===================================== compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs ===================================== @@ -0,0 +1,70 @@ +module GHC.Unit.Module.ModIface.SelfRecomp where + +import GHC.Prelude +import GHC.Fingerprint +import GHC.Utils.Outputable +import GHC.Unit.Module.Deps + +import GHC.Utils.Binary + +import Control.DeepSeq + +-- | The information for a module which is only used when deciding whether to recompile +-- itself. In particular the external interface of a module is recorded by the ABI +-- hash +data ModIfaceSelfRecomp = + ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint + -- ^ Hash of the .hs source, used for recompilation checking. + , mi_sr_usages :: [Usage] + -- ^ Usages; kept sorted so that it's easy to decide + -- whether to write a new iface file (changing usages + -- doesn't affect the hash of this module) + -- NOT STRICT! we read this field lazily from the interface file + -- It is *only* consulted by the recompilation checker + + , mi_sr_flag_hash :: !Fingerprint + -- ^ Hash of the important flags used when compiling the module, excluding + -- optimisation flags + , mi_sr_opt_hash :: !Fingerprint + -- ^ Hash of optimisation flags + , mi_sr_hpc_hash :: !Fingerprint + -- ^ Hash of hpc flags + , mi_sr_plugin_hash :: !Fingerprint + -- ^ Hash of plugins + } + + +instance Binary ModIfaceSelfRecomp where + put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do + put_ bh mi_sr_src_hash + lazyPut bh mi_sr_usages + put_ bh mi_sr_flag_hash + put_ bh mi_sr_opt_hash + put_ bh mi_sr_hpc_hash + put_ bh mi_sr_plugin_hash + + get bh = do + src_hash <- get bh + usages <- lazyGet bh + flag_hash <- get bh + opt_hash <- get bh + hpc_hash <- get bh + plugin_hash <- get bh + return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + +instance Outputable ModIfaceSelfRecomp where + ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) + = vcat [text "Self-Recomp" + , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash + , text "usages:" <+> ppr (length mi_sr_usages) + , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "opt hash:" <+> ppr mi_sr_opt_hash + , text "hpc hash:" <+> ppr mi_sr_hpc_hash + , text "plugin hash:" <+> ppr mi_sr_plugin_hash + ])] + +instance NFData ModIfaceSelfRecomp where + -- MP: Note does not deeply force Usages but the old ModIface logic didn't either, so + -- I left it as a shallow force. + rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file ===================================== compiler/ghc.cabal.in ===================================== @@ -955,6 +955,7 @@ Library GHC.Unit.Module.ModDetails GHC.Unit.Module.ModGuts GHC.Unit.Module.ModIface + GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.WholeCoreBindings GHC.Unit.Module.ModSummary GHC.Unit.Module.Status ===================================== docs/users_guide/phases.rst ===================================== @@ -702,6 +702,24 @@ Options affecting code generation depend on the optimisation level. Any definitions which are already included in an interface file (via an unfolding for an exported identifier) are reused. +.. ghc-flag:: -fwrite-self-recomp-info + :shortdesc: Write information for self-recompilation checking in an interface file + :type: dynamic + :category: codegen + + :default: on + + Include information in an interface file which can be used in future to determine + whether we need to recompile a module or can reuse the existing interface. + + This is intended to be turned off in situations where you know you will never try + to recompile a module, such as when compiling a package for distribution. + The advantage is that by omitting unecessary information to do with dependencies + there is less chance of build paths leaking into the interface file and affecting + determinism. + + + .. ghc-flag:: -fobject-code :shortdesc: Generate object code ===================================== hadrian/src/Flavour.hs ===================================== @@ -16,6 +16,7 @@ module Flavour , disableProfiledLibs , enableLinting , enableHaddock + , disableSelfRecompInfo , enableHiCore , useNativeBignum , enableTextWithSIMDUTF @@ -67,6 +68,7 @@ flavourTransformers = M.fromList , "debug_stage1_ghc" =: debugGhc Stage1 , "lint" =: enableLinting , "haddock" =: enableHaddock + , "no_self_recomp" =: disableSelfRecompInfo , "hi_core" =: enableHiCore , "late_ccs" =: enableLateCCS , "boot_nonmoving_gc" =: enableBootNonmovingGc @@ -208,6 +210,17 @@ enableHaddock = [ arg "-haddock" ] +-- | Disable self recompilation information in interface files +disableSelfRecompInfo :: Flavour -> Flavour +disableSelfRecompInfo = + addArgs $ stage1 ? mconcat + [ builder (Ghc CompileHs) ? selfRecomp + ] + where + selfRecomp = mconcat + [ arg "-fno-write-self-recomp-info" + ] + -- | Build stage2 dependencies with options to emit Core into -- interface files which is sufficient to restart code generation. enableHiCore :: Flavour -> Flavour ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,8 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableHaddock performanceFlavour { name = "release" } +releaseFlavour = + -- 1. These interface files will be distributed and the source files never recompiled. + disableSelfRecompInfo + -- 2. Include documentation in the interface for tools such as haddock and HLS to use + $ enableHaddock performanceFlavour { name = "release" } ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -201,6 +201,7 @@ GHC.Unit.Module.Env GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.Warnings GHC.Unit.Module.WholeCoreBindings GHC.Unit.Parser ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -227,6 +227,7 @@ GHC.Unit.Module.Graph GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.ModNodeKey GHC.Unit.Module.ModSummary GHC.Unit.Module.Warnings ===================================== testsuite/tests/driver/self-recomp/Makefile ===================================== @@ -0,0 +1,38 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +TEST_HC_OPTS_NO_RTSOPTS = $(filter-out -rtsopts,$(TEST_HC_OPTS)) + +# ----------------------------------------------------------------------------- +# One-shot compilations, non-hierarchical modules + +# Check that modifying flags doesn't affect interface +SelfRecomp01: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface1 + rm SelfRecomp01.hi + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-self-recomp-info -Iidir -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface2 + diff iface1 iface2 + +# Check that the result of addDependentFile doesn't end up in interface +SelfRecomp02: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp02.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp02.hi > iface + [ -z $(grep iface SelfRecomp02.hs) ] + +# Check that modifying source doesn't affect interface +SelfRecomp03: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface1 + rm SelfRecomp03.hi + echo "" >> SelfRecomp03.hs + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface2 + diff iface1 iface2 + +# Check that if you don't have recompilation info then you always recompile. +SelfRecomp04: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-self-recomp-info -fhide-source-paths + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-self-recomp-info -fhide-source-paths ===================================== testsuite/tests/driver/self-recomp/SelfRecomp01.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp01 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp02.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +module SelfRecomp02 where + +import Language.Haskell.TH.Syntax + +main = $(addDependentFile "SelfRecomp02.hs" >> [| print () |]) ===================================== testsuite/tests/driver/self-recomp/SelfRecomp03.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp03 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.hs ===================================== @@ -0,0 +1 @@ +module SelfRecomp04 where ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.stdout ===================================== @@ -0,0 +1,2 @@ +[1 of 1] Compiling SelfRecomp04 +[1 of 1] Compiling SelfRecomp04 [Old interface lacks recompilation info] ===================================== testsuite/tests/driver/self-recomp/all.T ===================================== @@ -0,0 +1,4 @@ +test('SelfRecomp01', normal, makefile_test, ['SelfRecomp01']) +test('SelfRecomp02', normal, makefile_test, ['SelfRecomp02']) +test('SelfRecomp03', [copy_files], makefile_test, ['SelfRecomp03']) +test('SelfRecomp04', normal, makefile_test, ['SelfRecomp04']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7161670210e28dc554b3da6313aafe4d777901b8...29c3d23ebbd9ff562d94e9a82e6aa5203b01681c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7161670210e28dc554b3da6313aafe4d777901b8...29c3d23ebbd9ff562d94e9a82e6aa5203b01681c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/1f51b52e/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 13:42:27 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 08:42:27 -0500 Subject: [Git][ghc/ghc][wip/22188] 2 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67c703436debf_a5f4839f91892349@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: 5679675c by Matthew Pickering at 2025-03-04T13:35:59+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-self-recomp-info which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 9c0a9d5a by Matthew Pickering at 2025-03-04T13:35:59+00:00 Disable self recomp in release flavour - - - - - 27 changed files: - compiler/GHC.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -104,10 +104,8 @@ module GHC ( mi_module, mi_sig_of, mi_hsc_src, - mi_src_hash, mi_hi_bytes, mi_deps, - mi_usages, mi_exports, mi_used_th, mi_fixities, ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1178,7 +1178,8 @@ defaultFlags settings Opt_ShowErrorContext, Opt_SuppressStgReps, Opt_UnoptimizedCoreForInterpreter, - Opt_SpecialiseIncoherents + Opt_SpecialiseIncoherents, + Opt_WriteSelfRecompInfo ] ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns] ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -692,6 +692,7 @@ data GeneralFlag | Opt_ExposeOverloadedUnfoldings | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code + | Opt_WriteSelfRecompInfo | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1243,11 +1243,11 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h (cg_guts, details) <- liftIO $ hscTidy hsc_env simplified_guts - let !partial_iface = + !partial_iface <- liftIO $ {-# SCC "GHC.Driver.Main.mkPartialIface" #-} -- This `force` saves 2M residency in test T10370 -- See Note [Avoiding space leaks in toIface*] for details. - force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) + fmap force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) return HscRecomp { hscs_guts = cg_guts, hscs_mod_location = ms_location summary, ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -875,10 +875,10 @@ pruneCache hpt summ modl = miKey iface linkable' | Just ms <- M.lookup modl ms_map - , mi_src_hash iface /= ms_hs_hash ms - = emptyHomeModInfoLinkable - | otherwise + , mi_src_hash iface == Just (ms_hs_hash ms) = linkable + | otherwise + = emptyHomeModInfoLinkable -- Using UFM Module is safe for determinism because the map is just used for a transient lookup. The cache should be unique and a key clash is an error. ms_map = M.fromListWith ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,6 +2528,7 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, + flagSpec "write-self-recomp-info" Opt_WriteSelfRecompInfo, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -22,14 +22,12 @@ import GHC.Driver.DynFlags import GHC.Driver.Config import GHC.Driver.Config.Core.Lint ( endPassHscEnvIO ) import GHC.Driver.Config.HsToCore.Ticks -import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env import GHC.Driver.Backend import GHC.Driver.Plugins import GHC.Hs -import GHC.HsToCore.Usage import GHC.HsToCore.Monad import GHC.HsToCore.Errors.Types import GHC.HsToCore.Expr @@ -42,7 +40,7 @@ import GHC.HsToCore.Docs import GHC.Tc.Types import GHC.Tc.Types.Origin ( Position(..) ) -import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceLoad ) +import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances ) import GHC.Tc.Module ( runTcInteractive ) import GHC.Core.Type @@ -100,6 +98,7 @@ import GHC.Unit.Module.Deps import Data.List (partition) import Data.IORef import Data.Traversable (for) +import GHC.Iface.Make (mkRecompUsageInfo) {- ************************************************************************ @@ -127,12 +126,10 @@ deSugar hsc_env tcg_fix_env = fix_env, tcg_inst_env = inst_env, tcg_fam_inst_env = fam_inst_env, - tcg_merged = merged, tcg_warns = warns, tcg_anns = anns, tcg_binds = binds, tcg_imp_specs = imp_specs, - tcg_dependent_files = dependent_files, tcg_ev_binds = ev_binds, tcg_th_foreign_files = th_foreign_files_var, tcg_fords = fords, @@ -228,8 +225,7 @@ deSugar hsc_env ; endPassHscEnvIO hsc_env name_ppr_ctx CoreDesugarOpt ds_binds ds_rules_for_imps - ; let used_names = mkUsedNames tcg_env - pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) + ; let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) home_unit = hsc_home_unit hsc_env ; let deps = mkDependencies home_unit (tcg_mod tcg_env) @@ -237,17 +233,10 @@ deSugar hsc_env (map mi_module pluginModules) ; used_th <- readIORef tc_splice_used - ; dep_files <- readIORef dependent_files ; safe_mode <- finalSafeMode dflags tcg_env - ; (needed_mods, needed_pkgs) <- readIORef (tcg_th_needed_deps tcg_env) - - ; let uc = initUsageConfig hsc_env - ; let plugins = hsc_plugins hsc_env - ; let fc = hsc_FC hsc_env - ; let unit_env = hsc_unit_env hsc_env - ; usages <- initIfaceLoad hsc_env $ - mkUsageInfo uc plugins fc unit_env mod (imp_mods imports) used_names - dep_files merged needed_mods needed_pkgs + + ; usages <- mkRecompUsageInfo hsc_env tcg_env + -- id_mod /= mod when we are processing an hsig, but hsigs -- never desugared and compiled (there's no code!) -- Consequently, this should hold for any ModGuts that make ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -50,7 +50,6 @@ import GHC.Types.Name.Cache import GHC.Types.SrcLoc import GHC.Platform import GHC.Settings.Constants -import GHC.Utils.Fingerprint import GHC.Iface.Type (IfaceType(..), getIfaceType, putIfaceType, ifaceTypeSharedByte) import Control.Monad @@ -115,7 +114,7 @@ readBinIfaceHeader -> CheckHiWay -> TraceBinIFace -> FilePath - -> IO (Fingerprint, ReadBinHandle) + -> IO ReadBinHandle readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do let platform = profilePlatform profile @@ -157,8 +156,7 @@ readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do when (checkHiWay == CheckHiWay) $ errorOnMismatch "mismatched interface file profile tag" tag check_tag - src_hash <- get bh - pure (src_hash, bh) + pure bh -- | Read an interface file. -- @@ -171,12 +169,11 @@ readBinIface -> FilePath -> IO ModIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do - (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path + bh <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path mod_iface <- getIfaceWithExtFields name_cache bh return $ mod_iface - & addSourceFingerprint src_hash getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface @@ -260,7 +257,6 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh (show hiVersion) let tag = profileBuildTag profile put_ bh tag - put_ bh (mi_src_hash mod_iface) putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1259,21 +1259,25 @@ pprModIfaceSimple unit_state iface = -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc pprModIface unit_state iface - = vcat [ text "interface" + = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) + <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash exts)) , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) + , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat + [ nest 2 (text "src_hash:" <+> ppr src) + , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "opt_hash:" <+> ppr opt_hash) + , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) + , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) + , vcat (map pprUsage usages) + ] , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) - , nest 2 (text "flag hash:" <+> ppr (mi_flag_hash exts)) - , nest 2 (text "opt_hash:" <+> ppr (mi_opt_hash exts)) - , nest 2 (text "hpc_hash:" <+> ppr (mi_hpc_hash exts)) - , nest 2 (text "plugin_hash:" <+> ppr (mi_plugin_hash exts)) - , nest 2 (text "src_hash:" <+> ppr (mi_src_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "used TH splices:" <+> ppr (mi_used_th iface)) , nest 2 (text "where") @@ -1282,7 +1286,6 @@ pprModIface unit_state iface , text "defaults:" , nest 2 (vcat (map ppr (mi_defaults iface))) , pprDeps unit_state (mi_deps iface) - , vcat (map pprUsage (mi_usages iface)) , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] @@ -1302,6 +1305,7 @@ pprModIface unit_state iface ] where exts = mi_final_exts iface + pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -13,6 +13,7 @@ module GHC.Iface.Make ( mkPartialIface , mkFullIface , mkIfaceTc + , mkRecompUsageInfo , mkIfaceExports ) where @@ -110,7 +111,7 @@ mkPartialIface :: HscEnv -> ModSummary -> [ImportUserSpec] -> ModGuts - -> PartialModIface + -> IO PartialModIface mkPartialIface hsc_env core_prog mod_details mod_summary import_decls ModGuts{ mg_module = this_mod , mg_hsc_src = hsc_src @@ -125,8 +126,10 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_trust_pkg = self_trust , mg_docs = docs } - = mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust - safe_mode usages docs mod_summary mod_details + = do + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages + return $ mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust + safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code -- generator produced information. @@ -181,9 +184,8 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = restoreFromOldModIface mi res - forceModIface resiface - return resiface + forceModIface res + return res -- | Initial ram buffer to allocate for writing interface files. initBinMemSize :: Int @@ -236,14 +238,11 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_merged = merged, tcg_warns = warns, tcg_hpc = other_hpc_info, - tcg_th_splice_used = tc_splice_used, - tcg_dependent_files = dependent_files + tcg_th_splice_used = tc_splice_used } = do - let used_names = mkUsedNames tc_result let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) let home_unit = hsc_home_unit hsc_env let deps = mkDependencies home_unit @@ -252,48 +251,59 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (map mi_module pluginModules) let hpc_info = emptyHpcInfo other_hpc_info used_th <- readIORef tc_splice_used - dep_files <- (readIORef dependent_files) - (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) - let uc = initUsageConfig hsc_env - plugins = hsc_plugins hsc_env - fc = hsc_FC hsc_env - unit_env = hsc_unit_env hsc_env - -- Do NOT use semantic module here; this_mod in mkUsageInfo - -- is used solely to decide if we should record a dependency - -- or not. When we instantiate a signature, the semantic - -- module is something we want to record dependencies for, - -- but if you pass that in here, we'll decide it's the local - -- module and does not need to be recorded as a dependency. - -- See Note [Identity versus semantic module] - usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env this_mod (imp_mods imports) used_names - dep_files merged needed_links needed_pkgs + usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usage let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info - (imp_trust_own_pkg imports) safe_mode usages - docs mod_summary + (imp_trust_own_pkg imports) safe_mode self_recomp + docs mod_details mkFullIface hsc_env partial_iface Nothing Nothing NoStubs [] +mkRecompUsageInfo :: HscEnv -> TcGblEnv -> IO (Maybe [Usage]) +mkRecompUsageInfo hsc_env tc_result = do + let dflags = hsc_dflags hsc_env + if not (gopt Opt_WriteSelfRecompInfo dflags) + then return Nothing + else do + let used_names = mkUsedNames tc_result + dep_files <- (readIORef (tcg_dependent_files tc_result)) + (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) + let uc = initUsageConfig hsc_env + plugins = hsc_plugins hsc_env + fc = hsc_FC hsc_env + unit_env = hsc_unit_env hsc_env + + -- Do NOT use semantic module here; this_mod in mkUsageInfo + -- is used solely to decide if we should record a dependency + -- or not. When we instantiate a signature, the semantic + -- module is something we want to record dependencies for, + -- but if you pass that in here, we'll decide it's the local + -- module and does not need to be recorded as a dependency. + -- See Note [Identity versus semantic module] + usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env (tcg_mod tc_result) (imp_mods (tcg_imports tc_result)) used_names + dep_files (tcg_merged tc_result) needed_links needed_pkgs + return (Just usages) + mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Bool -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo -> Bool -> SafeHaskellMode - -> [Usage] + -> Maybe ModIfaceSelfRecomp -> Maybe Docs - -> ModSummary -> ModDetails -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode usages - docs mod_summary + hpc_info pkg_trust_req safe_mode self_recomp + docs ModDetails{ md_defaults = defaults, md_insts = insts, md_fam_insts = fam_insts, @@ -350,8 +360,8 @@ mkIface_ hsc_env then Nothing else Just semantic_mod) & set_mi_hsc_src hsc_src + & set_mi_self_recomp self_recomp & set_mi_deps deps - & set_mi_usages usages & set_mi_exports (mkIfaceExports exports) & set_mi_defaults (defaultsToIfaceDefaults defaults) @@ -376,7 +386,6 @@ mkIface_ hsc_env & set_mi_docs docs & set_mi_final_exts () & set_mi_ext_fields emptyExtensibleFields - & set_mi_src_hash (ms_hs_hash mod_summary) & set_mi_hi_bytes PartialIfaceBinHandle where ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -15,6 +15,7 @@ module GHC.Iface.Recomp , CompileReason(..) , recompileRequired , addFingerprints + , mkSelfRecomp ) where @@ -171,6 +172,7 @@ data RecompReason = UnitDepRemoved UnitId | ModulePackageChanged FastString | SourceFileChanged + | NoSelfRecompInfo | ThisUnitIdChanged | ImpurePlugin | PluginsChanged @@ -204,6 +206,7 @@ instance Outputable RecompReason where UnitDepRemoved uid -> ppr uid <+> text "removed" ModulePackageChanged s -> ftext s <+> text "package changed" SourceFileChanged -> text "Source file changed" + NoSelfRecompInfo -> text "Old interface lacks recompilation info" ThisUnitIdChanged -> text "-this-unit-id changed" ImpurePlugin -> text "Impure plugin forced recompilation" PluginsChanged -> text "Plugins changed" @@ -283,7 +286,7 @@ check_old_iface hsc_env mod_summary maybe_iface logger = hsc_logger hsc_env getIface = case maybe_iface of - Just _ -> do + Just {} -> do trace_if logger (text "We already have the old interface for" <+> ppr (ms_mod mod_summary)) return maybe_iface @@ -354,7 +357,9 @@ check_old_iface hsc_env mod_summary maybe_iface -- should check versions because some packages -- might have changed or gone away. Just iface -> - check_dyn_hi iface $ checkVersions hsc_env mod_summary iface + case mi_self_recomp_info iface of + Nothing -> return $ outOfDateItemBecause NoSelfRecompInfo Nothing + Just sr_info -> check_dyn_hi iface $ checkVersions hsc_env mod_summary iface sr_info -- | Check if a module is still the same 'version'. -- @@ -370,8 +375,9 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface + -> ModIfaceSelfRecomp -> IfG (MaybeValidated ModIface) -checkVersions hsc_env mod_summary iface +checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger (text "Considering whether compilation is required for" <+> ppr (mi_module iface) <> colon) @@ -380,23 +386,22 @@ checkVersions hsc_env mod_summary iface -- but we ALSO must make sure the instantiation matches up. See -- test case bkpcabal04! ; hsc_env <- getTopEnv - ; if mi_src_hash iface /= ms_hs_hash mod_summary + ; if mi_sr_src_hash self_recomp /= ms_hs_hash mod_summary then return $ outOfDateItemBecause SourceFileChanged Nothing else do { ; if not (isHomeModule home_unit (mi_module iface)) then return $ outOfDateItemBecause ThisUnitIdChanged Nothing else do { - ; recomp <- liftIO $ checkFlagHash hsc_env iface - `recompThen` checkOptimHash hsc_env iface - `recompThen` checkHpcHash hsc_env iface - `recompThen` checkMergedSignatures hsc_env mod_summary iface + ; recomp <- liftIO $ checkFlagHash hsc_env (mi_module iface) self_recomp + `recompThen` checkOptimHash hsc_env self_recomp + `recompThen` checkHpcHash hsc_env self_recomp + `recompThen` checkMergedSignatures hsc_env mod_summary self_recomp `recompThen` checkHsig logger home_unit mod_summary iface `recompThen` pure (checkHie dflags mod_summary) ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { ; recomp <- checkDependencies hsc_env mod_summary iface ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { - ; recomp <- checkPlugins (hsc_plugins hsc_env) iface + ; recomp <- checkPlugins (hsc_plugins hsc_env) self_recomp ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { - -- Source code unchanged and no errors yet... carry on -- -- First put the dependent-module info, read from the old @@ -411,7 +416,7 @@ checkVersions hsc_env mod_summary iface ; updateEps_ $ \eps -> eps { eps_is_boot = mkModDeps $ dep_boot_mods (mi_deps iface) } } ; recomp <- checkList [checkModUsage (hsc_FC hsc_env) u - | u <- mi_usages iface] + | u <- mi_sr_usages self_recomp] ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { ; return $ UpToDateItem iface }}}}}}} @@ -423,11 +428,11 @@ checkVersions hsc_env mod_summary iface -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIface -> IfG RecompileRequired -checkPlugins plugins iface = liftIO $ do +checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp - let old_fingerprint = mi_plugin_hash (mi_final_exts iface) + let old_fingerprint = mi_sr_plugin_hash self_recomp return $ pluginRecompileToRecompileRequired old_fingerprint new_fingerprint recomp recompPlugins :: Plugins -> IO PluginRecompile @@ -516,11 +521,11 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> ModIface -> IO RecompileRequired -checkFlagHash hsc_env iface = do +checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_flag_hash (mi_final_exts iface) - new_hash <- fingerprintDynFlags hsc_env (mi_module iface) putNameLiterally + let old_hash = mi_sr_flag_hash self_recomp + new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally case old_hash == new_hash of True -> up_to_date logger (text "Module flags unchanged") False -> out_of_date_hash logger FlagsChanged @@ -528,10 +533,10 @@ checkFlagHash hsc_env iface = do old_hash new_hash -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIface -> IO RecompileRequired +checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env - let old_hash = mi_opt_hash (mi_final_exts iface) + let old_hash = mi_sr_opt_hash iface new_hash <- fingerprintOptFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -544,10 +549,10 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIface -> IO RecompileRequired -checkHpcHash hsc_env iface = do +checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_hpc_hash (mi_final_exts iface) + let old_hash = mi_sr_hpc_hash self_recomp new_hash <- fingerprintHpcFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -561,11 +566,11 @@ checkHpcHash hsc_env iface = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIface -> IO RecompileRequired -checkMergedSignatures hsc_env mod_summary iface = do +checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env - let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_usages iface ] + let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_sr_usages self_recomp ] new_merged = case lookupUniqMap (requirementContext unit_state) (ms_mod_name mod_summary) of Nothing -> [] @@ -939,6 +944,28 @@ we use is: -} +-- | Compute the information needed for self-recompilation checking. This +-- information can be computed before the backend phase. +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp hsc_env this_mod src_hash usages = do + let dflags = hsc_dflags hsc_env + + flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + + opt_hash <- fingerprintOptFlags dflags putNameLiterally + + hpc_hash <- fingerprintHpcFlags dflags putNameLiterally + + plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + + return (ModIfaceSelfRecomp + { mi_sr_flag_hash = flag_hash + , mi_sr_hpc_hash = hpc_hash + , mi_sr_opt_hash = opt_hash + , mi_sr_plugin_hash = plugin_hash + , mi_sr_src_hash = src_hash + , mi_sr_usages = usages }) + -- | Add fingerprints for top-level declarations to a 'ModIface'. -- -- See Note [Fingerprinting IfaceDecls] @@ -1213,18 +1240,6 @@ addFingerprints hsc_env iface0 sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - -- the flag hash depends on: - -- - (some of) dflags - -- it returns two hashes, one that shouldn't change - -- the abi hash and one that should - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally - - opt_hash <- fingerprintOptFlags dflags putNameLiterally - - hpc_hash <- fingerprintHpcFlags dflags putNameLiterally - - plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) - -- the ABI hash depends on: -- - decls -- - export list @@ -1238,6 +1253,7 @@ addFingerprints hsc_env iface0 mi_warns iface0, mi_foreign iface0) + -- The interface hash depends on: -- - the ABI hash, plus -- - the source file hash, @@ -1246,21 +1262,17 @@ addFingerprints hsc_env iface0 -- - deps (home and external packages, dependent files) -- - hpc iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - mi_src_hash iface0, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_usages iface0, - sorted_deps, - mi_hpc iface0) + (mod_hash, + mi_src_hash iface0, + ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache + mi_usages iface0, + sorted_deps, + mi_hpc iface0) let final_iface_exts = ModIfaceBackend - { mi_iface_hash = iface_hash - , mi_mod_hash = mod_hash - , mi_flag_hash = flag_hash - , mi_opt_hash = opt_hash - , mi_hpc_hash = hpc_hash - , mi_plugin_hash = plugin_hash + { mi_mod_hash = mod_hash + , mi_iface_hash = iface_hash , mi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts @@ -1281,12 +1293,12 @@ addFingerprints hsc_env iface0 where this_mod = mi_module iface0 semantic_mod = mi_semantic_module iface0 - dflags = hsc_dflags hsc_env (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) ann_fn = mkIfaceAnnCache (mi_anns iface0) + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the -- current module). ===================================== compiler/GHC/Unit/Module/ModGuts.hs ===================================== @@ -53,7 +53,7 @@ data ModGuts mg_exports :: ![AvailInfo], -- ^ What it exports mg_deps :: !Dependencies, -- ^ What it depends on, directly or -- otherwise - mg_usages :: ![Usage], -- ^ What was used? Used for interfaces. + mg_usages :: !(Maybe [Usage]), -- ^ What was used? Used for interfaces. mg_used_th :: !Bool, -- ^ Did we run a TH splice? mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -15,7 +15,6 @@ module GHC.Unit.Module.ModIface , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -36,19 +35,16 @@ module GHC.Unit.Module.ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info ) , pattern ModIface - , restoreFromOldModIface - , addSourceFingerprint , set_mi_module , set_mi_sig_of , set_mi_hsc_src - , set_mi_src_hash + , set_mi_self_recomp , set_mi_hi_bytes , set_mi_deps - , set_mi_usages , set_mi_exports , set_mi_used_th , set_mi_fixities @@ -73,6 +69,8 @@ module GHC.Unit.Module.ModIface , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) + , ModIfaceSelfRecomp (..) + , withSelfRecomp , IfaceDeclExts , IfaceBackendExts , IfaceExport @@ -85,6 +83,12 @@ module GHC.Unit.Module.ModIface , mi_semantic_module , mi_free_holes , mi_mnwib + , mi_flag_hash + , mi_opt_hash + , mi_hpc_hash + , mi_plugin_hash + , mi_src_hash + , mi_usages , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,6 +110,8 @@ import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.ModIface.SelfRecomp + import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env @@ -150,19 +156,10 @@ type ModIface = ModIface_ 'ModIfaceFinal -- * Or computed just before writing the iface to disk. (Hashes) -- In order to fully instantiate it. data ModIfaceBackend = ModIfaceBackend - { mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_mod_hash :: !Fingerprint + { mi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_flag_hash :: !Fingerprint - -- ^ Hash of the important flags used when compiling the module, excluding - -- optimisation flags - , mi_opt_hash :: !Fingerprint - -- ^ Hash of optimisation flags - , mi_hpc_hash :: !Fingerprint - -- ^ Hash of hpc flags - , mi_plugin_hash :: !Fingerprint - -- ^ Hash of plugins + , mi_iface_hash :: !Fingerprint + -- ^ Hash of the whole interface , mi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans , mi_finsts :: !WhetherHasFamInst @@ -218,6 +215,15 @@ data IfaceBinHandle (phase :: ModIfacePhase) where -- (e.g., set to 'Nothing'). FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal + +withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp iface nk jk = + case mi_self_recomp_info iface of + Nothing -> nk + Just x -> jk x + + + -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, -- and can be written out to an interface file. The 'ModDetails is after @@ -245,16 +251,6 @@ data ModIface_ (phase :: ModIfacePhase) -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages_ :: [Usage], - -- ^ Usages; kept sorted so that it's easy to decide - -- whether to write a new iface file (changing usages - -- doesn't affect the hash of this module) - -- NOT STRICT! we read this field lazily from the interface file - -- It is *only* consulted by the recompilation checker - -- - -- The elements must be *deterministically* sorted to guarantee - -- deterministic interface files - mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier @@ -352,13 +348,15 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash_ :: !Fingerprint, - -- ^ Hash of the .hs source, used for recompilation checking. - mi_hi_bytes_ :: !(IfaceBinHandle phase) + mi_hi_bytes_ :: !(IfaceBinHandle phase), -- ^ A serialised in-memory buffer of this 'ModIface'. -- If this handle is given, we can avoid serialising the 'ModIface' -- when writing this 'ModIface' to disk, and write this buffer to disk instead. -- See Note [Sharing of ModIface]. + + mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] } -- Enough information to reconstruct the top level environment for a module @@ -404,6 +402,24 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} +mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ + +mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ + +mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ + +mi_src_hash :: ModIface_ phase -> Maybe Fingerprint +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ + +mi_usages :: ModIface_ phase -> Maybe [Usage] +mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ + +mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ + -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. mi_boot :: ModIface -> IsBootInterface @@ -461,9 +477,6 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance - -- because we are going to write it - -- out separately in the actual file mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then @@ -471,7 +484,6 @@ instance Binary ModIface where -- the byte array. -- See Note [Private fields in ModIface] mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_fixities_ = fixities, @@ -493,13 +505,10 @@ instance Binary ModIface where mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file + mi_self_recomp_info_ = self_recomp, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -508,16 +517,12 @@ instance Binary ModIface where put_ bh mod put_ bh sig_of put_ bh hsc_src - put_ bh iface_hash + put_ bh self_recomp put_ bh mod_hash - put_ bh flag_hash - put_ bh opt_hash - put_ bh hpc_hash - put_ bh plugin_hash + put_ bh iface_hash put_ bh orphan put_ bh hasFamInsts lazyPut bh deps - lazyPut bh usages put_ bh exports put_ bh exp_hash put_ bh used_th @@ -543,16 +548,12 @@ instance Binary ModIface where mod <- get bh sig_of <- get bh hsc_src <- get bh - iface_hash <- get bh + self_recomp_info <- get bh mod_hash <- get bh - flag_hash <- get bh - opt_hash <- get bh - hpc_hash <- get bh - plugin_hash <- get bh + iface_hash <- get bh orphan <- get bh hasFamInsts <- get bh deps <- lazyGet bh - usages <- {-# SCC "bin_usages" #-} lazyGet bh exports <- {-# SCC "bin_exports" #-} get bh exp_hash <- get bh used_th <- get bh @@ -577,15 +578,12 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = fingerprint0, -- placeholder because this is dealt - -- with specially when the file is read mi_hi_bytes_ = -- We can't populate this field here, as we are -- missing the 'mi_ext_fields_' field, which is -- handled in 'getIfaceWithExtFields'. FullIfaceBinHandle Strict.Nothing, mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_anns_ = anns, @@ -607,13 +605,10 @@ instance Binary ModIface where mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read + mi_self_recomp_info_ = self_recomp_info, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -632,10 +627,8 @@ emptyPartialModIface mod { mi_module_ = mod, mi_sig_of_ = Nothing, mi_hsc_src_ = HsSrcFile, - mi_src_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_usages_ = [], mi_exports_ = [], mi_used_th_ = False, mi_fixities_ = [], @@ -655,21 +648,19 @@ emptyPartialModIface mod mi_complete_matches_ = [], mi_docs_ = Nothing, mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields + mi_ext_fields_ = emptyExtensibleFields, + mi_self_recomp_info_ = Nothing } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) { mi_decls_ = [] + , mi_self_recomp_info_ = Nothing , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing , mi_final_exts_ = ModIfaceBackend - { mi_iface_hash = fingerprint0, - mi_mod_hash = fingerprint0, - mi_flag_hash = fingerprint0, - mi_opt_hash = fingerprint0, - mi_hpc_hash = fingerprint0, - mi_plugin_hash = fingerprint0, + { mi_mod_hash = fingerprint0, + mi_iface_hash = fingerprint0, mi_orphan = False, mi_finsts = False, mi_exp_hash = fingerprint0, @@ -699,18 +690,17 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_, mi_src_hash_ }) + , mi_ext_fields_ }) = rnf mi_module_ `seq` rnf mi_sig_of_ `seq` mi_hsc_src_ `seq` mi_hi_bytes_ `seq` mi_deps_ - `seq` mi_usages_ `seq` mi_exports_ `seq` rnf mi_used_th_ `seq` mi_fixities_ @@ -731,20 +721,14 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_docs_ `seq` mi_final_exts_ `seq` mi_ext_fields_ - `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_iface_hash, mi_mod_hash, mi_flag_hash, mi_opt_hash - , mi_hpc_hash, mi_plugin_hash, mi_orphan, mi_finsts, mi_exp_hash + rnf (ModIfaceBackend{ mi_mod_hash + , mi_orphan, mi_finsts, mi_exp_hash , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn , mi_hash_fn}) - = rnf mi_iface_hash - `seq` rnf mi_mod_hash - `seq` rnf mi_flag_hash - `seq` rnf mi_opt_hash - `seq` rnf mi_hpc_hash - `seq` rnf mi_plugin_hash + = rnf mi_mod_hash `seq` rnf mi_orphan `seq` rnf mi_finsts `seq` rnf mi_exp_hash @@ -810,27 +794,6 @@ completePartialModIface partial decls extra_decls final_exts = partial , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing } --- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array --- buffer 'mi_hi_bytes'. --- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. --- --- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. -addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase -addSourceFingerprint val iface = iface { mi_src_hash_ = val } - --- | Copy fields that aren't serialised to disk to the new 'ModIface_'. --- This includes especially hashes that are usually stored in the interface --- file header and 'mi_top_env'. --- --- We need this function after calling 'shareIface', to make sure the --- 'ModIface_' doesn't lose any information. This function does not discard --- the in-memory byte array buffer 'mi_hi_bytes'. -restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase -restoreFromOldModIface old new = new - { mi_hsc_src_ = mi_hsc_src_ old - , mi_src_hash_ = mi_src_hash_ old - } - set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } @@ -840,8 +803,8 @@ set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } -set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase -set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } +set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -849,9 +812,6 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } -set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase -set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } - set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } @@ -976,7 +936,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} -{-# INLINE mi_usages #-} {-# INLINE mi_exports #-} {-# INLINE mi_used_th #-} {-# INLINE mi_fixities #-} @@ -996,25 +955,23 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_docs #-} {-# INLINE mi_final_exts #-} {-# INLINE mi_ext_fields #-} -{-# INLINE mi_src_hash #-} {-# INLINE mi_hi_bytes #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + Module -> Maybe Module -> HscSource -> Dependencies -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface { mi_module , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -1035,14 +992,13 @@ pattern ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info } <- PrivateModIface { mi_module_ = mi_module , mi_sig_of_ = mi_sig_of , mi_hsc_src_ = mi_hsc_src , mi_deps_ = mi_deps - , mi_usages_ = mi_usages , mi_exports_ = mi_exports , mi_used_th_ = mi_used_th , mi_fixities_ = mi_fixities @@ -1063,6 +1019,6 @@ pattern ModIface , mi_docs_ = mi_docs , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields - , mi_src_hash_ = mi_src_hash , mi_hi_bytes_ = mi_hi_bytes + , mi_self_recomp_info_ = mi_self_recomp_info } ===================================== compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs ===================================== @@ -0,0 +1,111 @@ +module GHC.Unit.Module.ModIface.SelfRecomp where + +import GHC.Prelude +import GHC.Fingerprint +import GHC.Utils.Outputable +import GHC.Unit.Module.Deps + +import GHC.Utils.Binary + +import Control.DeepSeq + +{- +Note [Self recompilation information in interface files] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The flag -fwrite-self-recomp-info controls whether +interface files contain the information necessary to answer the +question: + + Is the interface file up-to-date, relative to: + * the source file it corresponds to, + * the flags passed to the GHC invocation to compile it, + * its dependencies (e.g. imported items, watched files added by addDependentFile, ...) + +If there is no self-recompilation information stored, then we always re-generate +the interface file from scratch. + +Why? Most packages are only built once either by a distribution or cabal +and then placed into an immutable store, after which we will never ask +this question. Therefore we can derive two benefits from omitting this +information. + +* Primary motivation: It vastly reduces the surface area for creating + non-deterministic interface files. See issue #10424 which motivated a + proper fix to that issue. Distributions have long contained versions + of GHC which just have broken self-recompilation checking (in order to + get deterministic interface files). + +* Secondary motivation: This reduces the size of interface files + slightly.. the `mi_usages` field can be quite big but probably this + isn't such a great benefit. + +* Third motivation: Conceptually clarity about which parts of an + interface file are used in order to **communicate** with subsequent + packages about the **interface** for a module. And which parts are + used to self-communicate during recompilation checking. + +The main tracking issue is #22188 but fixes issues such as #10424 in a +proper way. + +-} + +-- | The information for a module which is only used when deciding whether to recompile +-- itself. +-- +-- See Note [Self recompilation information in interface files] +data ModIfaceSelfRecomp = + ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint + -- ^ Hash of the .hs source, used for recompilation checking. + , mi_sr_usages :: [Usage] + -- ^ Usages; kept sorted so that it's easy to decide + -- whether to write a new iface file (changing usages + -- doesn't affect the hash of this module) + -- NOT STRICT! we read this field lazily from the interface file + -- It is *only* consulted by the recompilation checker + + , mi_sr_flag_hash :: !Fingerprint + -- ^ Hash of the important flags used when compiling the module, excluding + -- optimisation flags + , mi_sr_opt_hash :: !Fingerprint + -- ^ Hash of optimisation flags + , mi_sr_hpc_hash :: !Fingerprint + -- ^ Hash of hpc flags + , mi_sr_plugin_hash :: !Fingerprint + -- ^ Hash of plugins + } + + +instance Binary ModIfaceSelfRecomp where + put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do + put_ bh mi_sr_src_hash + lazyPut bh mi_sr_usages + put_ bh mi_sr_flag_hash + put_ bh mi_sr_opt_hash + put_ bh mi_sr_hpc_hash + put_ bh mi_sr_plugin_hash + + get bh = do + src_hash <- get bh + usages <- lazyGet bh + flag_hash <- get bh + opt_hash <- get bh + hpc_hash <- get bh + plugin_hash <- get bh + return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + +instance Outputable ModIfaceSelfRecomp where + ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) + = vcat [text "Self-Recomp" + , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash + , text "usages:" <+> ppr (length mi_sr_usages) + , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "opt hash:" <+> ppr mi_sr_opt_hash + , text "hpc hash:" <+> ppr mi_sr_hpc_hash + , text "plugin hash:" <+> ppr mi_sr_plugin_hash + ])] + +instance NFData ModIfaceSelfRecomp where + -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so + -- I left it as a shallow force. + rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file ===================================== compiler/ghc.cabal.in ===================================== @@ -955,6 +955,7 @@ Library GHC.Unit.Module.ModDetails GHC.Unit.Module.ModGuts GHC.Unit.Module.ModIface + GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.WholeCoreBindings GHC.Unit.Module.ModSummary GHC.Unit.Module.Status ===================================== docs/users_guide/phases.rst ===================================== @@ -702,6 +702,24 @@ Options affecting code generation depend on the optimisation level. Any definitions which are already included in an interface file (via an unfolding for an exported identifier) are reused. +.. ghc-flag:: -fwrite-self-recomp-info + :shortdesc: Write information for self-recompilation checking in an interface file + :type: dynamic + :category: codegen + + :default: on + + Include information in an interface file which can be used in future to determine + whether we need to recompile a module or can reuse the existing interface. + + This is intended to be turned off in situations where you know you will never try + to recompile a module, such as when compiling a package for distribution. + The advantage is that by omitting unecessary information to do with dependencies + there is less chance of build paths leaking into the interface file and affecting + determinism. + + + .. ghc-flag:: -fobject-code :shortdesc: Generate object code ===================================== hadrian/src/Flavour.hs ===================================== @@ -16,6 +16,7 @@ module Flavour , disableProfiledLibs , enableLinting , enableHaddock + , disableSelfRecompInfo , enableHiCore , useNativeBignum , enableTextWithSIMDUTF @@ -67,6 +68,7 @@ flavourTransformers = M.fromList , "debug_stage1_ghc" =: debugGhc Stage1 , "lint" =: enableLinting , "haddock" =: enableHaddock + , "no_self_recomp" =: disableSelfRecompInfo , "hi_core" =: enableHiCore , "late_ccs" =: enableLateCCS , "boot_nonmoving_gc" =: enableBootNonmovingGc @@ -208,6 +210,17 @@ enableHaddock = [ arg "-haddock" ] +-- | Disable self recompilation information in interface files +disableSelfRecompInfo :: Flavour -> Flavour +disableSelfRecompInfo = + addArgs $ stage1 ? mconcat + [ builder (Ghc CompileHs) ? selfRecomp + ] + where + selfRecomp = mconcat + [ arg "-fno-write-self-recomp-info" + ] + -- | Build stage2 dependencies with options to emit Core into -- interface files which is sufficient to restart code generation. enableHiCore :: Flavour -> Flavour ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,8 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableHaddock performanceFlavour { name = "release" } +releaseFlavour = + -- 1. These interface files will be distributed and the source files never recompiled. + disableSelfRecompInfo + -- 2. Include documentation in the interface for tools such as haddock and HLS to use + $ enableHaddock performanceFlavour { name = "release" } ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -201,6 +201,7 @@ GHC.Unit.Module.Env GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.Warnings GHC.Unit.Module.WholeCoreBindings GHC.Unit.Parser ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -227,6 +227,7 @@ GHC.Unit.Module.Graph GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.ModNodeKey GHC.Unit.Module.ModSummary GHC.Unit.Module.Warnings ===================================== testsuite/tests/driver/self-recomp/Makefile ===================================== @@ -0,0 +1,38 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +TEST_HC_OPTS_NO_RTSOPTS = $(filter-out -rtsopts,$(TEST_HC_OPTS)) + +# ----------------------------------------------------------------------------- +# One-shot compilations, non-hierarchical modules + +# Check that modifying flags doesn't affect interface +SelfRecomp01: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface1 + rm SelfRecomp01.hi + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-self-recomp-info -Iidir -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface2 + diff iface1 iface2 + +# Check that the result of addDependentFile doesn't end up in interface +SelfRecomp02: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp02.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp02.hi > iface + [ -z $(grep iface SelfRecomp02.hs) ] + +# Check that modifying source doesn't affect interface +SelfRecomp03: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface1 + rm SelfRecomp03.hi + echo "" >> SelfRecomp03.hs + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-self-recomp-info -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface2 + diff iface1 iface2 + +# Check that if you don't have recompilation info then you always recompile. +SelfRecomp04: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-self-recomp-info -fhide-source-paths + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-self-recomp-info -fhide-source-paths ===================================== testsuite/tests/driver/self-recomp/SelfRecomp01.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp01 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp02.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +module SelfRecomp02 where + +import Language.Haskell.TH.Syntax + +main = $(addDependentFile "SelfRecomp02.hs" >> [| print () |]) ===================================== testsuite/tests/driver/self-recomp/SelfRecomp03.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp03 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.hs ===================================== @@ -0,0 +1 @@ +module SelfRecomp04 where ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.stdout ===================================== @@ -0,0 +1,2 @@ +[1 of 1] Compiling SelfRecomp04 +[1 of 1] Compiling SelfRecomp04 [Old interface lacks recompilation info] ===================================== testsuite/tests/driver/self-recomp/all.T ===================================== @@ -0,0 +1,4 @@ +test('SelfRecomp01', normal, makefile_test, ['SelfRecomp01']) +test('SelfRecomp02', normal, makefile_test, ['SelfRecomp02']) +test('SelfRecomp03', [copy_files], makefile_test, ['SelfRecomp03']) +test('SelfRecomp04', normal, makefile_test, ['SelfRecomp04']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/29c3d23ebbd9ff562d94e9a82e6aa5203b01681c...9c0a9d5a8e8891009293ccf594233d1cad0b3434 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/29c3d23ebbd9ff562d94e9a82e6aa5203b01681c...9c0a9d5a8e8891009293ccf594233d1cad0b3434 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/0b20c6e9/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:11:52 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 09:11:52 -0500 Subject: [Git][ghc/ghc][master] 6 commits: rts: fix top handler closure type signatures Message-ID: <67c70a28df37e_a5f4875d8d497229@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - 13 changed files: - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/Tc/Gen/Foreign.hs - docs/users_guide/wasm.rst - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/include/RtsAPI.h - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs Changes: ===================================== compiler/GHC/HsToCore/Foreign/C.hs ===================================== @@ -515,8 +515,7 @@ mkFExportCBits dflags c_nm maybe_target arg_htys res_hty is_IO_res_ty cc , text "rts_inCall" <> parens ( char '&' <> cap <> text "rts_apply" <> parens ( - cap <> - text "(HaskellObj)" + cap <> (if is_IO_res_ty then text "runIO_closure" else text "runNonIO_closure") ===================================== compiler/GHC/HsToCore/Foreign/Wasm.hs ===================================== @@ -11,6 +11,7 @@ import Data.List ( intercalate, stripPrefix, ) +import Data.List qualified import Data.Maybe import GHC.Builtin.Names import GHC.Builtin.Types @@ -46,6 +47,9 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import Language.Haskell.Syntax.Basic +data Synchronicity = Sync | Async + deriving (Eq) + dsWasmJSImport :: Id -> Coercion -> @@ -53,10 +57,15 @@ dsWasmJSImport :: Safety -> DsM ([Binding], CHeader, CStub, [Id]) dsWasmJSImport id co (CFunction (StaticTarget _ js_src mUnitId _)) safety - | js_src == "wrapper" = dsWasmJSDynamicExport id co mUnitId + | js_src == "wrapper" = dsWasmJSDynamicExport Async id co mUnitId + | js_src == "wrapper sync" = dsWasmJSDynamicExport Sync id co mUnitId | otherwise = do - (bs, h, c) <- dsWasmJSStaticImport id co (unpackFS js_src) mUnitId safety + (bs, h, c) <- dsWasmJSStaticImport id co (unpackFS js_src) mUnitId sync pure (bs, h, c, []) + where + sync = case safety of + PlayRisky -> Sync + _ -> Async dsWasmJSImport _ _ _ _ = panic "dsWasmJSImport: unreachable" {- @@ -77,17 +86,24 @@ We desugar it to three bindings under the hood: mk_wrapper_worker :: StablePtr HsFuncType -> HsFuncType mk_wrapper_worker sp = unsafeDupablePerformIO (deRefStablePtr sp) -No need to bother with eta-expansion here. Also, the worker function -is marked as a JSFFI static export. +The worker function is marked as a JSFFI static export. It turns a +dynamic export to a static one by prepending a StablePtr to the +argument list. + +We don't actually generate a Core binding for the worker function +though; the JSFFI static export C stub generation logic would just +generate a function that doesn't need to refer to the worker Id's +closure. This is not just for convenience, it's actually required for +correctness, see #25473. 2. The adjustor function foreign import javascript unsafe "(...args) => __exports.mk_wrapper_worker($1, ...args)" mk_wrapper_adjustor :: StablePtr HsFuncType -> IO JSVal -It generates a JavaScript callback that captures the stable pointer. -When the callback is invoked later, it calls our worker function and -passes the stable pointer as well as the rest of the arguments. +Now that mk_wrapper_worker is exported in __exports, we need to make a +JavaScript callback that invokes mk_wrapper_worker with the right +StablePtr as well as the rest of the arguments. 3. The wrapper function @@ -102,43 +118,47 @@ a StablePtr# field which is NULL by default, but for JSFFI dynamic exports, it's set to the Haskell function's stable pointer. This way, when we call freeJSVal, the Haskell function can be freed as well. +By default, JSFFI exports are async JavaScript functions. One can use +"wrapper sync" instead of "wrapper" to indicate the Haskell function +is meant to be exported as a sync JavaScript function. All the +comments above still hold, with only only difference: +mk_wrapper_worker is exported as a sync function. See +Note [Desugaring JSFFI static export] for further details. + -} dsWasmJSDynamicExport :: - Id -> Coercion -> Maybe Unit -> DsM ([Binding], CHeader, CStub, [Id]) -dsWasmJSDynamicExport fn_id co mUnitId = do + Synchronicity -> + Id -> + Coercion -> + Maybe Unit -> + DsM ([Binding], CHeader, CStub, [Id]) +dsWasmJSDynamicExport sync fn_id co mUnitId = do sp_tycon <- dsLookupTyCon stablePtrTyConName let ty = coercionLKind co (tv_bndrs, fun_ty) = tcSplitForAllTyVarBinders ty ([Scaled ManyTy arg_ty], io_jsval_ty) = tcSplitFunTys fun_ty sp_ty = mkTyConApp sp_tycon [arg_ty] - (real_arg_tys, _) = tcSplitFunTys arg_ty sp_id <- newSysLocalMDs sp_ty - work_uniq <- newUnique - work_export_name <- uniqueCFunName - deRefStablePtr_id <- lookupGhcInternalVarId "GHC.Internal.Stable" "deRefStablePtr" + work_export_name <- unpackFS <$> uniqueCFunName + deRefStablePtr_id <- + lookupGhcInternalVarId + "GHC.Internal.Stable" + "deRefStablePtr" unsafeDupablePerformIO_id <- lookupGhcInternalVarId "GHC.Internal.IO.Unsafe" "unsafeDupablePerformIO" - let work_id = - mkExportedVanillaId - ( mkExternalName - work_uniq - (nameModule $ getName fn_id) - (mkVarOcc $ "jsffi_" ++ occNameString (getOccName fn_id) ++ "_work") - generatedSrcSpan - ) - work_ty - work_rhs = + let work_rhs = mkCoreLams ([tv | Bndr tv _ <- tv_bndrs] ++ [sp_id]) $ mkApps (Var unsafeDupablePerformIO_id) [Type arg_ty, mkApps (Var deRefStablePtr_id) [Type arg_ty, Var sp_id]] work_ty = exprType work_rhs (work_h, work_c, _, work_ids, work_bs) <- - dsWasmJSExport - work_id + dsWasmJSExport' + sync + Nothing (mkRepReflCo work_ty) work_export_name adjustor_uniq <- newUnique @@ -157,21 +177,18 @@ dsWasmJSDynamicExport fn_id co mUnitId = do adjustor_ty adjustor_ty = mkForAllTys tv_bndrs $ mkVisFunTysMany [sp_ty] io_jsval_ty adjustor_js_src = - "(" - ++ intercalate "," ["a" ++ show i | i <- [1 .. length real_arg_tys]] - ++ ") => __exports." - ++ unpackFS work_export_name - ++ "($1" - ++ mconcat [",a" ++ show i | i <- [1 .. length real_arg_tys]] - ++ ")" + "(...args) => __exports." ++ work_export_name ++ "($1, ...args)" (adjustor_bs, adjustor_h, adjustor_c) <- dsWasmJSStaticImport adjustor_id (mkRepReflCo adjustor_ty) adjustor_js_src mUnitId - PlayRisky - mkJSCallback_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "mkJSCallback" + Sync + mkJSCallback_id <- + lookupGhcInternalVarId + "GHC.Internal.Wasm.Prim.Exports" + "mkJSCallback" let wrap_rhs = mkCoreLams [tv | Bndr tv _ <- tv_bndrs] $ mkApps @@ -182,7 +199,7 @@ dsWasmJSDynamicExport fn_id co mUnitId = do [Type $ mkTyVarTy tv | Bndr tv _ <- tv_bndrs] ] pure - ( [(fn_id, Cast wrap_rhs co), (work_id, work_rhs)] ++ work_bs ++ adjustor_bs, + ( [(fn_id, Cast wrap_rhs co)] ++ work_bs ++ adjustor_bs, work_h `mappend` adjustor_h, work_c `mappend` adjustor_c, work_ids @@ -194,7 +211,7 @@ Note [Desugaring JSFFI import] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The simplest case is JSFFI sync import, those marked as unsafe. It is -implemented on top of C FFI unsafe import. +implemented on top of C FFI safe import. Unlike C FFI which generates a worker/wrapper pair that unboxes the arguments and boxes the result in Haskell, we only desugar to a single @@ -202,10 +219,11 @@ Haskell binding that case-binds the arguments to ensure they're evaluated, then passes the boxed arguments directly to C and receive the boxed result from C as well. -This is of course less efficient than how C FFI does it, and unboxed -FFI types aren't supported, but it's the easiest way to implement it, +This is slightly less efficient than how C FFI does it, and unboxed +FFI types aren't supported, but it's the simplest way to implement it, especially since leaving all the boxing/unboxing business to C unifies -the implementation of JSFFI imports and exports. +the implementation of JSFFI imports and exports +(rts_mkJSVal/rts_getJSVal). Now, each sync import calls a generated C function with a unique symbol. The C function uses rts_get* to unbox the arguments, call into @@ -240,6 +258,14 @@ module. Note that above is assembly source file, but we're only generating a C stub, so we need to smuggle the assembly code into C via __asm__. +The C FFI import that calls the generated C function is always marked +as safe. There is some extra overhead, but this allows re-entrance by +Haskell -> JavaScript -> Haskell function calls with each call being a +synchronous one. It's possible to steal the "interruptible" keyword to +indicate async imports, "safe" for sync imports and "unsafe" for sync +imports sans the safe C FFI overhead, but it's simply not worth the +extra complexity. + JSFFI async import is implemented on top of JSFFI sync import. We still desugar it to a single Haskell binding that calls C, with some subtle differences: @@ -250,12 +276,6 @@ subtle differences: "($1, $2)". As you can see, it is the arrow function binder, and the post-linker will respect the async binder and allow await in the function body. -- The C import is also marked as safe. This is required since the - JavaScript code may re-enter Haskell. If re-entrance only happens in - future event loop tasks, it's fine to mark the C import as unsafe - since the current Haskell execution context has already been freed - at that point, but there's no such guarantee, so better safe than - sorry here. Now we have the Promise JSVal, we apply stg_blockPromise to it to get a thunk with the desired return type. When the thunk is forced, it @@ -270,9 +290,9 @@ dsWasmJSStaticImport :: Coercion -> String -> Maybe Unit -> - Safety -> + Synchronicity -> DsM ([Binding], CHeader, CStub) -dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do +dsWasmJSStaticImport fn_id co js_src' mUnitId sync = do cfun_name <- uniqueCFunName let ty = coercionLKind co (tvs, fun_ty) = tcSplitForAllInvisTyVars ty @@ -289,36 +309,31 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do ++ ")" | otherwise = js_src' - case safety of - PlayRisky -> do - rhs <- - importBindingRHS - mUnitId - PlayRisky - cfun_name - tvs - arg_tys - orig_res_ty - id + case sync of + Sync -> do + rhs <- importBindingRHS mUnitId cfun_name tvs arg_tys orig_res_ty id pure ( [(fn_id, Cast rhs co)], CHeader commonCDecls, - importCStub - PlayRisky - cfun_name - (map scaledThing arg_tys) - res_ty - js_src + importCStub Sync cfun_name (map scaledThing arg_tys) res_ty js_src ) - _ -> do + Async -> do + err_msg <- mkStringExpr $ js_src io_tycon <- dsLookupTyCon ioTyConName - jsval_ty <- mkTyConTy <$> lookupGhcInternalTyCon "GHC.Internal.Wasm.Prim.Types" "JSVal" + jsval_ty <- + mkTyConTy + <$> lookupGhcInternalTyCon "GHC.Internal.Wasm.Prim.Types" "JSVal" bindIO_id <- dsLookupGlobalId bindIOName returnIO_id <- dsLookupGlobalId returnIOName promise_id <- newSysLocalMDs jsval_ty - blockPromise_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" "stg_blockPromise" + blockPromise_id <- + lookupGhcInternalVarId + "GHC.Internal.Wasm.Prim.Imports" + "stg_blockPromise" msgPromise_id <- - lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" $ "stg_messagePromise" ++ ffiType res_ty + lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Imports" + $ "stg_messagePromise" + ++ ffiType res_ty unsafeDupablePerformIO_id <- lookupGhcInternalVarId "GHC.Internal.IO.Unsafe" @@ -326,7 +341,6 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do rhs <- importBindingRHS mUnitId - PlaySafe cfun_name tvs arg_tys @@ -350,19 +364,14 @@ dsWasmJSStaticImport fn_id co js_src' mUnitId safety = do [ Type res_ty, mkApps (Var blockPromise_id) - [Type res_ty, Var promise_id, Var msgPromise_id] + [Type res_ty, err_msg, Var promise_id, Var msgPromise_id] ] ] ) pure ( [(fn_id, Cast rhs co)], CHeader commonCDecls, - importCStub - PlaySafe - cfun_name - (map scaledThing arg_tys) - jsval_ty - js_src + importCStub Async cfun_name (map scaledThing arg_tys) jsval_ty js_src ) uniqueCFunName :: DsM FastString @@ -372,92 +381,91 @@ uniqueCFunName = do importBindingRHS :: Maybe Unit -> - Safety -> FastString -> [TyVar] -> [Scaled Type] -> Type -> (CoreExpr -> CoreExpr) -> DsM CoreExpr -importBindingRHS mUnitId safety cfun_name tvs arg_tys orig_res_ty res_trans = - do - ccall_uniq <- newUnique - args_unevaled <- newSysLocalsDs arg_tys - args_evaled <- newSysLocalsDs arg_tys - -- ccall_action_ty: type of the_call, State# RealWorld -> (# State# RealWorld, a #) - -- res_wrapper: turn the_call to (IO a) or a - (ccall_action_ty, res_wrapper) <- case tcSplitIOType_maybe orig_res_ty of - Just (io_tycon, res_ty) -> do - s0_id <- newSysLocalMDs realWorldStatePrimTy - s1_id <- newSysLocalMDs realWorldStatePrimTy - let io_data_con = tyConSingleDataCon io_tycon - toIOCon = dataConWorkId io_data_con - (ccall_res_ty, wrap) - | res_ty `eqType` unitTy = - ( mkTupleTy Unboxed [realWorldStatePrimTy], - \the_call -> - mkApps - (Var toIOCon) - [ Type res_ty, - Lam s0_id - $ mkWildCase - (App the_call (Var s0_id)) - (unrestricted ccall_res_ty) - (mkTupleTy Unboxed [realWorldStatePrimTy, unitTy]) - [ Alt - (DataAlt (tupleDataCon Unboxed 1)) - [s1_id] - (mkCoreUnboxedTuple [Var s1_id, unitExpr]) - ] - ] - ) - | otherwise = - ( mkTupleTy Unboxed [realWorldStatePrimTy, res_ty], - \the_call -> mkApps (Var toIOCon) [Type res_ty, the_call] - ) - pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) - Nothing -> do - unsafeDupablePerformIO_id <- - lookupGhcInternalVarId - "GHC.Internal.IO.Unsafe" - "unsafeDupablePerformIO" - io_data_con <- dsLookupDataCon ioDataConName - let ccall_res_ty = - mkTupleTy Unboxed [realWorldStatePrimTy, orig_res_ty] - toIOCon = dataConWorkId io_data_con - wrap the_call = - mkApps - (Var unsafeDupablePerformIO_id) - [ Type orig_res_ty, - mkApps (Var toIOCon) [Type orig_res_ty, the_call] - ] - pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) - let cfun_fcall = - CCall - ( CCallSpec - (StaticTarget NoSourceText cfun_name mUnitId True) - CCallConv - safety - ) - call_app = - mkFCall ccall_uniq cfun_fcall (map Var args_evaled) ccall_action_ty - rhs = - mkCoreLams (tvs ++ args_unevaled) - $ foldr - (\(arg_u, arg_e) acc -> mkDefaultCase (Var arg_u) arg_e acc) - -- res_trans transforms the result. When desugaring - -- JSFFI sync imports, the result is just (IO a) or a, - -- and res_trans is id; for async cases, the result is - -- always (IO JSVal), and res_trans will wrap it in a - -- thunk that has the original return type. This way, we - -- can reuse most of the RHS generation logic for both - -- sync/async imports. - (res_trans $ res_wrapper call_app) - (zip args_unevaled args_evaled) - pure rhs - -importCStub :: Safety -> FastString -> [Type] -> Type -> String -> CStub -importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] +importBindingRHS mUnitId cfun_name tvs arg_tys orig_res_ty res_trans = do + ccall_uniq <- newUnique + args_unevaled <- newSysLocalsDs arg_tys + args_evaled <- newSysLocalsDs arg_tys + -- ccall_action_ty: type of the_call, State# RealWorld -> (# State# RealWorld, a #) + -- res_wrapper: turn the_call to (IO a) or a + (ccall_action_ty, res_wrapper) <- case tcSplitIOType_maybe orig_res_ty of + Just (io_tycon, res_ty) -> do + s0_id <- newSysLocalMDs realWorldStatePrimTy + s1_id <- newSysLocalMDs realWorldStatePrimTy + let io_data_con = tyConSingleDataCon io_tycon + toIOCon = dataConWorkId io_data_con + (ccall_res_ty, wrap) + | res_ty `eqType` unitTy = + ( mkTupleTy Unboxed [realWorldStatePrimTy], + \the_call -> + mkApps + (Var toIOCon) + [ Type res_ty, + Lam s0_id + $ mkWildCase + (App the_call (Var s0_id)) + (unrestricted ccall_res_ty) + (mkTupleTy Unboxed [realWorldStatePrimTy, unitTy]) + [ Alt + (DataAlt (tupleDataCon Unboxed 1)) + [s1_id] + (mkCoreUnboxedTuple [Var s1_id, unitExpr]) + ] + ] + ) + | otherwise = + ( mkTupleTy Unboxed [realWorldStatePrimTy, res_ty], + \the_call -> mkApps (Var toIOCon) [Type res_ty, the_call] + ) + pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) + Nothing -> do + unsafeDupablePerformIO_id <- + lookupGhcInternalVarId + "GHC.Internal.IO.Unsafe" + "unsafeDupablePerformIO" + io_data_con <- dsLookupDataCon ioDataConName + let ccall_res_ty = mkTupleTy Unboxed [realWorldStatePrimTy, orig_res_ty] + toIOCon = dataConWorkId io_data_con + wrap the_call = + mkApps + (Var unsafeDupablePerformIO_id) + [ Type orig_res_ty, + mkApps (Var toIOCon) [Type orig_res_ty, the_call] + ] + pure (realWorldStatePrimTy `mkVisFunTyMany` ccall_res_ty, wrap) + let cfun_fcall = + CCall + ( CCallSpec + (StaticTarget NoSourceText cfun_name mUnitId True) + CCallConv + -- Same even for foreign import javascript unsafe, for + -- the sake of re-entrancy. + PlaySafe + ) + call_app = + mkFCall ccall_uniq cfun_fcall (map Var args_evaled) ccall_action_ty + rhs = + mkCoreLams (tvs ++ args_unevaled) + $ foldr + (\(arg_u, arg_e) acc -> mkDefaultCase (Var arg_u) arg_e acc) + -- res_trans transforms the result. When desugaring + -- JSFFI sync imports, the result is just (IO a) or a, + -- and res_trans is id; for async cases, the result is + -- always (IO JSVal), and res_trans will wrap it in a + -- thunk that has the original return type. This way, we + -- can reuse most of the RHS generation logic for both + -- sync/async imports. + (res_trans $ res_wrapper call_app) + (zip args_unevaled args_evaled) + pure rhs + +importCStub :: Synchronicity -> FastString -> [Type] -> Type -> String -> CStub +importCStub sync cfun_name arg_tys res_ty js_src = CStub c_doc [] [] where import_name = fromJust $ stripPrefix "ghczuwasmzujsffi" (unpackFS cfun_name) import_asm = @@ -465,18 +473,18 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] <> parens ( vcat [ text (show l) - | l <- - [ ".section .custom_section.ghc_wasm_jsffi,\"\",@\n", - ".asciz \"" ++ import_name ++ "\"\n", - ".asciz \"" - ++ ( case safety of - PlayRisky -> "(" - _ -> "async (" - ) - ++ intercalate "," ["$" ++ show i | i <- [1 .. length arg_tys]] - ++ ")\"\n", - ".asciz " ++ show js_src ++ "\n" - ] + | l <- + [ ".section .custom_section.ghc_wasm_jsffi,\"\",@\n", + ".asciz \"" ++ import_name ++ "\"\n", + ".asciz \"" + ++ ( case sync of + Sync -> "(" + Async -> "async (" + ) + ++ intercalate "," ["$" ++ show i | i <- [1 .. length arg_tys]] + ++ ")\"\n", + ".asciz " ++ show js_src ++ "\n" + ] ] ) <> semi @@ -488,8 +496,8 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] ( punctuate comma [ text k <> parens (doubleQuotes (text v)) - | (k, v) <- - [("import_module", "ghc_wasm_jsffi"), ("import_name", import_name)] + | (k, v) <- + [("import_module", "ghc_wasm_jsffi"), ("import_name", import_name)] ] ) ) @@ -501,7 +509,7 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] | otherwise = text ("Hs" ++ ffiType res_ty) import_arg_list = [ text ("Hs" ++ ffiType arg_ty) <+> char 'a' <> int i - | (i, arg_ty) <- zip [1 ..] arg_tys + | (i, arg_ty) <- zip [1 ..] arg_tys ] import_args = case import_arg_list of [] -> text "void" @@ -528,7 +536,7 @@ importCStub safety cfun_name arg_tys res_ty js_src = CStub c_doc [] [] ( punctuate comma [ cfun_make_arg arg_ty (char 'a' <> int n) - | (arg_ty, n) <- zip arg_tys [1 ..] + | (arg_ty, n) <- zip arg_tys [1 ..] ] ) ) @@ -554,7 +562,8 @@ Note [Desugaring JSFFI static export] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A JSFFI static export wraps a top-level Haskell binding as a wasm -module export that can be called in JavaScript as an async function: +module export that can be called in JavaScript as an async/sync +function: foreign export javascript "plus" (+) :: Int -> Int -> Int @@ -565,32 +574,27 @@ stub for a JSFFI export as well: __attribute__((export_name("plus"))) HsJSVal plus(HsInt a1, HsInt a2) { ... } +The generated C stub function would be exported as __exports.plus and +can be called in JavaScript. By default, it's exported as an async +function, so the C stub would always return an HsJSVal which +represents the result Promise; in case of a sync export (using "plus +sync" instead of "plus"), it returns the original result type. + +The C stub function body applies the function closure to arguments, +wrap it with a runIO/runNonIO top handler function, then schedules +Haskell computation to happen, then fetches the result. In case of an +async export, the top handler creates a JavaScript Promise that stands +for Haskell evaluation result, and the Promise will eventually be +resolved with the result or rejected with an exception. That Promise +is what we return in the C stub function. See +Note [Async JSFFI scheduler] for detailed explanation. + At link time, you need to pass -optl-Wl,--export=plus,--export=... to specify your entrypoint function symbols as roots of wasm-ld link-time garbage collection. As for the auto-generated exports when desugaring the JSFFI dynamic exports, they will be transitively included as well due to the export_name attribute. -For each JSFFI static export, we create an internal worker function -which takes the same arguments as the exported Haskell binding, but -always returns (IO JSVal). Its RHS simply applies the arguments to the -original binding, then applies a runIO/runNonIO top handler function -to the result. The top handler creates a JavaScript Promise that -stands for Haskell evaluation result, schedules Haskell computation to -happen, and the Promise will eventually be resolved with the result or -rejected with an exception. That Promise is what we return in the C -stub function. See Note [Async JSFFI scheduler] for detailed -explanation. - -There's nothing else to explain about the C stub function body; just -like C FFI exports, it calls rts_mk* to box the arguments, rts_apply -to apply them to the worker function, evaluates the result, then -unboxes the resulting Promise using rts_getJSVal and returns it. - -Now, in JavaScript, once the wasm instance is initialized, you can -directly call these exports and await them, as if they're real -JavaScript async functions. - -} dsWasmJSExport :: @@ -598,108 +602,140 @@ dsWasmJSExport :: Coercion -> CLabelString -> DsM (CHeader, CStub, String, [Id], [Binding]) -dsWasmJSExport fn_id co ext_name = do - work_uniq <- newUnique +dsWasmJSExport fn_id co str = dsWasmJSExport' sync (Just fn_id) co ext_name + where + (sync, ext_name) = case words $ unpackFS str of + [ext_name] -> (Async, ext_name) + [ext_name, "sync"] -> (Sync, ext_name) + _ -> panic "dsWasmJSExport: unrecognized label string" + +dsWasmJSExport' :: + Synchronicity -> + Maybe Id -> + Coercion -> + String -> + DsM (CHeader, CStub, String, [Id], [Binding]) +dsWasmJSExport' sync m_fn_id co ext_name = do let ty = coercionRKind co - (tvs, fun_ty) = tcSplitForAllInvisTyVars ty + (_, fun_ty) = tcSplitForAllInvisTyVars ty (arg_tys, orig_res_ty) = tcSplitFunTys fun_ty (res_ty, is_io) = case tcSplitIOType_maybe orig_res_ty of Just (_, res_ty) -> (res_ty, True) Nothing -> (orig_res_ty, False) - (_, res_ty_args) = splitTyConApp res_ty res_ty_str = ffiType res_ty - args <- newSysLocalsDs arg_tys + top_handler_mod = case sync of + Sync -> "GHC.Internal.TopHandler" + Async -> "GHC.Internal.Wasm.Prim.Exports" + top_handler_name + | is_io = "runIO" + | otherwise = "runNonIO" + -- In case of sync export, we use the normal C FFI tophandler + -- functions. They would call flushStdHandles in case of uncaught + -- exception but not in normal cases, but we want flushStdHandles to + -- be called so that there are less run-time surprises for users, + -- and that's what our tophandler functions already do. + -- + -- So for each sync export, we first wrap the computation with a C + -- FFI tophandler, and then sequence it with flushStdHandles using + -- (<*) :: IO a -> IO b -> IO a. But it's trickier to call (<*) + -- using RTS API given type class dictionary is involved, so we'll + -- just use finally. + finally_id <- + lookupGhcInternalVarId + "GHC.Internal.Control.Exception.Base" + "finally" + flushStdHandles_id <- + lookupGhcInternalVarId + "GHC.Internal.TopHandler" + "flushStdHandles" promiseRes_id <- - lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" $ "js_promiseResolve" ++ res_ty_str - runIO_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "runIO" - runNonIO_id <- lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" "runNonIO" - let work_id = - mkExportedVanillaId - ( mkExternalName - work_uniq - (nameModule $ getName fn_id) - (mkVarOcc $ "jsffi_" ++ occNameString (getOccName fn_id)) - generatedSrcSpan - ) - (exprType work_rhs) - work_rhs = - mkCoreLams (tvs ++ args) - $ mkApps - (Var $ if is_io then runIO_id else runNonIO_id) - [ Type res_ty, - mkApps (Var promiseRes_id) $ map Type res_ty_args, - mkApps (Cast (Var fn_id) co) - $ map (Type . mkTyVarTy) tvs - ++ map Var args - ] - work_closure = ppr work_id <> text "_closure" - work_closure_decl = text "extern StgClosure" <+> work_closure <> semi + lookupGhcInternalVarId "GHC.Internal.Wasm.Prim.Exports" + $ "js_promiseResolve" + ++ res_ty_str + top_handler_id <- lookupGhcInternalVarId top_handler_mod top_handler_name + let ppr_closure c = ppr c <> text "_closure" + mk_extern_closure_decl c = + text "extern StgClosure" <+> ppr_closure c <> semi + gc_root_closures = maybeToList m_fn_id ++ case sync of + -- In case of C FFI top handlers, they are already declared in + -- RtsAPI.h and registered as GC roots in initBuiltinGcRoots. + -- flushStdHandles is already registered but somehow the C + -- stub can't access its declaration, won't hurt to declare it + -- again here. + Sync -> [finally_id, flushStdHandles_id] + Async -> [top_handler_id, promiseRes_id] + extern_closure_decls = vcat $ map mk_extern_closure_decl gc_root_closures cstub_attr = text "__attribute__" <> parens - (parens $ text "export_name" <> parens (doubleQuotes $ ftext ext_name)) + (parens $ text "export_name" <> parens (doubleQuotes $ text ext_name)) cstub_arg_list = [ text ("Hs" ++ ffiType (scaledThing arg_ty)) <+> char 'a' <> int i - | (i, arg_ty) <- zip [1 ..] arg_tys + | (i, arg_ty) <- zip [1 ..] arg_tys ] cstub_args = case cstub_arg_list of [] -> text "void" _ -> hsep $ punctuate comma cstub_arg_list - cstub_proto = text "HsJSVal" <+> ftext ext_name <> parens cstub_args + cstub_proto + | Sync <- sync, + res_ty `eqType` unitTy = + text "void" <+> text ext_name <> parens cstub_args + | Sync <- sync = + text ("Hs" ++ res_ty_str) <+> text ext_name <> parens cstub_args + | Async <- sync = + text "HsJSVal" <+> text ext_name <> parens cstub_args + c_closure c = char '&' <> ppr_closure c + c_call fn args = text fn <> parens (hsep $ punctuate comma args) + c_rts_apply = + Data.List.foldl1' $ \fn arg -> c_call "rts_apply" [text "cap", fn, arg] + apply_top_handler expr = case sync of + Sync -> + c_rts_apply + [ c_closure finally_id, + c_rts_apply [c_closure top_handler_id, expr], + c_closure flushStdHandles_id + ] + Async -> + c_rts_apply [c_closure top_handler_id, c_closure promiseRes_id, expr] + cstub_ret + | Sync <- sync, res_ty `eqType` unitTy = empty + | Sync <- sync = text $ "return rts_get" ++ res_ty_str ++ "(ret);" + | Async <- sync = text "return rts_getJSVal(ret);" + (cstub_target, real_args) + | Just fn_id <- m_fn_id = (c_closure fn_id, zip [1 ..] arg_tys) + | otherwise = (text "(HaskellObj)deRefStablePtr(a1)", zip [2 ..] $ tail arg_tys) cstub_body = vcat [ lbrace, text "Capability *cap = rts_lock();", text "HaskellObj ret;", - -- rts_evalLazyIO is fine, the top handler always returns - -- an evaluated result - text "rts_evalLazyIO" - <> parens - ( hsep - $ punctuate - comma - [ text "&cap", - foldl' - ( \acc (i, arg_ty) -> - text "rts_apply" - <> parens - ( hsep - $ punctuate - comma - [ text "cap", - acc, - text ("rts_mk" ++ ffiType (scaledThing arg_ty)) - <> parens - (hsep $ punctuate comma [text "cap", char 'a' <> int i]) - ] - ) - ) - (char '&' <> work_closure) - $ zip [1 ..] arg_tys, - text "&ret" - ] - ) + c_call + "rts_inCall" + [ text "&cap", + apply_top_handler + $ c_rts_apply + $ cstub_target + : [ c_call + ("rts_mk" ++ ffiType (scaledThing arg_ty)) + [text "cap", char 'a' <> int i] + | (i, arg_ty) <- real_args + ], + text "&ret" + ] <> semi, - text "rts_checkSchedStatus" - <> parens (doubleQuotes (ftext ext_name) <> comma <> text "cap") + c_call "rts_checkSchedStatus" [doubleQuotes (text ext_name), text "cap"] <> semi, text "rts_unlock(cap);", - text "return rts_getJSVal(ret);", + cstub_ret, rbrace ] cstub = commonCDecls - $+$ work_closure_decl + $+$ extern_closure_decls $+$ cstub_attr $+$ cstub_proto $+$ cstub_body - pure - ( CHeader commonCDecls, - CStub cstub [] [], - "", - [work_id], - [(work_id, work_rhs)] - ) + pure (CHeader commonCDecls, CStub cstub [] [], "", gc_root_closures, []) lookupGhcInternalVarId :: FastString -> String -> DsM Id lookupGhcInternalVarId m v = do ===================================== compiler/GHC/Tc/Gen/Foreign.hs ===================================== @@ -78,7 +78,7 @@ import GHC.Data.Bag import GHC.Driver.Hooks import qualified GHC.LanguageExtensions as LangExt -import Control.Monad ( zipWithM ) +import Control.Monad ( when, zipWithM ) import Control.Monad.Trans.Writer.CPS ( WriterT, runWriterT, tell ) import Control.Monad.Trans.Class @@ -444,7 +444,7 @@ tcFExport d = pprPanic "tcFExport" (ppr d) tcCheckFEType :: Type -> ForeignExport GhcRn -> TcM (ForeignExport GhcTc) tcCheckFEType sig_ty edecl@(CExport src (L l (CExportStatic esrc str cconv))) = do checkCg (Left edecl) backendValidityOfCExport - checkTc (isCLabelString str) (TcRnInvalidCIdentifier str) + when (cconv /= JavaScriptCallConv) $ checkTc (isCLabelString str) (TcRnInvalidCIdentifier str) cconv' <- checkCConv (Left edecl) cconv checkForeignArgs isFFIExternalTy arg_tys checkForeignRes nonIOok noCheckSafe isFFIExportResultTy res_ty ===================================== docs/users_guide/wasm.rst ===================================== @@ -231,15 +231,15 @@ There are two kinds of JSFFI imports: synchronous/asynchronous imports. ``unsafe`` indicates synchronous imports, which has the following caveats: -- The calling thread as well as the entire runtime blocks on waiting - for the import result. -- If the JavaScript code throws, the runtime crashes with the same - error. A JavaScript exception cannot be handled as a Haskell - exception here, so you need to use a JavaScript ``catch`` explicitly - shall the need arise. -- Like ``unsafe`` C imports, re-entrance is not supported, the imported - foreign code must not call into Haskell again. Doing so would result - in a runtime panic. +- The calling thread as well as the entire runtime blocks on waiting for + the import result. +- If the JavaScript code throws, the runtime crashes with the same + error. A JavaScript exception cannot be handled as a Haskell exception + here, so you need to use a JavaScript ``catch`` explicitly shall the + need arise. +- Unlike ``unsafe`` C imports, re-entrance is actually supported, the + imported JavaScript code can call into Haskell again, provided that + Haskell function is exported as a synchronous one. When a JSFFI import is marked as ``safe`` / ``interruptible`` or lacks safety annotation, then it’s treated as an asynchronous import. The @@ -274,14 +274,12 @@ runtime, and resumed when the ``Promise`` actually resolves or rejects. Compared to synchronous JSFFI imports, asynchronous JSFFI imports have the following notable pros/cons: -- Waiting for the result only blocks a single Haskell thread, other - threads can still make progress and garbage collection may still - happen. -- If the ``Promise`` rejects, Haskell code can catch JavaScript errors - as ``JSException``\ s. -- Re-entrance is supported. The JavaScript code may call into Haskell - again and vice versa. -- Of course, it has higher overhead than synchronous JSFFI imports. +- Waiting for the result only blocks a single Haskell thread, other + threads can still make progress and garbage collection may still + happen. +- If the ``Promise`` rejects, Haskell code can catch JavaScript errors + as ``JSException``\ s. +- It has higher overhead than synchronous JSFFI imports. Using thunks to encapsulate ``Promise`` result allows cheaper concurrency without even needing to fork Haskell threads just for @@ -345,12 +343,17 @@ wrapper, and as long as the wasm instance is properly initialized, you can call ``await instance.exports.my_fib(10)`` to invoke the exported Haskell function and get the result. -Unlike JSFFI imports which have synchronous/asynchronous flavors, JSFFI -exports are always asynchronous. Calling them always return a -``Promise`` in JavaScript that needs to be ``await``\ ed for the real -result. If the Haskell function throws, the ``Promise`` is rejected with -a ``WebAssembly.RuntimeError``, and the ``message`` field contains a -JavaScript string of the Haskell exception. +JSFFI exports are asynchronous by default. Calling an async export +return a ``Promise`` in JavaScript that needs to be ``await``\ ed for +the real result. If the Haskell function throws, the ``Promise`` is +rejected with a ``WebAssembly.RuntimeError``, and the ``message`` field +contains a JavaScript string of the Haskell exception. + +Additionally, sync exports are also supported by using ``"my_fib sync"`` +instead of ``"my_fib"``. With ``sync`` added alongside export function +name, the JavaScript function would return the result synchronously. For +the time being, sync exports don’t support propagating uncaught Haskell +exception to a JavaScript exception at the call site yet. Above is the static flavor of JSFFI exports. It’s also possible to export a dynamically created Haskell function closure as a JavaScript @@ -366,8 +369,9 @@ function and obtain its ``JSVal``: This is also much like ``foreign import ccall "wrapper"``, which wraps a Haskell function closure as a C function pointer. Note that ``unsafe`` / ``safe`` annotation is ignored here, since the ``JSVal`` that represent -the exported function is always returned synchronously, but it is always -an asynchronous JavaScript function, just like static JSFFI exports. +the exported function is always returned synchronously. Likewise, you +can use ``"wrapper sync"`` instead of ``"wrapper"`` to indicate the +returned JavaScript function is sync instead of async. The ``JSVal`` callbacks created by dynamic JSFFI exports can be passed to the rest of JavaScript world to be invoked later. But wait, didn’t we ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -79,9 +79,9 @@ filled is generated via raiseJSException. -} -stg_blockPromise :: JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r -stg_blockPromise p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> - case stg_jsffi_check (unsafeCoerce# $ toException WouldBlockException) s0 of +stg_blockPromise :: String -> JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r +stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> + case stg_jsffi_check (unsafeCoerce# $ toException $ WouldBlockException err_msg) s0 of (# s1 #) -> case myThreadId# s1 of (# s2, tso #) -> case makeStablePtr# tso s2 of (# s3, sp #) -> ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -139,8 +139,8 @@ foreign import javascript unsafe "`${$1.stack ? $1.stack : $1}`" instance Exception JSException -data WouldBlockException - = WouldBlockException +newtype WouldBlockException + = WouldBlockException String deriving (Show) instance Exception WouldBlockException ===================================== rts/include/RtsAPI.h ===================================== @@ -587,15 +587,15 @@ void rts_done (void); // the base package itself. // #if defined(COMPILING_WINDOWS_DLL) && !defined(COMPILING_GHC_INTERNAL_PACKAGE) -__declspec(dllimport) extern StgWord ghczminternal_GHCziInternalziTopHandler_runIO_closure[]; -__declspec(dllimport) extern StgWord ghczminternal_GHCziInternalziTopHandler_runNonIO_closure[]; +__declspec(dllimport) extern StgClosure ghczminternal_GHCziInternalziTopHandler_runIO_closure; +__declspec(dllimport) extern StgClosure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure; #else -extern StgWord ghczminternal_GHCziInternalziTopHandler_runIO_closure[]; -extern StgWord ghczminternal_GHCziInternalziTopHandler_runNonIO_closure[]; +extern StgClosure ghczminternal_GHCziInternalziTopHandler_runIO_closure; +extern StgClosure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure; #endif -#define runIO_closure ghczminternal_GHCziInternalziTopHandler_runIO_closure -#define runNonIO_closure ghczminternal_GHCziInternalziTopHandler_runNonIO_closure +#define runIO_closure DLL_IMPORT_DATA_REF(ghczminternal_GHCziInternalziTopHandler_runIO_closure) +#define runNonIO_closure DLL_IMPORT_DATA_REF(ghczminternal_GHCziInternalziTopHandler_runNonIO_closure) /* ------------------------------------------------------------------------ */ ===================================== testsuite/tests/jsffi/jsffigc.hs ===================================== @@ -10,17 +10,16 @@ import System.Mem type BinOp a = a -> a -> a -foreign import javascript "wrapper" +foreign import javascript "wrapper sync" js_from_hs :: BinOp Int -> IO JSVal --- This must be safe since we intend to call back into Haskell again. -foreign import javascript safe "dynamic" +foreign import javascript unsafe "dynamic" js_to_hs :: JSVal -> BinOp Int foreign import javascript "wrapper" js_mk_cont :: IO () -> IO JSVal -foreign export javascript "testDynExportFree" +foreign export javascript "testDynExportFree sync" testDynExportFree :: Int -> Int -> Int -> IO () -- JSVal uses Weak# under the hood for garbage collection support, ===================================== testsuite/tests/jsffi/jsffigc.mjs ===================================== @@ -8,7 +8,7 @@ async function reallyGC() { } export default async (__exports) => { - await __exports.testDynExportFree(114, 514, 1919810); + __exports.testDynExportFree(114, 514, 1919810); const cont = await __exports.testDynExportGC(114, 514, 1919810); await reallyGC(); ===================================== testsuite/tests/jsffi/jsffisleep.hs ===================================== @@ -20,8 +20,8 @@ foreign export ccall "testWouldBlock" -- non-main exports in C FFI. In JSFFI, it's always done automatically -- for every export though. testWouldBlock :: IO () -testWouldBlock = catch (threadDelay 1000000) $ \WouldBlockException -> do - print WouldBlockException +testWouldBlock = catch (threadDelay 1000000) $ \(WouldBlockException err) -> do + print $ WouldBlockException err flushStdHandles foreign export javascript "testLazySleep" ===================================== testsuite/tests/jsffi/jsffisleep.stdout ===================================== @@ -1,4 +1,4 @@ -WouldBlockException +WouldBlockException "new Promise(res => setTimeout(res, $1 / 1000))" zzzzzzz i sleep Left thread killed ===================================== testsuite/tests/jsffi/textconv.hs ===================================== @@ -45,7 +45,7 @@ textToJSString (Text (ByteArray ba#) (I# off#) (I# len#)) = unsafeDupablePerform (# s1, mba# #) -> case copyByteArray# ba# off# mba# 0# len# s1 of s2 -> keepAlive# mba# s2 $ unIO $ js_to_str (Ptr (mutableByteArrayContents# mba#)) $ I# len# -foreign export javascript "main" +foreign export javascript "main sync" main :: IO () main :: IO () ===================================== testsuite/tests/jsffi/textconv.mjs ===================================== @@ -1,3 +1,3 @@ -export default async (__exports) => { - await __exports.main(); +export default (__exports) => { + __exports.main(); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/73ba1e6ec811c19baaf77abc72ba886a80fef5b4...9b54eecbee7329543e5016cec1574831bfb788c2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/73ba1e6ec811c19baaf77abc72ba886a80fef5b4...9b54eecbee7329543e5016cec1574831bfb788c2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/80eb084a/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:13:41 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 09:13:41 -0500 Subject: [Git][ghc/ghc][master] compiler: avoid overwriting existing writers in putWithTables Message-ID: <67c70a958a3e_a5f48cd7238105615@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - 1 changed file: - compiler/GHC/Iface/Binary.hs Changes: ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -43,7 +43,6 @@ import GHC.Types.Unique.FM import GHC.Utils.Panic import GHC.Utils.Binary as Binary import GHC.Data.FastMutInt -import GHC.Data.FastString (FastString) import GHC.Types.Unique import GHC.Utils.Outputable import GHC.Types.Name.Cache @@ -321,18 +320,21 @@ putWithTables compressionLevel bh' put_payload = do (ifaceType_wt, ifaceTypeWriter) <- initWriteIfaceType compressionLevel -- Initialise the 'WriterUserData'. - let writerUserData = mkWriterUserData - [ mkSomeBinaryWriter @FastString fsWriter - , mkSomeBinaryWriter @Name nameWriter - -- We sometimes serialise binding and non-binding names differently, but - -- not during 'ModIface' serialisation. Here, we serialise both to the same - -- deduplication table. - -- - -- See Note [Binary UserData] - , mkSomeBinaryWriter @BindingName $ mkWriter (\bh name -> putEntry nameWriter bh (getBindingName name)) - , mkSomeBinaryWriter @IfaceType ifaceTypeWriter - ] - let bh = setWriterUserData bh' writerUserData + -- + -- Similar to how 'getTables' calls 'addReaderToUserData', here we + -- call 'addWriterToUserData' instead of 'setWriterUserData', to + -- avoid overwriting existing writers of other types in bh'. + let bh = + addWriterToUserData fsWriter + $ addWriterToUserData nameWriter + -- We sometimes serialise binding and non-binding names differently, but + -- not during 'ModIface' serialisation. Here, we serialise both to the same + -- deduplication table. + -- + -- See Note [Binary UserData] + $ addWriterToUserData + (mkWriter $ \bh name -> putEntry nameWriter bh $ getBindingName name) + $ addWriterToUserData ifaceTypeWriter bh' ([fs_count, name_count, ifacetype_count] , r) <- -- The order of these entries matters! View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c331eebf575221ed8c67ca232bac4ae047b794a3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c331eebf575221ed8c67ca232bac4ae047b794a3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/a2f4719d/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:14:34 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 09:14:34 -0500 Subject: [Git][ghc/ghc][master] 2 commits: ghci: Serialise mi_top_env Message-ID: <67c70aca77a63_a5f48aa71d4110476@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 17 changed files: - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModIface.hs - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T Changes: ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -47,7 +47,6 @@ import GHC.Core.RoughMap ( RoughMatchTc(..) ) import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env -import GHC.Driver.Backend import GHC.Driver.DynFlags import GHC.Driver.Plugins @@ -342,7 +341,7 @@ mkIface_ hsc_env trust_info = setSafeMode safe_mode annotations = map mkIfaceAnnotation anns icomplete_matches = map mkIfaceCompleteMatch complete_matches - !rdrs = maybeGlobalRdrEnv rdr_env + !rdrs = mkIfaceTopEnv rdr_env emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag @@ -395,15 +394,11 @@ mkIface_ hsc_env -- Desugar.addExportFlagsAndRules). The mi_top_env field is used -- by GHCi to decide whether the module has its full top-level -- scope available. (#5534) - maybeGlobalRdrEnv :: GlobalRdrEnv -> Maybe IfaceTopEnv - maybeGlobalRdrEnv rdr_env - | backendWantsGlobalBindings (backend dflags) - = Just $! let !exports = forceGlobalRdrEnv (globalRdrEnvLocal rdr_env) - !imports = mkIfaceImports import_decls - in IfaceTopEnv exports imports - -- See Note [Forcing GREInfo] in GHC.Types.GREInfo. - | otherwise - = Nothing + mkIfaceTopEnv :: GlobalRdrEnv -> IfaceTopEnv + mkIfaceTopEnv rdr_env + = let !exports = sortAvails $ gresToAvailInfo $ globalRdrEnvElts $ globalRdrEnvLocal rdr_env + !imports = mkIfaceImports import_decls + in IfaceTopEnv exports imports ifFamInstTcName = ifFamInstFam @@ -515,8 +510,8 @@ mkIfaceImports :: [ImportUserSpec] -> [IfaceImport] mkIfaceImports = map go where go (ImpUserSpec decl ImpUserAll) = IfaceImport decl ImpIfaceAll - go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env)) - go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns) + go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (sortAvails env)) + go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut (nameSetElemsStable ns)) mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -26,7 +26,8 @@ module GHC.Iface.Syntax ( IfaceCompleteMatch(..), IfaceLFInfo(..), IfaceTopBndrInfo(..), IfaceImport(..), - ImpIfaceList(..), + ifImpModule, + ImpIfaceList(..), IfaceExport, -- * Binding names IfaceTopBndr, @@ -69,6 +70,7 @@ import GHC.Types.Name.Set import GHC.Types.Name.Reader import GHC.Types.CostCentre import GHC.Types.Literal +import GHC.Types.Avail import GHC.Types.ForeignCall import GHC.Types.Annotations( AnnPayload, AnnTarget ) import GHC.Types.Basic @@ -112,12 +114,48 @@ infixl 3 &&& ************************************************************************ -} +type IfaceExport = AvailInfo + data IfaceImport = IfaceImport ImpDeclSpec ImpIfaceList data ImpIfaceList = ImpIfaceAll -- ^ no user import list - | ImpIfaceExplicit !IfGlobalRdrEnv - | ImpIfaceEverythingBut !NameSet + | ImpIfaceExplicit !DetOrdAvails + | ImpIfaceEverythingBut ![Name] + + +-- | Extract the imported module from an IfaceImport +ifImpModule :: IfaceImport -> Module +ifImpModule (IfaceImport declSpec _) = is_mod declSpec + +instance Binary IfaceImport where + put_ bh (IfaceImport declSpec ifaceList) = do + put_ bh declSpec + put_ bh ifaceList + get bh = do + declSpec <- get bh + ifaceList <- get bh + return (IfaceImport declSpec ifaceList) + +instance Binary ImpIfaceList where + put_ bh ImpIfaceAll = putByte bh 0 + put_ bh (ImpIfaceExplicit env) = do + putByte bh 1 + put_ bh env + put_ bh (ImpIfaceEverythingBut ns) = do + putByte bh 2 + put_ @[Name] bh ns + get bh = do + tag <- getByte bh + case tag of + 0 -> return ImpIfaceAll + 1 -> do + env <- get bh + return (ImpIfaceExplicit env) + 2 -> do + ns <- get @[Name] bh + return (ImpIfaceEverythingBut ns) + _ -> fail "instance Binary ImpIfaceList: Invalid tag" -- | A binding top-level 'Name' in an interface file (e.g. the name of an -- 'IfaceDecl'). ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -104,6 +104,7 @@ import GHC.Types.SourceText import GHC.Types.Basic hiding ( SuccessFlag(..) ) import GHC.Types.CompleteMatch import GHC.Types.SrcLoc +import GHC.Types.Avail import GHC.Types.TypeEnv import GHC.Types.Unique.FM import GHC.Types.Unique.DSet ( mkUniqDSet ) @@ -114,7 +115,7 @@ import GHC.Types.Literal import GHC.Types.Var as Var import GHC.Types.Var.Set import GHC.Types.Name -import GHC.Types.Name.Reader +import GHC.Types.Name.Set import GHC.Types.Name.Env import GHC.Types.DefaultEnv ( ClassDefaults(..), defaultEnv ) import GHC.Types.Id @@ -2242,9 +2243,7 @@ hydrateCgBreakInfo CgBreakInfo{..} = do -- | This function is only used to construct the environment for GHCi, -- so we make up fake locations -tcIfaceImport :: HscEnv -> IfaceImport -> ImportUserSpec -tcIfaceImport _ (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll -tcIfaceImport _ (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut ns) -tcIfaceImport hsc_env (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (hydrateGlobalRdrEnv get_GRE_info gre)) - where - get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm +tcIfaceImport :: IfaceImport -> ImportUserSpec +tcIfaceImport (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll +tcIfaceImport (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut (mkNameSet ns)) +tcIfaceImport (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (getDetOrdAvails gre)) ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -2015,6 +2015,8 @@ lookupGREInfo hsc_env nm -- and looks up the TyThing in the type environment. -- -- See Note [Retrieving the GREInfo from interfaces] in GHC.Types.GREInfo. + -- Note: This function is very similar to 'tcIfaceGlobal', it would be better to + -- use that if possible. = case nameModule_maybe nm of Nothing -> UnboundGRE Just mod -> ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -1189,7 +1189,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) (gres, imp_user_list) = case want_hiding of Exactly -> let gre_env = mkGlobalRdrEnv $ concatMap (gresFromIE decl_spec) items2 - in (gre_env, ImpUserExplicit gre_env) + in (gre_env, ImpUserExplicit (gresToAvailInfo $ globalRdrEnvElts $ gre_env)) EverythingBut -> let hidden_names = mkNameSet $ concatMap (map greName . snd) items2 in (importsFromIface hsc_env iface decl_spec (Just hidden_names), ImpUserEverythingBut hidden_names) ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -53,7 +53,7 @@ import GHC.Driver.DynFlags import GHC.Driver.Ppr import GHC.Driver.Config -import GHC.Rename.Names (importsFromIface) +import GHC.Rename.Names (importsFromIface, gresFromAvails) import GHC.Runtime.Eval.Types import GHC.Runtime.Interpreter as GHCi @@ -113,6 +113,7 @@ import GHC.Types.TyThing import GHC.Types.Breakpoint import GHC.Types.Unique.Map +import GHC.Types.Avail import GHC.Unit import GHC.Unit.Module.Graph import GHC.Unit.Module.ModIface @@ -122,7 +123,7 @@ import GHC.Unit.Home.PackageTable import GHC.Tc.Module ( runTcInteractive, tcRnType, loadUnqualIfaces ) import GHC.Tc.Solver (simplifyWantedsTcM) -import GHC.Tc.Utils.Env (tcGetInstEnvs, lookupGlobal) +import GHC.Tc.Utils.Env (tcGetInstEnvs) import GHC.Tc.Utils.Instantiate (instDFunType) import GHC.Tc.Utils.Monad import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) ) @@ -836,21 +837,25 @@ mkTopLevEnv hsc_env modl Nothing -> pure $ Left "not a home module" Just details -> case mi_top_env (hm_iface details) of - Nothing -> pure $ Left "not interpreted" - Just (IfaceTopEnv exports imports) -> do + (IfaceTopEnv exports imports) -> do imports_env <- runInteractiveHsc hsc_env $ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv) $ forM imports $ \iface_import -> do - let ImpUserSpec spec details = tcIfaceImport hsc_env iface_import + let ImpUserSpec spec details = tcIfaceImport iface_import iface <- loadSrcInterface (text "imported by GHCi") (moduleName $ is_mod spec) (is_isboot spec) (is_pkg_qual spec) pure $ case details of ImpUserAll -> importsFromIface hsc_env iface spec Nothing ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns) - ImpUserExplicit x -> x - let get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm - let exports_env = hydrateGlobalRdrEnv get_GRE_info exports + ImpUserExplicit x -> + -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y). + -- It is only used for error messages. It seems dubious even to add an import context to these GREs as + -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that + -- the test case produce the same output as before. + let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } } + in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x + let exports_env = mkGlobalRdrEnv $ gresFromAvails hsc_env Nothing (getDetOrdAvails exports) pure $ Right $ plusGlobalRdrEnv imports_env exports_env where hpt = hsc_HPT hsc_env @@ -868,8 +873,8 @@ moduleIsInterpreted :: GhcMonad m => Module -> m Bool moduleIsInterpreted modl = withSession $ \h -> if notHomeModule (hsc_home_unit h) modl then return False - else liftIO (lookupHpt (hsc_HPT h) (moduleName modl)) >>= \case - Just details -> return (isJust (mi_top_env (hm_iface details))) + else liftIO (HUG.lookupHugByModule modl (hsc_HUG h)) >>= \case + Just hmi -> return (isJust $ homeModInfoByteCode hmi) _not_a_home_module -> return False -- | Looks up an identifier in the current interactive context (for :info) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -124,7 +124,7 @@ import GHC.Serialized import GHC.Unit.Finder import GHC.Unit.Module import GHC.Unit.Module.ModIface -import GHC.Unit.Module.Deps +import GHC.Iface.Syntax import GHC.Utils.Misc import GHC.Utils.Panic as Panic @@ -2887,16 +2887,12 @@ reifyModule (TH.Module (TH.PkgName pkgString) (TH.ModName mString)) = do reifyFromIface reifMod = do iface <- loadInterfaceForModule (text "reifying module from TH for" <+> ppr reifMod) reifMod - let usages = [modToTHMod m | usage <- mi_usages iface, - Just m <- [usageToModule (moduleUnit reifMod) usage] ] + let IfaceTopEnv _ imports = mi_top_env iface + -- Convert IfaceImport to module names + usages = [modToTHMod (ifImpModule imp) | imp <- imports] return $ TH.ModuleInfo usages - usageToModule :: Unit -> Usage -> Maybe Module - usageToModule _ (UsageFile {}) = Nothing - usageToModule this_pkg (UsageHomeModule { usg_mod_name = mn }) = Just $ mkModule this_pkg mn - usageToModule _ (UsagePackageModule { usg_mod = m }) = Just m - usageToModule _ (UsageMergedRequirement { usg_mod = m }) = Just m - usageToModule this_pkg (UsageHomeModuleInterface { usg_mod_name = mn }) = Just $ mkModule this_pkg mn + ------------------------------ mkThAppTs :: TH.Type -> [TH.Type] -> TH.Type ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -206,7 +206,7 @@ data ImportUserSpec data ImpUserList = ImpUserAll -- ^ no user import list - | ImpUserExplicit !GlobalRdrEnv + | ImpUserExplicit ![AvailInfo] | ImpUserEverythingBut !NameSet -- | A 'NameShape' is a substitution on 'Name's that can be used ===================================== compiler/GHC/Types/Avail.hs ===================================== @@ -22,7 +22,8 @@ module GHC.Types.Avail ( filterAvails, nubAvails, sortAvails, - DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails) + DetOrdAvails(DetOrdAvails, getDetOrdAvails, DefinitelyDeterministicAvails), + emptyDetOrdAvails ) where import GHC.Prelude @@ -74,7 +75,7 @@ type Avails = [AvailInfo] -- We guarantee a deterministic order by either using the order explicitly -- given by the user (e.g. in an explicit constructor export list) or instead -- by sorting the avails with 'sortAvails'. -newtype DetOrdAvails = DefinitelyDeterministicAvails Avails +newtype DetOrdAvails = DefinitelyDeterministicAvails { getDetOrdAvails :: Avails } deriving newtype (Binary, Outputable, NFData) -- | It's always safe to match on 'DetOrdAvails' @@ -245,3 +246,7 @@ instance Binary AvailInfo where instance NFData AvailInfo where rnf (Avail n) = rnf n rnf (AvailTC a b) = rnf a `seq` rnf b + +-- | Create an empty DetOrdAvails +emptyDetOrdAvails :: DetOrdAvails +emptyDetOrdAvails = DefinitelyDeterministicAvails [] ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -133,6 +133,7 @@ import GHC.Unit.Module import GHC.Utils.Misc as Utils import GHC.Utils.Outputable import GHC.Utils.Panic +import GHC.Utils.Binary import Control.DeepSeq import Control.Monad ( guard ) @@ -1946,6 +1947,22 @@ data ImpDeclSpec instance NFData ImpDeclSpec where rnf = rwhnf -- Already strict in all fields +instance Binary ImpDeclSpec where + put_ bh (ImpDeclSpec mod as pkg_qual qual _dloc isboot) = do + put_ bh mod + put_ bh as + put_ bh pkg_qual + put_ bh qual + put_ bh isboot + + get bh = do + mod <- get bh + as <- get bh + pkg_qual <- get bh + qual <- get bh + isboot <- get bh + return (ImpDeclSpec mod as pkg_qual qual noSrcSpan isboot) + -- | Import Item Specification -- -- Describes import info a particular Name ===================================== compiler/GHC/Types/PkgQual.hs ===================================== @@ -6,6 +6,7 @@ module GHC.Types.PkgQual where import GHC.Prelude import GHC.Types.SourceText import GHC.Unit.Types +import GHC.Utils.Binary import GHC.Utils.Outputable import Data.Data @@ -38,4 +39,22 @@ instance Outputable PkgQual where ThisPkg u -> doubleQuotes (ppr u) OtherPkg u -> doubleQuotes (ppr u) +instance Binary PkgQual where + put_ bh NoPkgQual = putByte bh 0 + put_ bh (ThisPkg u) = do + putByte bh 1 + put_ bh u + put_ bh (OtherPkg u) = do + putByte bh 2 + put_ bh u + + get bh = do + tag <- getByte bh + case tag of + 0 -> return NoPkgQual + 1 -> do u <- get bh + return (ThisPkg u) + 2 -> do u <- get bh + return (OtherPkg u) + _ -> fail "instance Binary PkgQual: Invalid tag" ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -111,7 +111,6 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name -import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -299,20 +298,13 @@ data ModIface_ (phase :: ModIfacePhase) mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: !(Maybe IfaceTopEnv), + mi_top_env_ :: IfaceTopEnv, -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which -- may contains declarations for things not actually -- defined by the user). Used for GHCi and for inspecting -- the contents of modules via the GHC API only. - -- - -- (We need the source file to figure out the - -- top-level environment, if we didn't compile this module - -- from source then this field contains @Nothing@). - -- - -- Strictly speaking this field should live in the - -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -365,13 +357,23 @@ data ModIface_ (phase :: ModIfacePhase) -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !IfGlobalRdrEnv -- ^ all top level things in this module, including unexported stuff + { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where rnf (IfaceTopEnv a b) = rnf a `seq` rnf b +instance Binary IfaceTopEnv where + put_ bh (IfaceTopEnv exports imports) = do + put_ bh exports + put_ bh imports + get bh = do + exports <- get bh + imports <- get bh + return (IfaceTopEnv exports imports) + + {- Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -479,6 +481,7 @@ instance Binary ModIface where mi_trust_ = trust, mi_trust_pkg_ = trust_pkg, mi_complete_matches_ = complete_matches, + mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header @@ -526,6 +529,7 @@ instance Binary ModIface where put_ bh trust put_ bh trust_pkg put_ bh complete_matches + lazyPut bh top_env lazyPutMaybe bh docs get bh = do @@ -560,6 +564,7 @@ instance Binary ModIface where trust <- get bh trust_pkg <- get bh complete_matches <- get bh + top_env <- lazyGet bh docs <- lazyGetMaybe bh return (PrivateModIface { mi_module_ = mod, @@ -582,7 +587,6 @@ instance Binary ModIface where mi_decls_ = decls, mi_extra_decls_ = extra_decls, mi_foreign_ = foreign_, - mi_top_env_ = Nothing, mi_defaults_ = defaults, mi_insts_ = insts, mi_fam_insts_ = fam_insts, @@ -593,6 +597,7 @@ instance Binary ModIface where -- And build the cached values mi_complete_matches_ = complete_matches, mi_docs_ = docs, + mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read mi_final_exts_ = ModIfaceBackend { @@ -613,8 +618,6 @@ instance Binary ModIface where }}) --- | The original names declared of a certain module that are exported -type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod @@ -638,7 +641,7 @@ emptyPartialModIface mod mi_decls_ = [], mi_extra_decls_ = Nothing, mi_foreign_ = emptyIfaceForeign, - mi_top_env_ = Nothing, + mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , mi_hpc_ = False, mi_trust_ = noIfaceTrustInfo, mi_trust_pkg_ = False, @@ -810,15 +813,14 @@ addSourceFingerprint val iface = iface { mi_src_hash_ = val } -- | Copy fields that aren't serialised to disk to the new 'ModIface_'. -- This includes especially hashes that are usually stored in the interface --- file header and 'mi_top_env'. +-- file header. -- -- We need this function after calling 'shareIface', to make sure the -- 'ModIface_' doesn't lose any information. This function does not discard -- the in-memory byte array buffer 'mi_hi_bytes'. restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase restoreFromOldModIface old new = new - { mi_top_env_ = mi_top_env_ old - , mi_hsc_src_ = mi_hsc_src_ old + { mi_hsc_src_ = mi_hsc_src_ old , mi_src_hash_ = mi_src_hash_ old } @@ -879,7 +881,7 @@ set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } -set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase @@ -996,7 +998,7 @@ pattern ModIface :: [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> ModIface_ phase ===================================== testsuite/tests/ghci/should_run/Makefile ===================================== @@ -7,3 +7,9 @@ T3171: echo "do Control.Concurrent.threadDelay 3000000; putStrLn \"threadDelay was not interrupted\"" | \ "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) & \ sleep 2; kill -INT $$!; wait + +TopEnvIface: + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface + # Second compilation starts from interface files, but still can print "a" + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface + ===================================== testsuite/tests/ghci/should_run/TopEnvIface.hs ===================================== @@ -0,0 +1,4 @@ +module TopEnvIface where + +import TopEnvIface2 + ===================================== testsuite/tests/ghci/should_run/TopEnvIface.stdout ===================================== @@ -0,0 +1,8 @@ +[1 of 2] Compiling TopEnvIface2 ( TopEnvIface2.hs, interpreted ) +[2 of 2] Compiling TopEnvIface ( TopEnvIface.hs, interpreted ) +Ok, two modules loaded. +"I should be printed twice" +Leaving GHCi. +Ok, two modules loaded. +"I should be printed twice" +Leaving GHCi. ===================================== testsuite/tests/ghci/should_run/TopEnvIface2.hs ===================================== @@ -0,0 +1,3 @@ +module TopEnvIface2 where + +a = "I should be printed twice" ===================================== testsuite/tests/ghci/should_run/all.T ===================================== @@ -96,3 +96,4 @@ test('LargeBCO', [extra_files(['LargeBCO_A.hs']), req_interp, extra_hc_opts("-O test('T24115', just_ghci + [extra_run_opts("-e ':add T24115.hs'")], ghci_script, ['T24115.script']) test('T10920', [only_ways(ghci_ways), extra_files(['LocalPrelude/Prelude.hs'])], ghci_script, ['T10920.script']) +test('TopEnvIface', [only_ways(ghci_ways)], makefile_test, []) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c331eebf575221ed8c67ca232bac4ae047b794a3...73e0206819d9367a7a91a865adceee45ecbd54d6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c331eebf575221ed8c67ca232bac4ae047b794a3...73e0206819d9367a7a91a865adceee45ecbd54d6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/e4f40a41/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:15:04 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 09:15:04 -0500 Subject: [Git][ghc/ghc][master] hadrian: Refactor handling of test suite environment Message-ID: <67c70ae8a91a_a5f4878cd6411067b@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 1 changed file: - hadrian/src/Rules/Test.hs Changes: ===================================== hadrian/src/Rules/Test.hs ===================================== @@ -1,8 +1,6 @@ {-# OPTIONS_GHC -Wno-unused-top-binds #-} module Rules.Test (testRules) where -import System.Environment - import Base import CommandLine import Expression @@ -171,7 +169,6 @@ testRules = do root -/- timeoutPath %> \_ -> timeoutProgBuilder "test" ~> do - args <- userSetting defaultTestArgs let testCompilerArg = testCompiler args let stg = fromMaybe Stage2 $ stageOf testCompilerArg @@ -185,92 +182,98 @@ testRules = do let ok_to_build = filter (isOkToBuild args) extra_targets putVerbose $ " | ExtraTargets: " ++ intercalate ", " extra_targets putVerbose $ " | ExtraTargets (ok-to-build): " ++ intercalate ", " ok_to_build - need ok_to_build - - -- Prepare Ghc configuration file for input compiler. - need [root -/- timeoutPath] - - cross <- flag CrossCompiling - - -- get relative path for the given program in the given stage - let relative_path_stage s p = programPath =<< programContext s p - let make_absolute rel_path = do - abs_path <- liftIO (makeAbsolute rel_path) - fixAbsolutePathOnWindows abs_path - - rel_ghc_pkg <- relative_path_stage Stage1 ghcPkg - rel_hsc2hs <- relative_path_stage Stage1 hsc2hs - rel_hp2ps <- relative_path_stage Stage1 hp2ps - rel_haddock <- relative_path_stage (Stage0 InTreeLibs) haddock - rel_hpc <- relative_path_stage (Stage0 InTreeLibs) hpc - rel_runghc <- relative_path_stage (Stage0 InTreeLibs) runGhc + need $ ok_to_build ++ [root -/- timeoutPath] -- force stage0 program building for cross - when cross $ need [rel_hpc, rel_haddock, rel_runghc] - - prog_ghc_pkg <- make_absolute rel_ghc_pkg - prog_hsc2hs <- make_absolute rel_hsc2hs - prog_hp2ps <- make_absolute rel_hp2ps - prog_haddock <- make_absolute rel_haddock - prog_hpc <- make_absolute rel_hpc - prog_runghc <- make_absolute rel_runghc - - ghcPath <- getCompilerPath testCompilerArg - - makePath <- builderPath $ Make "" - top <- topDirectory - ghcFlags <- runTestGhcFlags - let ghciFlags = ghcFlags ++ unwords - [ "--interactive", "-v0", "-ignore-dot-ghci" - , "-fno-ghci-history", "-fprint-error-index-links=never" - ] - ccPath <- queryTargetTarget (Toolchain.prgPath . Toolchain.ccProgram . Toolchain.tgtCCompiler) - ccFlags <- queryTargetTarget (unwords . Toolchain.prgFlags . Toolchain.ccProgram . Toolchain.tgtCCompiler) - - pythonPath <- builderPath Python + cross <- flag CrossCompiling + when cross $ mapM (relativePathStage (Stage0 InTreeLibs)) [hpc, haddock, runGhc] >>= need -- Set environment variables for test's Makefile. - -- TODO: Ideally we would define all those env vars in 'env', so that - -- Shake can keep track of them, but it is not as easy as it seems - -- to get that to work. - liftIO $ do - -- Many of those env vars are used by Makefiles in the - -- test infrastructure, or from tests or their - -- Makefiles. - setEnv "MAKE" makePath - setEnv "PYTHON" pythonPath - setEnv "TEST_HC" ghcPath - setEnv "TEST_HC_OPTS" ghcFlags - setEnv "TEST_HC_OPTS_INTERACTIVE" ghciFlags - setEnv "TEST_CC" ccPath - setEnv "TEST_CC_OPTS" ccFlags - - when cross $ do - setEnv "GHC_PKG" prog_ghc_pkg - setEnv "HSC2HS" prog_hsc2hs - setEnv "HP2PS_ABS" prog_hp2ps - setEnv "HPC" prog_hpc - setEnv "HADDOCK" prog_haddock - setEnv "RUNGHC" prog_runghc - - setEnv "CHECK_PPR" (top -/- root -/- checkPprProgPath) - setEnv "CHECK_EXACT" (top -/- root -/- checkExactProgPath) - setEnv "DUMP_DECLS" (top -/- root -/- dumpDeclsProgPath) - setEnv "COUNT_DEPS" (top -/- root -/- countDepsProgPath) - setEnv "LINT_NOTES" (top -/- root -/- noteLinterProgPath) - setEnv "LINT_CODES" (top -/- root -/- codeLinterProgPath) - setEnv "LINT_WHITESPACE" (top -/- root -/- whitespaceLinterProgPath) - - -- This lets us bypass the need to generate a config - -- through Make, which happens in testsuite/mk/boilerplate.mk - -- which is in turn included by all test 'Makefile's. - setEnv "ghc_config_mk" (top -/- root -/- ghcConfigPath) - + env <- testEnv -- Execute the test target. -- We override the verbosity setting to make sure the user can see -- the test output: https://gitlab.haskell.org/ghc/ghc/issues/15951. - withVerbosity Diagnostic $ buildWithCmdOptions [] $ test_target RunTest + withVerbosity Diagnostic $ buildWithCmdOptions [AddEnv k v | (k,v) <- env] $ test_target RunTest + +testEnv :: Action [(String, String)] +testEnv = do + cross <- flag CrossCompiling + makePath <- builderPath $ Make "" + prog_ghc_pkg <- absolutePathStage Stage1 ghcPkg + prog_hsc2hs <- absolutePathStage Stage1 hsc2hs + prog_hp2ps <- absolutePathStage Stage1 hp2ps + prog_haddock <- absolutePathStage (Stage0 InTreeLibs) haddock + prog_hpc <- absolutePathStage (Stage0 InTreeLibs) hpc + prog_runghc <- absolutePathStage (Stage0 InTreeLibs) runGhc + + root <- buildRoot + args <- userSetting defaultTestArgs + let testCompilerArg = testCompiler args + ghcPath <- getCompilerPath testCompilerArg + + top <- topDirectory + pythonPath <- builderPath Python + ccPath <- queryTargetTarget (Toolchain.prgPath . Toolchain.ccProgram . Toolchain.tgtCCompiler) + ccFlags <- queryTargetTarget (unwords . Toolchain.prgFlags . Toolchain.ccProgram . Toolchain.tgtCCompiler) + ghcFlags <- runTestGhcFlags + let ghciFlags = ghcFlags ++ unwords + [ "--interactive", "-v0", "-ignore-dot-ghci" + , "-fno-ghci-history", "-fprint-error-index-links=never" + ] + + -- Many of those env vars are used by Makefiles in the + -- test infrastructure, or from tests or their + -- Makefiles. + return $ + [ "MAKE" .= makePath + , "PYTHON" .= pythonPath + , "TEST_HC" .= ghcPath + , "TEST_HC_OPTS" .= ghcFlags + , "TEST_HC_OPTS_INTERACTIVE" .= ghciFlags + , "TEST_CC" .= ccPath + , "TEST_CC_OPTS" .= ccFlags + , "CHECK_PPR" .= (top -/- root -/- checkPprProgPath) + , "CHECK_EXACT" .= (top -/- root -/- checkExactProgPath) + , "DUMP_DECLS" .= (top -/- root -/- dumpDeclsProgPath) + , "COUNT_DEPS" .= (top -/- root -/- countDepsProgPath) + , "LINT_NOTES" .= (top -/- root -/- noteLinterProgPath) + , "LINT_CODES" .= (top -/- root -/- codeLinterProgPath) + , "LINT_WHITESPACE" .= (top -/- root -/- whitespaceLinterProgPath) + -- This lets us bypass the need to generate a config + -- through Make, which happens in testsuite/mk/boilerplate.mk + -- which is in turn included by all test 'Makefile's. + , "ghc_config_mk" .= (top -/- root -/- ghcConfigPath) + ] ++ + if_ cross + [ "GHC_PKG" .= prog_ghc_pkg + , "HSC2HS" .= prog_hsc2hs + , "HP2PS_ABS" .= prog_hp2ps + , "HPC" .= prog_hpc + , "HADDOCK" .= prog_haddock + , "RUNGHC" .= prog_runghc + ] + where + if_ :: Bool -> [a] -> [a] + if_ True xs = xs + if_ False _ = [] + + (.=) = (,) + +needProgramStage :: Stage -> Package -> Action () +needProgramStage s p = relativePathStage s p >>= need . (:[]) + +-- | Get relative path for the given program in the given stage. +relativePathStage :: Stage -> Package -> Action FilePath +relativePathStage s p = programPath =<< programContext s p + +absolutePathStage :: Stage -> Package -> Action FilePath +absolutePathStage s p = + relativePathStage s p >>= make_absolute + where + make_absolute rel_path = do + abs_path <- liftIO (makeAbsolute rel_path) + fixAbsolutePathOnWindows abs_path -- | Given a test compiler and a hadrian dependency (target), check if we -- can build the target with the compiler View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0a99825d7ac0590db6c3f8867b33c40b2d1cc644 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0a99825d7ac0590db6c3f8867b33c40b2d1cc644 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/2e9a6dee/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:15:44 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 09:15:44 -0500 Subject: [Git][ghc/ghc][master] [EPA] Sync with the ghc-exactprint repo Message-ID: <67c70b105d317_a5f4810f81641108c7@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 4 changed files: - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs Changes: ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE BlockArguments #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} @@ -7,15 +8,14 @@ {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE StandaloneDeriving #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeSynonymInstances #-} -{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -{-# LANGUAGE BlockArguments #-} +{-# LANGUAGE TypeSynonymInstances #-} +{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE UndecidableInstances #-} -- For the (StmtLR GhcPs GhcPs (LocatedA (body GhcPs))) ExactPrint instance {-# OPTIONS_GHC -Wno-incomplete-uni-patterns -Wno-incomplete-record-updates #-} @@ -38,6 +38,7 @@ import GHC.Base (NonEmpty(..)) import GHC.Core.Coercion.Axiom (Role(..)) import qualified GHC.Data.BooleanFormula as BF import GHC.Data.FastString +import qualified GHC.Data.Strict as Strict import GHC.TypeLits import GHC.Types.Basic hiding (EP) import GHC.Types.Fixity @@ -106,16 +107,19 @@ runEP epReader action = do defaultEPState :: EPState defaultEPState = EPState - { epPos = (1,1) - , dLHS = 0 - , pMarkLayout = False - , pLHS = 0 - , dMarkLayout = False - , dPriorEndPosition = (1,1) - , uAnchorSpan = badRealSrcSpan + { uAnchorSpan = badRealSrcSpan , uExtraDP = Nothing , uExtraDPReturn = Nothing , pAcceptSpan = False + + , epPos = (1,1) + , pMarkLayout = False + , pLHS = LayoutStartCol 1 + + , dPriorEndPosition = (1,1) + , dMarkLayout = False + , dLHS = LayoutStartCol 1 + , epComments = [] , epCommentsApplied = [] , epEof = Nothing @@ -165,7 +169,7 @@ data EPState = EPState -- Annotation , uExtraDP :: !(Maybe EpaLocation) -- ^ Used to anchor a -- list - , uExtraDPReturn :: !(Maybe DeltaPos) + , uExtraDPReturn :: !(Maybe (SrcSpan, DeltaPos)) -- ^ Used to return Delta version of uExtraDP , pAcceptSpan :: Bool -- ^ When we have processed an -- entry of EpaDelta, accept the @@ -452,7 +456,6 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do -- delta phase variables ----------------------------------- -- Calculate offset required to get to the start of the SrcSPan !off <- getLayoutOffsetD - let spanStart = ss2pos curAnchor priorEndAfterComments <- getPriorEndD let edp' = adjustDeltaForOffset -- Use the propagated offset if one is set @@ -471,7 +474,7 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do Just (EpaDelta _ dp _) -> (dp, Nothing) -- Replace original with desired one. Allows all -- list entry values to be DP (1,0) - Just (EpaSpan (RealSrcSpan r _)) -> (dp, Just dp) + Just (EpaSpan ss@(RealSrcSpan r _)) -> (dp, Just (ss, dp)) where dp = adjustDeltaForOffset off (ss2delta priorEndAfterComments r) @@ -480,6 +483,7 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do when (isJust medr) $ setExtraDPReturn medr -- --------------------------------------------- -- Preparation complete, perform the action + let spanStart = ss2pos curAnchor when (priorEndAfterComments < spanStart) (do debugM $ "enterAnn.dPriorEndPosition:spanStart=" ++ show spanStart modify (\s -> s { dPriorEndPosition = spanStart } )) @@ -512,8 +516,8 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do Just (pos, prior) -> do let dp = if pos == prior then (DifferentLine 1 0) - else origDelta pos prior - debugM $ "EOF:(pos,posEnd,prior,dp) =" ++ showGhc (ss2pos pos, ss2posEnd pos, ss2pos prior, dp) + else adjustDeltaForOffset off (origDelta pos prior) + debugM $ "EOF:(pos,posend,prior,off,dp) =" ++ show (ss2pos pos, ss2posEnd pos, ss2pos prior, off, dp) printStringAtLsDelta dp "" setEofPos Nothing -- Only do this once @@ -542,12 +546,13 @@ enterAnn !(Entry anchor' trailing_anns cs flush canUpdateAnchor) a = do return after else return [] !trailing' <- markTrailing trailing_anns - -- mapM_ printOneComment (concatMap tokComment $ following) addCommentsA following -- Update original anchor, comments based on the printing process -- TODO:AZ: probably need to put something appropriate in instead of noSrcSpan - let newAnchor = EpaDelta noSrcSpan edp [] + let newAnchor = case anchor' of + EpaSpan s -> EpaDelta s edp [] + _ -> EpaDelta noSrcSpan edp [] let r = case canUpdateAnchor of CanUpdateAnchor -> setAnnotationAnchor a' newAnchor trailing' (mkEpaComments priorCs postCs) CanUpdateAnchorOnly -> setAnnotationAnchor a' newAnchor [] emptyComments @@ -695,7 +700,7 @@ printStringAtRsC capture pa str = do debugM $ "printStringAtRsC:p'=" ++ showAst p' debugM $ "printStringAtRsC: (EpaDelta p' [])=" ++ showAst (EpaDelta noSrcSpan p' NoComments) debugM $ "printStringAtRsC: (EpaDelta p' (map comment2LEpaComment cs'))=" ++ showAst (EpaDelta noSrcSpan p' (map comment2LEpaComment cs')) - return (EpaDelta noSrcSpan p' (map comment2LEpaComment cs')) + return (EpaDelta (RealSrcSpan pa Strict.Nothing) p' (map comment2LEpaComment cs')) printStringAtRs' :: (Monad m, Monoid w) => RealSrcSpan -> String -> EP w m () printStringAtRs' pa str = printStringAtRsC NoCaptureComments pa str >> return () @@ -1385,7 +1390,7 @@ printOneComment c@(Comment _str loc _r _mo) = do dp' <- case mep of Just (EpaDelta _ edp _) -> do debugM $ "printOneComment:edp=" ++ show edp - adjustDeltaForOffsetM edp + return edp _ -> return dp -- Start of debug printing LayoutStartCol dOff <- getLayoutOffsetD @@ -1398,28 +1403,10 @@ updateAndApplyComment :: (Monad m, Monoid w) => Comment -> DeltaPos -> EP w m () updateAndApplyComment (Comment str anc pp mo) dp = do applyComment (Comment str anc' pp mo) where - (r,c) = ss2posEnd pp - dp'' = case anc of - EpaDelta _ dp1 _ -> dp1 - EpaSpan (RealSrcSpan la _) -> - if r == 0 - then (ss2delta (r,c+0) la) - else (ss2delta (r,c) la) - EpaSpan (UnhelpfulSpan _) -> SameLine 0 - dp' = case anc of - EpaSpan (RealSrcSpan r1 _) -> - if pp == r1 - then dp - else dp'' - _ -> dp'' - op' = case dp' of - SameLine n -> if n >= 0 - then EpaDelta noSrcSpan dp' NoComments - else EpaDelta noSrcSpan dp NoComments - _ -> EpaDelta noSrcSpan dp' NoComments - anc' = if str == "" && op' == EpaDelta noSrcSpan (SameLine 0) NoComments -- EOF comment - then EpaDelta noSrcSpan dp NoComments - else EpaDelta noSrcSpan dp NoComments + ss = case anc of + EpaSpan ss' -> ss' + _ -> noSrcSpan + anc' = EpaDelta ss dp NoComments -- --------------------------------------------------------------------- @@ -1459,11 +1446,6 @@ commentAllocationIn ss = do markAnnotatedWithLayout :: (Monad m, Monoid w) => ExactPrint ast => ast -> EP w m ast markAnnotatedWithLayout a = setLayoutBoth $ markAnnotated a --- --------------------------------------------------------------------- - -markTopLevelList :: (Monad m, Monoid w) => ExactPrint ast => [ast] -> EP w m [ast] -markTopLevelList ls = mapM (\a -> setLayoutTopLevelP $ markAnnotated a) ls - -- --------------------------------------------------------------------- -- End of utility functions -- --------------------------------------------------------------------- @@ -1540,11 +1522,11 @@ instance ExactPrint (HsModule GhcPs) where an0 <- markLensTok an lam_mod m' <- markAnnotated m - mdeprec' <- setLayoutTopLevelP $ markAnnotated mdeprec + mdeprec' <- markAnnotated mdeprec - mexports' <- setLayoutTopLevelP $ markAnnotated mexports + mexports' <- markAnnotated mexports - an1 <- setLayoutTopLevelP $ markLensTok an0 lam_where + an1 <- markLensTok an0 lam_where return (an1, Just m', mdeprec', mexports') @@ -1595,8 +1577,8 @@ instance ExactPrint HsModuleImpDecls where setAnnotationAnchor mid _anc _ cs = mid { id_cs = priorComments cs ++ getFollowingComments cs } `debug` ("HsModuleImpDecls.setAnnotationAnchor:cs=" ++ showAst cs) exact (HsModuleImpDecls cs imports decls) = do - imports' <- markTopLevelList imports - decls' <- markTopLevelList (filter notDocDecl decls) + imports' <- mapM markAnnotated imports + decls' <- mapM markAnnotated (filter notDocDecl decls) return (HsModuleImpDecls cs imports' decls') @@ -2535,8 +2517,7 @@ instance ExactPrint (HsLocalBinds GhcPs) where setAnnotationAnchor a _ _ _ = a exact (HsValBinds an valbinds) = do - debugM $ "exact HsValBinds: an=" ++ showAst an - an0 <- markLensFun' an lal_rest markEpToken + an0 <- markLensFun' an lal_rest markEpToken -- 'where' case al_anchor $ anns an of Just anc -> do @@ -2548,9 +2529,9 @@ instance ExactPrint (HsLocalBinds GhcPs) where medr <- getExtraDPReturn an2 <- case medr of Nothing -> return an1 - Just dp -> do + Just (ss,dp) -> do setExtraDPReturn Nothing - return $ an1 { anns = (anns an1) { al_anchor = Just (EpaDelta noSrcSpan dp []) }} + return $ an1 { anns = (anns an1) { al_anchor = Just (EpaDelta ss dp []) }} return (HsValBinds an2 valbinds') exact (HsIPBinds an bs) = do @@ -4246,7 +4227,7 @@ printUnicode anc n = do -- TODO: unicode support? "forall" -> if spanLength (epaLocationRealSrcSpan anc) == 1 then "∀" else "forall" s -> s - loc <- printStringAtAAC NoCaptureComments (EpaDelta noSrcSpan (SameLine 0) []) str + loc <- printStringAtAAC NoCaptureComments (EpaDelta (getHasLoc anc) (SameLine 0) []) str case loc of EpaSpan _ -> return anc EpaDelta ss dp [] -> return $ EpaDelta ss dp [] @@ -4901,18 +4882,6 @@ setLayoutBoth k = do , pLHS = oldAnchorOffset} ) k <* reset --- Use 'local', designed for this -setLayoutTopLevelP :: (Monad m, Monoid w) => EP w m a -> EP w m a -setLayoutTopLevelP k = do - debugM $ "setLayoutTopLevelP entered" - oldAnchorOffset <- getLayoutOffsetP - modify (\a -> a { pMarkLayout = False - , pLHS = 0} ) - r <- k - debugM $ "setLayoutTopLevelP:resetting" - setLayoutOffsetP oldAnchorOffset - return r - ------------------------------------------------------------------------ getPosP :: (Monad m, Monoid w) => EP w m Pos @@ -4931,10 +4900,10 @@ setExtraDP md = do debugM $ "setExtraDP:" ++ show md modify (\s -> s {uExtraDP = md}) -getExtraDPReturn :: (Monad m, Monoid w) => EP w m (Maybe DeltaPos) +getExtraDPReturn :: (Monad m, Monoid w) => EP w m (Maybe (SrcSpan, DeltaPos)) getExtraDPReturn = gets uExtraDPReturn -setExtraDPReturn :: (Monad m, Monoid w) => Maybe DeltaPos -> EP w m () +setExtraDPReturn :: (Monad m, Monoid w) => Maybe (SrcSpan, DeltaPos) -> EP w m () setExtraDPReturn md = do debugM $ "setExtraDPReturn:" ++ show md modify (\s -> s {uExtraDPReturn = md}) ===================================== utils/check-exact/Main.hs ===================================== @@ -533,7 +533,7 @@ changeLocalDecls libdir (L l p) = do os' = setEntryDP os (DifferentLine 2 0) let sortKey = captureOrderBinds decls let (EpAnn anc (AnnList (Just _) a b c dd) cs) = van - let van' = (EpAnn anc (AnnList (Just (EpaDelta noSrcSpan (DifferentLine 1 5) [])) a b c dd) cs) + let van' = (EpAnn anc (AnnList (Just (EpaDelta noSrcSpan (DifferentLine 1 4) [])) a b c dd) cs) let binds' = (HsValBinds van' (ValBinds sortKey (decl':oldBinds) (sig':os':oldSigs))) @@ -557,8 +557,8 @@ changeLocalDecls2 libdir (L l p) = do replaceLocalBinds :: LMatch GhcPs (LHsExpr GhcPs) -> Transform (LMatch GhcPs (LHsExpr GhcPs)) replaceLocalBinds (L lm (Match ma mln pats (GRHSs _ rhs EmptyLocalBinds{}))) = do - let anc = (EpaDelta noSrcSpan (DifferentLine 1 3) []) - let anc2 = (EpaDelta noSrcSpan (DifferentLine 1 5) []) + let anc = (EpaDelta noSrcSpan (DifferentLine 1 2) []) + let anc2 = (EpaDelta noSrcSpan (DifferentLine 1 4) []) let an = EpAnn anc (AnnList (Just anc2) ListNone [] @@ -937,13 +937,13 @@ addClassMethod :: Changer addClassMethod libdir lp = do Right sig <- withDynFlags libdir (\df -> parseDecl df "sig" "nn :: Int") Right decl <- withDynFlags libdir (\df -> parseDecl df "decl" "nn = 2") - let decl' = setEntryDP decl (DifferentLine 1 3) - let sig' = setEntryDP sig (DifferentLine 2 3) + let decl' = setEntryDP decl (DifferentLine 1 2) + let sig' = setEntryDP sig (DifferentLine 2 2) let doAddMethod = do let [cd] = hsDecls lp (f1:f2s:f2d:_) = hsDecls cd - f2s' = setEntryDP f2s (DifferentLine 2 3) + f2s' = setEntryDP f2s (DifferentLine 2 2) cd' = replaceDecls cd [f1, sig', decl', f2s', f2d] lp' = replaceDecls lp [cd'] return lp' ===================================== utils/check-exact/Transform.hs ===================================== @@ -258,12 +258,15 @@ setEntryDP (L (EpAnn (EpaSpan ss) an (EpaComments [])) a) dp setEntryDP (L (EpAnn (EpaDelta ss d csd) an cs) a) dp = L (EpAnn (EpaDelta ss d' csd') an cs') a where + -- I suspect we should assume the comments are already in the + -- right place, and just set the entry DP for this case. This + -- avoids surprises from the caller. (d', csd', cs') = case cs of EpaComments (h:t) -> let (dp0,c') = go h in - (dp0, c':t++csd, EpaComments []) + (dp0, csd, EpaComments (c':t)) EpaComments [] -> (dp, csd, cs) EpaCommentsBalanced (h:t) ts -> @@ -299,7 +302,9 @@ setEntryDP (L (EpAnn (EpaSpan ss@(RealSrcSpan r _)) an cs) a) dp line = getDeltaLine delta col = deltaColumn delta edp' = if line == 0 then SameLine col - else DifferentLine line col + else DifferentLine line (col - 1) + -- At the top level the layout offset is 1, adjust for it + -- TODO: what about the layout offset for nested items? edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ epaLocationRealSrcSpan $ getLoc lc), r)) @@ -330,17 +335,23 @@ setEntryDPFromAnchor off (EpaSpan (RealSrcSpan anc _)) ll@(L la _) = setEntryDP -- --------------------------------------------------------------------- --- |Take the annEntryDelta associated with the first item and associate it with the second. --- Also transfer any comments occurring before it. +-- |Take the annEntryDelta associated with the first item and +-- associate it with the second. Also transfer any comments occurring +-- before it. transferEntryDP :: (Typeable t1, Typeable t2) => LocatedAn t1 a -> LocatedAn t2 b -> (LocatedAn t2 b) -transferEntryDP (L (EpAnn anc1 an1 cs1) _) (L (EpAnn _anc2 an2 cs2) b) = +transferEntryDP (L (EpAnn anc1 an1 cs1) _) (L (EpAnn anc2 an2 cs2) b) = + -- Note: the EpaDelta version of an EpaLocation contains the original + -- SrcSpan. We must preserve that. + let anc1' = case (anc1,anc2) of + (EpaDelta _ dp cs, EpaDelta ss2 _ _) -> EpaDelta ss2 dp cs + (_, _) -> anc1 -- Problem: if the original had preceding comments, blindly -- transferring the location is not correct - case priorComments cs1 of - [] -> (L (EpAnn anc1 (combine an1 an2) cs2) b) + in case priorComments cs1 of + [] -> (L (EpAnn anc1' (combine an1 an2) cs2) b) -- TODO: what happens if the receiving side already has comments? - (L _ _:_) -> (L (EpAnn anc1 (combine an1 an2) (cs1 <> cs2)) b) + (L _ _:_) -> (L (EpAnn anc1' (combine an1 an2) (cs1 <> cs2)) b) -- |If a and b are the same type return first arg, else return second @@ -519,7 +530,7 @@ balanceCommentsA la1 la2 = (la1', la2') anc2 = comments an2 (p1,m1,f1) = splitComments (anchorFromLocatedA la1) anc1 - cs1p = priorCommentsDeltas (anchorFromLocatedA la1) p1 + cs1p = priorCommentsDeltas (anchorFromLocatedA la1) p1 -- Split cs1 following comments into those before any -- TrailingAnn's on an1, and any after @@ -1103,8 +1114,8 @@ oldWhereAnnotation (EpAnn anc an cs) ww _oldSpan = an' newWhereAnnotation :: WithWhere -> (EpAnn (AnnList (EpToken "where"))) newWhereAnnotation ww = an where - anc = EpaDelta noSrcSpan (DifferentLine 1 3) [] - anc2 = EpaDelta noSrcSpan (DifferentLine 1 5) [] + anc = EpaDelta noSrcSpan (DifferentLine 1 2) [] + anc2 = EpaDelta noSrcSpan (DifferentLine 1 4) [] w = case ww of WithWhere -> EpTok (EpaDelta noSrcSpan (SameLine 0) []) WithoutWhere -> NoEpTok ===================================== utils/check-exact/Utils.hs ===================================== @@ -141,7 +141,7 @@ undelta (l,_) (DifferentLine dl dc) (LayoutStartCol co) = (fl,fc) -- --------------------------------------------------------------------- adjustDeltaForOffset :: LayoutStartCol -> DeltaPos -> DeltaPos -adjustDeltaForOffset _colOffset dp@(SameLine _) = dp +adjustDeltaForOffset _colOffset dp@(SameLine _) = dp adjustDeltaForOffset (LayoutStartCol colOffset) (DifferentLine l c) = DifferentLine l (c - colOffset) @@ -196,14 +196,17 @@ isPointSrcSpan ss = spanLength ss == 0 -- does not already have one. commentOrigDelta :: LEpaComment -> LEpaComment commentOrigDelta (L (EpaSpan ss@(RealSrcSpan la _)) (GHC.EpaComment t pp)) - = (L (EpaDelta ss dp NoComments) (GHC.EpaComment t pp)) - `debug` ("commentOrigDelta: (la, pp, r,c, dp)=" ++ showAst (la, pp, r,c, dp)) + = (L (EpaDelta ss dp' NoComments) (GHC.EpaComment t pp)) + `debug` ("commentOrigDelta: (la, pp, r,c, dp, dp')=" ++ showAst (la, pp, r,c, dp, dp')) where (r,c) = ss2posEnd pp dp = if r == 0 then (ss2delta (r,c+1) la) else (ss2delta (r,c) la) + dp' = case dp of + SameLine _ -> dp + DifferentLine l cc -> DifferentLine l (cc - 1) commentOrigDelta c = c origDelta :: RealSrcSpan -> RealSrcSpan -> DeltaPos View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7ca72844337a68423e651a4b5f11fe55fc24e302 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7ca72844337a68423e651a4b5f11fe55fc24e302 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/57f956b0/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:21:30 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 09:21:30 -0500 Subject: [Git][ghc/ghc][wip/fix-in-scope-simple-opt-expr] 15 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67c70c6a8312a_dd0c9fd8f4423af@gitlab.mail> Matthew Pickering pushed to branch wip/fix-in-scope-simple-opt-expr at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 35f6403c by Matthew Pickering at 2025-03-04T14:21:12+00:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 43 changed files: - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModIface.hs - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/src/Rules/Test.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/include/RtsAPI.h - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b7ab4fcf85cf04b286833d1de49dc37b4346f39a...35f6403c32f031cc297fb22503afccedfb683cd8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b7ab4fcf85cf04b286833d1de49dc37b4346f39a...35f6403c32f031cc297fb22503afccedfb683cd8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/73793b0f/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:27:48 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Tue, 04 Mar 2025 09:27:48 -0500 Subject: [Git][ghc/ghc][wip/wasm-prim-improve] 38 commits: LLVM: account for register type in funPrologue Message-ID: <67c70de49a5ec_dd0c92230e4507ee@gitlab.mail> Cheng Shao pushed to branch wip/wasm-prim-improve at Glasgow Haskell Compiler / GHC Commits: 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-â” |---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | â””-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 005f50fb by Cheng Shao at 2025-03-04T14:26:33+00:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4fbe7091 by Cheng Shao at 2025-03-04T14:26:33+00:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. - - - - - b9c27390 by Cheng Shao at 2025-03-04T14:26:33+00:00 ghc-experimental: add mkWeakJSVal - - - - - 197 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - distrib/configure.ac.in - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/wasm/JSFFI.c - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/doc/conf.py The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/91cf4fce96249a967cab1d709dc5a499c68da35f...b9c27390d828250dc836333ac8fd7ae57ff00861 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/91cf4fce96249a967cab1d709dc5a499c68da35f...b9c27390d828250dc836333ac8fd7ae57ff00861 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/5a01bd1e/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:38:22 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Tue, 04 Mar 2025 09:38:22 -0500 Subject: [Git][ghc/ghc][wip/wasm-prim-improve] 2 commits: wasm: make JSVal internal Weak# point to lifted JSVal Message-ID: <67c7105e8029_ea9f3c5c88868d6@gitlab.mail> Cheng Shao pushed to branch wip/wasm-prim-improve at Glasgow Haskell Compiler / GHC Commits: b232796c by Cheng Shao at 2025-03-04T14:35:55+00:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - c5fb34e2 by Cheng Shao at 2025-03-04T14:36:45+00:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 5 changed files: - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - testsuite/tests/jsffi/jsffigc.hs Changes: ===================================== libraries/ghc-experimental/src/GHC/Wasm/Prim.hs ===================================== @@ -4,6 +4,7 @@ module GHC.Wasm.Prim ( -- User-facing JSVal type and freeJSVal JSVal, freeJSVal, + mkWeakJSVal, -- The JSString type and conversion from/to Haskell String JSString (..), ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs ===================================== @@ -4,6 +4,7 @@ module GHC.Internal.Wasm.Prim ( -- User-facing JSVal type and freeJSVal JSVal (..), freeJSVal, + mkWeakJSVal, -- The JSString type and conversion from/to Haskell String JSString (..), ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -8,6 +8,7 @@ module GHC.Internal.Wasm.Prim.Types ( JSVal# (..), JSVal (..), freeJSVal, + mkWeakJSVal, JSString (..), fromJSString, toJSString, @@ -26,6 +27,7 @@ import GHC.Internal.IO.Encoding import GHC.Internal.Num import GHC.Internal.Show import GHC.Internal.Stable +import GHC.Internal.Weak {- @@ -82,7 +84,7 @@ newtype JSVal# = JSVal# (Any :: UnliftedType) data JSVal - = forall a . JSVal JSVal# (Weak# JSVal#) (StablePtr# a) + = forall a . JSVal JSVal# (Weak# JSVal) (StablePtr# a) freeJSVal :: JSVal -> IO () freeJSVal v@(JSVal _ w sp) = do @@ -94,6 +96,12 @@ freeJSVal v@(JSVal _ w sp) = do IO $ \s0 -> case finalizeWeak# w s0 of (# s1, _, _ #) -> (# s1, () #) +mkWeakJSVal :: JSVal -> Maybe (IO ()) -> IO (Weak JSVal) +mkWeakJSVal v@(JSVal k _ _) (Just (IO fin)) = IO $ \s0 -> + case mkWeak# k v fin s0 of + (# s1, w #) -> (# s1, Weak w #) +mkWeakJSVal (JSVal _ w _) Nothing = pure $ Weak w + foreign import javascript unsafe "if (!__ghc_wasm_jsffi_finalization_registry.unregister($1)) { throw new WebAssembly.RuntimeError('js_callback_unregister'); }" js_callback_unregister :: JSVal -> IO () ===================================== rts/wasm/JSFFI.c ===================================== @@ -107,7 +107,6 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { SET_HDR(w, &stg_WEAK_info, CCS_SYSTEM); w->cfinalizers = (StgClosure *)cfin; w->key = p; - w->value = Unit_closure; w->finalizer = &stg_NO_FINALIZER_closure; w->link = cap->weak_ptr_list_hd; cap->weak_ptr_list_hd = w; @@ -120,7 +119,9 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { box->payload[0] = p; box->payload[1] = (HaskellObj)w; box->payload[2] = NULL; - return TAG_CLOSURE(1, box); + + w->value = TAG_CLOSURE(1, box); + return w->value; } __attribute__((import_module("ghc_wasm_jsffi"), import_name("getJSVal"))) ===================================== testsuite/tests/jsffi/jsffigc.hs ===================================== @@ -4,7 +4,7 @@ module Test where import Data.Maybe import GHC.Exts -import GHC.Internal.Wasm.Prim +import GHC.Wasm.Prim import GHC.Weak import System.Mem @@ -22,13 +22,6 @@ foreign import javascript "wrapper" foreign export javascript "testDynExportFree sync" testDynExportFree :: Int -> Int -> Int -> IO () --- JSVal uses Weak# under the hood for garbage collection support, --- this exposes the internal Weak# to observe the liveliness of --- JSVal#. Do not use this in your own codebase since this is purely --- an implementation detail of JSVal and subject to change! -jsvalWeak :: JSVal -> Weak JSVal -jsvalWeak (JSVal _ w _) = Weak $ unsafeCoerce# Weak w - probeWeak :: Weak v -> IO () probeWeak wk = print =<< isJust <$> deRefWeak wk @@ -42,7 +35,7 @@ testDynExportFree x y z = do -- wk_js observe the liveliness of the JavaScript callback on the -- Haskell heap. Make sure it's eagerly evaluated and isn't a thunk -- that retains cb. - let !wk_js = jsvalWeak cb + !wk_js <- mkWeakJSVal cb Nothing print $ js_to_hs cb x y -- Eagerly drop references to both the JavaScript callback and the -- Haskell function closure. @@ -60,7 +53,7 @@ testDynExportGC x y z = do let fn a b = a * b + z wk_fn <- mkWeak fn () Nothing cb <- js_from_hs fn - let !wk_js = jsvalWeak cb + !wk_js <- mkWeakJSVal cb Nothing print $ js_to_hs cb x y -- Why performGC twice? The first run gathers some C finalizers -- which will be invoked in the second run to free the JSVal View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b9c27390d828250dc836333ac8fd7ae57ff00861...c5fb34e2cb46a5387b7f0766c4e845febd1a9917 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b9c27390d828250dc836333ac8fd7ae57ff00861...c5fb34e2cb46a5387b7f0766c4e845febd1a9917 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/d390234a/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:43:20 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 09:43:20 -0500 Subject: [Git][ghc/ghc][wip/t25571] 136 commits: warnings: Find out if a qualified name is in the interactive scope directly Message-ID: <67c71188622b3_ea9f3c5cc4899d9@gitlab.mail> Matthew Pickering pushed to branch wip/t25571 at Glasgow Haskell Compiler / GHC Commits: f56558be by Matthew Pickering at 2025-01-07T13:53:03-05:00 warnings: Find out if a qualified name is in the interactive scope directly There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600 - - - - - 84155cdb by Simon Peyton Jones at 2025-01-07T13:53:40-05:00 Tidy up kcConDecls Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types - - - - - 6c12b6cf by Bryan Richter at 2025-01-07T18:15:02-05:00 Remove tmp files after toolchain check Fixes #25620 - - - - - 42826a89 by Cheng Shao at 2025-01-07T18:15:39-05:00 xxhash: bump to v0.8.3 - - - - - 185f17e4 by sheaf at 2025-01-07T18:16:15-05:00 Fix typo in GHC.Tc.Solver.Solve.runTcPluginsWanted - - - - - 23099752 by Luite Stegeman at 2025-01-08T00:33:33+01:00 Add flags for switching off speculative evaluation. We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284 - - - - - 0161badc by Ben Gamari at 2025-01-09T17:30:05-05:00 rts/printClosure: Print IPE information for thunks and functions This makes it considerably easier to grok the structure of the heap when IPE information is available. - - - - - 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz GoÅ›linowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-â” |---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | â””-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 1f8dd609 by Matthew Pickering at 2025-03-03T16:44:38+00:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - d9c8ea1a by Matthew Pickering at 2025-03-03T16:44:38+00:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 5679675c by Matthew Pickering at 2025-03-04T13:35:59+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-self-recomp-info which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 9c0a9d5a by Matthew Pickering at 2025-03-04T13:35:59+00:00 Disable self recomp in release flavour - - - - - 950c58de by Matthew Pickering at 2025-03-04T14:40:52+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 1253 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Config/CoreToStg/Prep.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/cbits/genSym.c - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/diagnostics-as-json-schema-1_0.json - docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/expected-undocumented-flags.txt - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/phases.rst - docs/users_guide/using-optimisation.rst - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/bindist/Makefile - hadrian/cabal.project - hadrian/cfg/system.config.in - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Warnings.hs - libffi-tarballs - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/Data/Semigroup.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Exts.hs - libraries/base/src/System/Timeout.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-experimental/src/Data/Sum/Experimental.hs - libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/tests/stack_big_ret.hs - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - libraries/ghc-internal/src/GHC/Internal/Char.hs - libraries/ghc-prim/GHC/Classes.hs → libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - libraries/ghc-internal/src/GHC/Internal/Err.hs - libraries/ghc-internal/src/GHC/Internal/Event.hs - libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - libraries/ghc-internal/src/GHC/Internal/Generics.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Int.hs - libraries/ghc-internal/src/GHC/Internal/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - libraries/ghc-internal/src/GHC/Internal/Ix.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - libraries/ghc-internal/src/GHC/Internal/Maybe.hs - libraries/ghc-internal/src/GHC/Internal/Natural.hs - libraries/ghc-prim/GHC/Prim/Exception.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Read.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - libraries/ghc-internal/src/GHC/Internal/Records.hs - libraries/ghc-internal/src/GHC/Internal/Show.hs - libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - libraries/ghc-prim/GHC/Tuple.hs → libraries/ghc-internal/src/GHC/Internal/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - libraries/ghc-prim/GHC/Types.hs → libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Word.hs - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - linters/lint-codes/LintCodes/Static.hs - linters/lint-codes/Main.hs - m4/fp_settings.m4 - m4/ghc_toolchain.m4 - rts/Exception.cmm - rts/Interpreter.c - rts/Interpreter.h - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/RtsMain.c - rts/RtsSymbols.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStdThunks.cmm - rts/configure.ac - rts/external-symbols.list.in - rts/include/Stg.h - rts/include/stg/Prim.h - rts/js/environment.js - rts/js/mem.js - rts/js/verify.js - rts/linker/MachO.c - rts/rts.cabal - rts/wasm/scheduler.cmm - rts/win32/libHSghc-prim.def - rts/xxhash.h - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - testsuite/tests/bytecode/T24634/Makefile - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - testsuite/tests/codeGen/should_compile/T25166.stdout - testsuite/tests/codeGen/should_run/T23146/all.T - testsuite/tests/codeGen/should_run/T25364.hs - testsuite/tests/codeGen/should_run/T25364.stdout - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - + testsuite/tests/core-to-stg/T25284/A.hs - + testsuite/tests/core-to-stg/T25284/B.hs - + testsuite/tests/core-to-stg/T25284/Cls.hs - + testsuite/tests/core-to-stg/T25284/Main.hs - + testsuite/tests/core-to-stg/T25284/T25284.stdout - + testsuite/tests/core-to-stg/T25284/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail07.stderr - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/driver/T20604/T20604.stdout - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/recomp24656/recomp24656.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - testsuite/tests/ghc-e/should_fail/T23663.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T23686.stderr - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/T11361a.stderr - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs → testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/javascript/Makefile - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLet10.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19892.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/perf/compiler/T11068.stdout - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/all.T - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TTH_top_splice.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/T12686a.stderr - testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23740i.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T23153.stderr - testsuite/tests/rep-poly/T23154.stderr - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T1791/Makefile - testsuite/tests/rts/all.T - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/ipe/T24005/t24005.hs - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/Orphans.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - testsuite/tests/simd/should_run/all.T - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T21851_2.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23927.stdout - testsuite/tests/th/T24111.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - testsuite/tests/typecheck/should_compile/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.stderr - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_fail/T23734.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T23778.stderr - testsuite/tests/typecheck/should_fail/T24298.stderr - testsuite/tests/typecheck/should_fail/T24553.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T22510.stdout - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/T24396.stderr - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/Transform.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/Instances.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/941d84944a4a719540641fa0081b41b0220d32e1...950c58dec3ee75afba2545b10ba954ce485ffc48 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/941d84944a4a719540641fa0081b41b0220d32e1...950c58dec3ee75afba2545b10ba954ce485ffc48 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/590e025a/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 14:44:50 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 09:44:50 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: compiler: avoid overwriting existing writers in putWithTables Message-ID: <67c711e25a2da_ea9f3c5d009306@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - dd4622e1 by Matthew Pickering at 2025-03-04T09:44:43-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - 94f00834 by Teo Camarasu at 2025-03-04T09:44:43-05:00 template-haskell: remove Language.Haskell.TH.Lib.Internal This module is purely used for the implementation of TH quote desugarring. Historically this needed to be exposed from `template-haskell`, since that's the package that the desugarred expressions referenced but since https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12479, this is no longer the case. Now these identifiers are in `ghc-internal`. Note that this module has carried the following warning for a long time: > This is not a part of the public API, and as such, there are no API guarantees for this module from version to version. Resolves #24766 - - - - - 33 changed files: - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModIface.hs - hadrian/src/Rules/Test.hs - − libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/83c1e2eed937b2daaddb0803e14b6f44823e117a...94f008346075970901359d5fb713958ea4006ede -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/83c1e2eed937b2daaddb0803e14b6f44823e117a...94f008346075970901359d5fb713958ea4006ede You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/5de2e6bf/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 4 15:33:58 2025 From: gitlab at gitlab.haskell.org (Matthew Craven (@clyring)) Date: Tue, 04 Mar 2025 10:33:58 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T25771-tests Message-ID: <67c71d6695cb3_1127f218b424282cb@gitlab.mail> Matthew Craven pushed new branch wip/T25771-tests at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25771-tests You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/e6bdcc1a/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 16:08:15 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 04 Mar 2025 11:08:15 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T23675 Message-ID: <67c7256f288c6_12ca94c5da0706d@gitlab.mail> Ben Gamari pushed new branch wip/T23675 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T23675 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/3e0a144c/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 4 16:08:55 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 04 Mar 2025 11:08:55 -0500 Subject: [Git][ghc/ghc][wip/T23675] 2 commits: ghc-toolchain: Add support for otool, install-name-tool Message-ID: <67c725978791b_12ca94c5da085ef@gitlab.mail> Ben Gamari pushed to branch wip/T23675 at Glasgow Haskell Compiler / GHC Commits: 8580020a by Ben Gamari at 2025-03-04T11:08:41-05:00 ghc-toolchain: Add support for otool, install-name-tool Fixes part of ghc#23675. - - - - - 551d4623 by Ben Gamari at 2025-03-04T11:08:44-05:00 ghc-toolchain: Add support for llc, opt, llvm-as Fixes #23675. - - - - - 5 changed files: - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - m4/prep_target_file.m4 - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs Changes: ===================================== hadrian/cfg/default.host.target.in ===================================== @@ -39,4 +39,6 @@ Target , tgtNm = Nm {nmProgram = Program {prgPath = "", prgFlags = []}} , tgtMergeObjs = Just (MergeObjs {mergeObjsProgram = Program {prgPath = "@LD_STAGE0@", prgFlags = ["-r"]}, mergeObjsSupportsResponseFiles = False}) , tgtWindres = Nothing +, tgtOtool = Nothing +, tgtInstallNameTool = Nothing } ===================================== hadrian/cfg/default.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Just (Ranlib {ranlibProgram = Program {prgPath = "@RanlibCmd@", prgFlags = []}}) , tgtNm = Nm {nmProgram = Program {prgPath = "@NmCmd@", prgFlags = []}} , tgtMergeObjs = @MergeObjsCmdMaybe@ +, tgtLlc = @LlcCmdMaybeProg@ +, tgtOpt = @OptCmdMaybeProg@ +, tgtLlvmAs = @LlvmAsCmdMaybeProg@ , tgtWindres = @WindresCmdMaybeProg@ +, tgtOtool = @OtoolCmdMaybeProg@ +, tgtInstallNameTool = @InstallNameToolCmdMaybeProg@ } ===================================== m4/prep_target_file.m4 ===================================== @@ -148,7 +148,12 @@ AC_DEFUN([PREP_TARGET_FILE],[ PREP_LIST([JavaScriptCPPArgs]) PREP_LIST([CmmCPPArgs]) PREP_LIST([CmmCPPArgs_STAGE0]) + PREP_MAYBE_SIMPLE_PROGRAM([LlcCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OptCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([LlvmAsCmd]) PREP_MAYBE_SIMPLE_PROGRAM([WindresCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OtoolCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([InstallNameToolCmd]) PREP_MAYBE_STRING([TargetVendor_CPP]) PREP_MAYBE_STRING([HostVendor_CPP]) PREP_LIST([CONF_CPP_OPTS_STAGE2]) ===================================== utils/ghc-toolchain/exe/Main.hs ===================================== @@ -52,7 +52,11 @@ data Opts = Opts , optNm :: ProgOpt , optReadelf :: ProgOpt , optMergeObjs :: ProgOpt + , optLlc :: ProgOpt + , optOpt :: ProgOpt , optWindres :: ProgOpt + , optOtool :: ProgOpt + , optInstallNameTool :: ProgOpt -- Note we don't actually configure LD into anything but -- see #23857 and #22550 for the very unfortunate story. , optLd :: ProgOpt @@ -99,8 +103,12 @@ emptyOpts = Opts , optNm = po0 , optReadelf = po0 , optMergeObjs = po0 + , optLlc = po0 + , optOpt = po0 , optWindres = po0 , optLd = po0 + , optOtool = po0 + , optInstallNameTool = po0 , optUnregisterised = Nothing , optTablesNextToCode = Nothing , optUseLibFFIForAdjustors = Nothing @@ -112,7 +120,8 @@ emptyOpts = Opts po0 = emptyProgOpt _optCc, _optCxx, _optCpp, _optHsCpp, _optJsCpp, _optCmmCpp, _optCcLink, _optAr, - _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optWindres, _optLd + _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optLlc, _optOpt, + _optWindres, _optLd, _optOtool, _optInstallNameTool :: Lens Opts ProgOpt _optCc = Lens optCc (\x o -> o {optCc=x}) _optCxx = Lens optCxx (\x o -> o {optCxx=x}) @@ -126,8 +135,12 @@ _optRanlib = Lens optRanlib (\x o -> o {optRanlib=x}) _optNm = Lens optNm (\x o -> o {optNm=x}) _optReadelf = Lens optReadelf (\x o -> o {optReadelf=x}) _optMergeObjs = Lens optMergeObjs (\x o -> o {optMergeObjs=x}) +_optLlc = Lens optLlc (\x o -> o {optLlc=x}) +_optOpt = Lens optOpt (\x o -> o {optOpt=x}) _optWindres = Lens optWindres (\x o -> o {optWindres=x}) -_optLd = Lens optLd (\x o -> o {optLd= x}) +_optLd = Lens optLd (\x o -> o {optLd=x}) +_optOtool = Lens optOtool (\x o -> o {optOtool=x}) +_optInstallNameTool = Lens optInstallNameTool (\x o -> o {optInstallName=x}) _optTriple :: Lens Opts (Maybe String) _optTriple = Lens optTriple (\x o -> o {optTriple=x}) @@ -183,8 +196,12 @@ options = , progOpts "nm" "nm archiver" _optNm , progOpts "readelf" "readelf utility" _optReadelf , progOpts "merge-objs" "linker for merging objects" _optMergeObjs + , progOpts "llc" "LLVM llc utility" _optLlc + , progOpts "opt" "LLVM opt utility" _optOpt , progOpts "windres" "windres utility" _optWindres , progOpts "ld" "linker" _optLd + , progOpts "otool" "otool utility" _optOtool + , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool ] where progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)] @@ -434,6 +451,11 @@ mkTarget opts = do when (isNothing mergeObjs && not (arSupportsDashL ar)) $ throwE "Neither a object-merging tool (e.g. ld -r) nor an ar that supports -L is available" + -- LLVM toolchain + llc <- optional $ findProgram "llc" (optLlc opts) ["llc"] + opt <- optional $ findProgram "opt" (optOpt opts) ["opt"] + llvmAs <- optional $ findProgram "llvm assembler" (optLlvmAs opts) ["clang"] + -- Windows-specific utilities windres <- case archOS_OS archOs of @@ -442,6 +464,15 @@ mkTarget opts = do return (Just windres) _ -> return Nothing + -- Darwin-specific utilities + (otool, installNameTool) <- + case archOS_OS archOs of + OSDarwin -> do + otool <- findProgram "otool" (optOtool opts) ["otool"] + installNameTool <- findProgram "install-name-tool" (optInstallNameTool opts) ["install-name-tool"] + return (Just otool, Just installNameTool) + _ _> return (Nothing, Nothing) + -- various other properties of the platform tgtWordSize <- checkWordSize cc tgtEndianness <- checkEndianness cc @@ -478,7 +509,11 @@ mkTarget opts = do , tgtRanlib = ranlib , tgtNm = nm , tgtMergeObjs = mergeObjs + , tgtLlc = llc + , tgtOpt = opt , tgtWindres = windres + , tgtOtool = otool + , tgtInstallNameTool = installNameTool , tgtWordSize , tgtEndianness , tgtUnregisterised ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Target.hs ===================================== @@ -72,8 +72,18 @@ data Target = Target , tgtMergeObjs :: Maybe MergeObjs -- ^ We don't need a merge objects tool if we @Ar@ supports @-L@ + -- LLVM backend toolchain + , tgtLlc :: Program + , tgtOpt :: Program + , tgtLlvmAs :: Program + -- ^ assembler used to assemble LLVM backend output; typically @clang@ + -- Windows-specific tools , tgtWindres :: Maybe Program + + -- Darwin-specific tools + , tgtOtool :: Maybe Program + , tgtInstallNameTool :: Maybe Program } deriving (Read, Eq, Ord) @@ -121,6 +131,11 @@ instance Show Target where , ", tgtRanlib = " ++ show tgtRanlib , ", tgtNm = " ++ show tgtNm , ", tgtMergeObjs = " ++ show tgtMergeObjs + , ", tgtLlc = " ++ show tgtLlc + , ", tgtOpt = " ++ show tgtOpt + , ", tgtLlvmAs = " ++ show tgtLlvmAs , ", tgtWindres = " ++ show tgtWindres + , ", tgtOtool = " ++ show tgtOtool + , ", tgtInstallNameTool = " ++ show tgtInstallNameTool , "}" ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/209bc8bc8e681e2a96a29cfc463fc4a3f5e79437...551d46231483a324a663c64e3c627b41290eab49 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/209bc8bc8e681e2a96a29cfc463fc4a3f5e79437...551d46231483a324a663c64e3c627b41290eab49 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/b1fb0d34/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 16:26:53 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 04 Mar 2025 11:26:53 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/25799 Message-ID: <67c729cdc5917_12ca9454b7f8201a2@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/25799 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/25799 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/a7017b3c/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 4 17:40:10 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 12:40:10 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/compress-iface Message-ID: <67c73afa2bd32_14f02d450a8859150@gitlab.mail> Matthew Pickering pushed new branch wip/compress-iface at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/compress-iface You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/c33deaa6/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 4 17:55:37 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 12:55:37 -0500 Subject: [Git][ghc/ghc][wip/22188] 16 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67c73e99939be_14f02d5bff406545a@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - e3eaf6c1 by Matthew Pickering at 2025-03-04T17:55:01+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-self-recomp-info which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - ffafd83d by Matthew Pickering at 2025-03-04T17:55:02+00:00 Disable self recomp in release flavour - - - - - 64 changed files: - compiler/GHC.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/src/Flavour.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/include/RtsAPI.h - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9c0a9d5a8e8891009293ccf594233d1cad0b3434...ffafd83d12a220a8a0a7a1ea52abe6d4d0aaeee3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9c0a9d5a8e8891009293ccf594233d1cad0b3434...ffafd83d12a220a8a0a7a1ea52abe6d4d0aaeee3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/d29d5b80/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 18:50:12 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 04 Mar 2025 13:50:12 -0500 Subject: [Git][ghc/ghc][wip/T23675] 2 commits: ghc-toolchain: Add support for otool, install-name-tool Message-ID: <67c74b64e38c6_17b19a4f10782301f@gitlab.mail> Ben Gamari pushed to branch wip/T23675 at Glasgow Haskell Compiler / GHC Commits: 567e2ae9 by Ben Gamari at 2025-03-04T13:50:01-05:00 ghc-toolchain: Add support for otool, install-name-tool Fixes part of ghc#23675. - - - - - 162094c9 by Ben Gamari at 2025-03-04T13:50:01-05:00 ghc-toolchain: Add support for llc, opt, llvm-as Fixes #23675. - - - - - 5 changed files: - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - m4/prep_target_file.m4 - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs Changes: ===================================== hadrian/cfg/default.host.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Nothing , tgtNm = Nm {nmProgram = Program {prgPath = "", prgFlags = []}} , tgtMergeObjs = Just (MergeObjs {mergeObjsProgram = Program {prgPath = "@LD_STAGE0@", prgFlags = ["-r"]}, mergeObjsSupportsResponseFiles = False}) +, tgtLlc = Nothing +, tgtOpt = Nothing +, tgtLlvmAs = Nothing , tgtWindres = Nothing +, tgtOtool = Nothing +, tgtInstallNameTool = Nothing } ===================================== hadrian/cfg/default.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Just (Ranlib {ranlibProgram = Program {prgPath = "@RanlibCmd@", prgFlags = []}}) , tgtNm = Nm {nmProgram = Program {prgPath = "@NmCmd@", prgFlags = []}} , tgtMergeObjs = @MergeObjsCmdMaybe@ +, tgtLlc = @LlcCmdMaybeProg@ +, tgtOpt = @OptCmdMaybeProg@ +, tgtLlvmAs = @LlvmAsCmdMaybeProg@ , tgtWindres = @WindresCmdMaybeProg@ +, tgtOtool = @OtoolCmdMaybeProg@ +, tgtInstallNameTool = @InstallNameToolCmdMaybeProg@ } ===================================== m4/prep_target_file.m4 ===================================== @@ -10,6 +10,38 @@ # This toolchain will additionally be used to validate the one generated by # ghc-toolchain. See Note [ghc-toolchain consistency checking]. +# PREP_LIST +# ============ +# +# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a +# space-separated list of args +# i.e. +# "arg1 arg2 arg3" +# ==> +# ["arg1","arg2","arg3"] +# +# $1 = list variable to substitute +dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'. +AC_DEFUN([PREP_LIST],[ + # shell array + set -- $$1 + $1List="@<:@" + if test "[$]#" -eq 0; then + # no arguments + true + else + $1List="${$1List}\"[$]1\"" + shift # drop first elem + for arg in "[$]@" + do + $1List="${$1List},\"$arg\"" + done + fi + $1List="${$1List}@:>@" + + AC_SUBST([$1List]) +]) + # PREP_MAYBE_SIMPLE_PROGRAM # ========================= # @@ -27,6 +59,25 @@ AC_DEFUN([PREP_MAYBE_SIMPLE_PROGRAM],[ AC_SUBST([$1MaybeProg]) ]) +# PREP_MAYBE_PROGRAM +# ========================= +# +# Issue a substitution of [$1MaybeProg] with +# * Nothing, if $1 is empty +# * Just (Program {prgPath = "$$1", prgFlags = [elements of $$2]}), otherwise +# +# $1 = optional program path +# $2 = program arguments +AC_DEFUN([PREP_MAYBE_SIMPLE_PROGRAM],[ + if test -z "$$1"; then + $1MaybeProg=Nothing + else + PREP_LIST($$2) + $1MaybeProg="Just (Program {prgPath = \"$$1\", prgFlags = $$2List})" + fi + AC_SUBST([$1MaybeProg]) +]) + # PREP_MAYBE_STRING # ========================= # @@ -86,38 +137,6 @@ AC_DEFUN([PREP_NOT_BOOLEAN],[ AC_SUBST([Not$1Bool]) ]) -# PREP_LIST -# ============ -# -# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a -# space-separated list of args -# i.e. -# "arg1 arg2 arg3" -# ==> -# ["arg1","arg2","arg3"] -# -# $1 = list variable to substitute -dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'. -AC_DEFUN([PREP_LIST],[ - # shell array - set -- $$1 - $1List="@<:@" - if test "[$]#" -eq 0; then - # no arguments - true - else - $1List="${$1List}\"[$]1\"" - shift # drop first elem - for arg in "[$]@" - do - $1List="${$1List},\"$arg\"" - done - fi - $1List="${$1List}@:>@" - - AC_SUBST([$1List]) -]) - # Eventually: PREP_BUILD_TARGET_FILE, PREP_HOST_TARGET_FILE, PREP_TARGET_TARGET_FILE # Prepares required substitutions to generate the target file AC_DEFUN([PREP_TARGET_FILE],[ @@ -148,7 +167,12 @@ AC_DEFUN([PREP_TARGET_FILE],[ PREP_LIST([JavaScriptCPPArgs]) PREP_LIST([CmmCPPArgs]) PREP_LIST([CmmCPPArgs_STAGE0]) + PREP_MAYBE_SIMPLE_PROGRAM([LlcCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OptCmd]) + PREP_MAYBE_PROGRAM([LlvmAsCmd], [LlvmAsFlags]) PREP_MAYBE_SIMPLE_PROGRAM([WindresCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OtoolCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([InstallNameToolCmd]) PREP_MAYBE_STRING([TargetVendor_CPP]) PREP_MAYBE_STRING([HostVendor_CPP]) PREP_LIST([CONF_CPP_OPTS_STAGE2]) ===================================== utils/ghc-toolchain/exe/Main.hs ===================================== @@ -52,7 +52,11 @@ data Opts = Opts , optNm :: ProgOpt , optReadelf :: ProgOpt , optMergeObjs :: ProgOpt + , optLlc :: ProgOpt + , optOpt :: ProgOpt , optWindres :: ProgOpt + , optOtool :: ProgOpt + , optInstallNameTool :: ProgOpt -- Note we don't actually configure LD into anything but -- see #23857 and #22550 for the very unfortunate story. , optLd :: ProgOpt @@ -99,8 +103,12 @@ emptyOpts = Opts , optNm = po0 , optReadelf = po0 , optMergeObjs = po0 + , optLlc = po0 + , optOpt = po0 , optWindres = po0 , optLd = po0 + , optOtool = po0 + , optInstallNameTool = po0 , optUnregisterised = Nothing , optTablesNextToCode = Nothing , optUseLibFFIForAdjustors = Nothing @@ -112,7 +120,8 @@ emptyOpts = Opts po0 = emptyProgOpt _optCc, _optCxx, _optCpp, _optHsCpp, _optJsCpp, _optCmmCpp, _optCcLink, _optAr, - _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optWindres, _optLd + _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optLlc, _optOpt, + _optWindres, _optLd, _optOtool, _optInstallNameTool :: Lens Opts ProgOpt _optCc = Lens optCc (\x o -> o {optCc=x}) _optCxx = Lens optCxx (\x o -> o {optCxx=x}) @@ -126,8 +135,12 @@ _optRanlib = Lens optRanlib (\x o -> o {optRanlib=x}) _optNm = Lens optNm (\x o -> o {optNm=x}) _optReadelf = Lens optReadelf (\x o -> o {optReadelf=x}) _optMergeObjs = Lens optMergeObjs (\x o -> o {optMergeObjs=x}) +_optLlc = Lens optLlc (\x o -> o {optLlc=x}) +_optOpt = Lens optOpt (\x o -> o {optOpt=x}) _optWindres = Lens optWindres (\x o -> o {optWindres=x}) -_optLd = Lens optLd (\x o -> o {optLd= x}) +_optLd = Lens optLd (\x o -> o {optLd=x}) +_optOtool = Lens optOtool (\x o -> o {optOtool=x}) +_optInstallNameTool = Lens optInstallNameTool (\x o -> o {optInstallName=x}) _optTriple :: Lens Opts (Maybe String) _optTriple = Lens optTriple (\x o -> o {optTriple=x}) @@ -183,8 +196,12 @@ options = , progOpts "nm" "nm archiver" _optNm , progOpts "readelf" "readelf utility" _optReadelf , progOpts "merge-objs" "linker for merging objects" _optMergeObjs + , progOpts "llc" "LLVM llc utility" _optLlc + , progOpts "opt" "LLVM opt utility" _optOpt , progOpts "windres" "windres utility" _optWindres , progOpts "ld" "linker" _optLd + , progOpts "otool" "otool utility" _optOtool + , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool ] where progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)] @@ -434,6 +451,11 @@ mkTarget opts = do when (isNothing mergeObjs && not (arSupportsDashL ar)) $ throwE "Neither a object-merging tool (e.g. ld -r) nor an ar that supports -L is available" + -- LLVM toolchain + llc <- optional $ findProgram "llc" (optLlc opts) ["llc"] + opt <- optional $ findProgram "opt" (optOpt opts) ["opt"] + llvmAs <- optional $ findProgram "llvm assembler" (optLlvmAs opts) ["clang"] + -- Windows-specific utilities windres <- case archOS_OS archOs of @@ -442,6 +464,15 @@ mkTarget opts = do return (Just windres) _ -> return Nothing + -- Darwin-specific utilities + (otool, installNameTool) <- + case archOS_OS archOs of + OSDarwin -> do + otool <- findProgram "otool" (optOtool opts) ["otool"] + installNameTool <- findProgram "install-name-tool" (optInstallNameTool opts) ["install-name-tool"] + return (Just otool, Just installNameTool) + _ -> return (Nothing, Nothing) + -- various other properties of the platform tgtWordSize <- checkWordSize cc tgtEndianness <- checkEndianness cc @@ -478,7 +509,11 @@ mkTarget opts = do , tgtRanlib = ranlib , tgtNm = nm , tgtMergeObjs = mergeObjs + , tgtLlc = llc + , tgtOpt = opt , tgtWindres = windres + , tgtOtool = otool + , tgtInstallNameTool = installNameTool , tgtWordSize , tgtEndianness , tgtUnregisterised ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Target.hs ===================================== @@ -72,8 +72,18 @@ data Target = Target , tgtMergeObjs :: Maybe MergeObjs -- ^ We don't need a merge objects tool if we @Ar@ supports @-L@ + -- LLVM backend toolchain + , tgtLlc :: Program + , tgtOpt :: Program + , tgtLlvmAs :: Program + -- ^ assembler used to assemble LLVM backend output; typically @clang@ + -- Windows-specific tools , tgtWindres :: Maybe Program + + -- Darwin-specific tools + , tgtOtool :: Maybe Program + , tgtInstallNameTool :: Maybe Program } deriving (Read, Eq, Ord) @@ -121,6 +131,11 @@ instance Show Target where , ", tgtRanlib = " ++ show tgtRanlib , ", tgtNm = " ++ show tgtNm , ", tgtMergeObjs = " ++ show tgtMergeObjs + , ", tgtLlc = " ++ show tgtLlc + , ", tgtOpt = " ++ show tgtOpt + , ", tgtLlvmAs = " ++ show tgtLlvmAs , ", tgtWindres = " ++ show tgtWindres + , ", tgtOtool = " ++ show tgtOtool + , ", tgtInstallNameTool = " ++ show tgtInstallNameTool , "}" ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/551d46231483a324a663c64e3c627b41290eab49...162094c9790a5c1b6154a118bae8b765b83f79a3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/551d46231483a324a663c64e3c627b41290eab49...162094c9790a5c1b6154a118bae8b765b83f79a3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/f7365019/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 19:37:08 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 04 Mar 2025 14:37:08 -0500 Subject: [Git][ghc/ghc][wip/T25647] 2 commits: move [FamArgFlavour] to tyCon Message-ID: <67c756646deed_17b19ab6c8a825470@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 90e97f12 by Patrick at 2025-03-04T23:42:18+08:00 move [FamArgFlavour] to tyCon - - - - - dbe81ead by Patrick at 2025-03-05T03:36:49+08:00 add note - - - - - 5 changed files: - compiler/GHC/Core/TyCon.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -17,6 +17,7 @@ module GHC.Core.TyCon( AlgTyConFlav(..), isNoParent, FamTyConFlav(..), Role(..), Injectivity(..), PromDataConInfo(..), TyConFlavour(..), + FamArgFlavour(..), -- * TyConBinder TyConBinder, TyConBndrVis(..), @@ -109,6 +110,7 @@ module GHC.Core.TyCon( tcTyConScopedTyVars, isMonoTcTyCon, tyConHasClosedResKind, mkTyConTagMap, + tyConFamArgFlavours, -- ** Manipulating TyCons ExpandSynResult(..), @@ -740,6 +742,7 @@ instance Binary TyConBndrVis where -} + -- | TyCons represent type constructors. Type constructors are introduced by -- things such as: -- @@ -881,7 +884,7 @@ data TyConDetails = -- abstract, built-in. See comments for -- FamTyConFlav - famTcParent :: Maybe TyCon, -- ^ For *associated* type/data families + famTcParent :: Maybe (TyCon, [FamArgFlavour]), -- ^ For *associated* type/data families -- The class tycon in which the family is declared -- See Note [Associated families and their parent class] @@ -1948,8 +1951,17 @@ mkFamilyTyCon name binders res_kind resVar flav parent inj = mkTyCon name binders res_kind (constRoles binders Nominal) $ FamilyTyCon { famTcResVar = resVar , famTcFlav = flav - , famTcParent = classTyCon <$> parent + , famTcParent = genfamTcParent <$> parent , famTcInj = inj } + where + genfamTcParent cls = (classTyCon cls, argFlavours) + where clsArgs = classTyVars cls + argFlavours = [if b `elem` clsArgs then ClassArg else FreeArg | b <- binderVars binders] + +tyConFamArgFlavours :: TyCon -> [FamArgFlavour] +tyConFamArgFlavours (TyCon { tyConDetails = details }) + | FamilyTyCon { famTcParent = Just (_, argFlavours) } <- details = argFlavours + | otherwise = [] -- | Create a promoted data constructor 'TyCon' -- Somewhat dodgily, we give it the same Name @@ -2846,8 +2858,8 @@ tyConFlavour (TyCon { tyConDetails = details }) | FamilyTyCon { famTcFlav = flav, famTcParent = parent } <- details = case flav of - DataFamilyTyCon{} -> OpenFamilyFlavour (IAmData DataType) parent - OpenSynFamilyTyCon -> OpenFamilyFlavour IAmType parent + DataFamilyTyCon{} -> OpenFamilyFlavour (IAmData DataType) (fst <$> parent) + OpenSynFamilyTyCon -> OpenFamilyFlavour IAmType (fst <$> parent) ClosedSynFamilyTyCon{} -> ClosedTypeFamilyFlavour AbstractClosedSynFamilyTyCon -> ClosedTypeFamilyFlavour BuiltInSynFamTyCon{} -> ClosedTypeFamilyFlavour @@ -2965,3 +2977,55 @@ tyConSkolem = isHoleName . tyConName -- -- This is why the test is on the original name of the TyCon, -- not whether it is abstract or not. + + + +{- Note [FamArgFlavour and family instance decl type checking] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The FamArgFlavour is used to distinguish the different kinds of arguments that may +appear in an associated type family declaration/instance. In an associated type family, +some arguments come directly from the parent class (the “class argumentsâ€) while +others are provided freely by the user (the “free argumentsâ€). For example, consider: + + class C a b c where + type F x y a -- Here, 'x' and 'y' are free arguments, while 'a' comes from the class. + type G p c b -- Here, 'p' is free and both 'c' and 'b' are class arguments. + +We can conceptually view the kinds of arguments for a type family as a famArgFlavour–vector, +with one flavour per argument of the family. Each flavour indicates whether the corresponding +argument is a ClassArg or a FreeArg. We also introduce a third flavour, SigArg, +to flag arguments that appear only in a kind signature for a type instance (i.e. when +a wildcard is provided along with a kind annotation, as in @(_ :: _)@). + +Under the current design, when type-checking an instance the interpretation of wildcards +depends on their position: + + - In free arguments, a wildcard is interpreted as a TyVarTv-variable type variable. + - In class arguments, a wildcard is interpreted as a Tau–variable. + - In signature arguments, a wildcard is similarly treated as a Tau–variable. + +For instance, for an instance declaration like + + instance C Int [x] Bool where + type F _ _ (_ :: _) = Int + +the first two underscores (free arguments) would yield TyVarTv’s while the last two underscores (a class +argument and a signature argument) would produce TauTv's. + +This design provides flexibility in handling wildcards in type families. + +Side note: +we maintain diffirent flavours between class arguments and signature arguments because +we might want to be able to flip only the class arguments to use TyVarTv without affecting +the signature arguments. + +For more discussion, see #13908. +-} + +-- see Note [FamArgFlavour and family instance decl type checking] +data FamArgFlavour = ClassArg | FreeArg | SigArg deriving (Eq, Show) + +instance Outputable FamArgFlavour where + ppr ClassArg = text "ClassArg" + ppr FreeArg = text "FreeArg" + ppr SigArg = text "SigArg" ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -142,8 +142,6 @@ import Data.List ( mapAccumL ) import Control.Monad import Data.Tuple( swap ) import GHC.Types.SourceText -import GHC.Tc.Instance.Class (AssocInstInfo (..), FamArgType (..), - buildPatsArgTypes, buildPatsModeTypes) {- ---------------------------- @@ -781,20 +779,22 @@ There is also the possibility of mentioning a wildcard tcFamTyPats :: TyCon -> HsFamEqnPats GhcRn -- Patterns - -> AssocInstInfo -- Associated instance info -> TcM (TcType, TcKind) -- (lhs_type, lhs_kind) -- Check the LHS of a type/data family instance -- e.g. type instance F ty1 .. tyn = ... -- Used for both type and data families -tcFamTyPats fam_tc hs_pats mb_clsinfo +tcFamTyPats fam_tc hs_pats = do { traceTc "tcFamTyPats {" $ - vcat [ ppr fam_tc, text "arity:" <+> ppr fam_arity, text "pats:" <+> ppr hs_pats ] + vcat [ ppr fam_tc, + text "arity:" <+> ppr fam_arity, + text "pats:" <+> ppr hs_pats + ] ; mode <- mkHoleMode TypeLevel (HM_FamPat FreeArg) -- HM_FamPat: See Note [Wildcards in family instances] in -- GHC.Rename.Module ; let fun_ty = mkTyConApp fam_tc [] - ; (fam_app, res_kind) <- tcInferTyApps mode lhs_fun fun_ty (buildPatsArgTypes mb_clsinfo hs_pats) + ; (fam_app, res_kind) <- tcInferTyApps mode lhs_fun fun_ty hs_pats (tyConFamArgFlavours fam_tc ++ cycle [FreeArg]) -- Hack alert: see Note [tcFamTyPats: zonking the result kind] ; res_kind <- liftZonkM $ zonkTcType res_kind @@ -888,14 +888,14 @@ tcInferLHsTypeUnsaturated hs_ty ; case splitHsAppTys_maybe (unLoc hs_ty) of Just (hs_fun_ty, hs_args) -> do { (fun_ty, _ki) <- tcInferTyAppHead mode hs_fun_ty - ; tcInferTyApps_nosat mode hs_fun_ty fun_ty (buildPatsModeTypes (tcTyModeFamArgType mode) hs_args) } + ; tcInferTyApps_nosat mode hs_fun_ty fun_ty hs_args (cycle [FreeArg])} -- Notice the 'nosat'; do not instantiate trailing -- invisible arguments of a type family. -- See Note [Dealing with :kind] Nothing -> tc_infer_lhs_type mode hs_ty } -tcTyModeFamArgType :: TcTyMode -> FamArgType -tcTyModeFamArgType (TcTyMode { mode_holes = mh }) +tcTyModeFamArgFlavour :: TcTyMode -> FamArgFlavour +tcTyModeFamArgFlavour (TcTyMode { mode_holes = mh }) = case mh of Just (_, HM_FamPat artType) -> artType _ -> FreeArg @@ -976,7 +976,7 @@ type HoleInfo = Maybe (TcLevel, HoleMode) -- HoleMode says how to treat the occurrences -- of anonymous wildcards; see tcAnonWildCardOcc data HoleMode = HM_Sig -- Partial type signatures: f :: _ -> Int - | HM_FamPat FamArgType -- Family instances: F _ Int = Bool + | HM_FamPat FamArgFlavour -- Family instances: F _ Int = Bool | HM_VTA -- Visible type and kind application: -- f @(Maybe _) -- Maybe @(_ -> _) @@ -998,8 +998,8 @@ mkHoleMode tyki hm ; return (TcTyMode { mode_tyki = tyki , mode_holes = Just (lvl,hm) }) } -updateFamArgType :: FamArgType -> TcTyMode -> TcTyMode -updateFamArgType fam_arg m at TcTyMode { mode_tyki = tyki, mode_holes = mh } +updateFamArgFlavour :: FamArgFlavour -> TcTyMode -> TcTyMode +updateFamArgFlavour fam_arg m at TcTyMode { mode_tyki = tyki, mode_holes = mh } |Just (lvl, HM_FamPat _) <- mh = (TcTyMode { mode_tyki = tyki , mode_holes = Just (lvl,HM_FamPat fam_arg) }) @@ -1285,7 +1285,7 @@ tcHsType mode rn_ty@(HsAppKindTy{}) exp_kind = tc_app_ty mode rn_ty exp_kind tcHsType mode rn_ty@(HsOpTy{}) exp_kind = tc_app_ty mode rn_ty exp_kind tcHsType mode rn_ty@(HsKindSig _ ty sig) exp_kind - = do { let mode' = (updateFamArgType SigArg $ mode { mode_tyki = KindLevel}) + = do { let mode' = (updateFamArgFlavour SigArg $ mode { mode_tyki = KindLevel}) ; sig' <- tc_lhs_kind_sig mode' KindSigCtxt sig -- We must typecheck the kind signature, and solve all -- its equalities etc; from this point on we may do @@ -1555,7 +1555,7 @@ tc_app_ty :: TcTyMode -> HsType GhcRn -> ExpKind -> TcM TcType tc_app_ty mode rn_ty exp_kind = do { (fun_ty, _ki) <- tcInferTyAppHead mode hs_fun_ty ; (ty, infered_kind) <- tcInferTyApps mode hs_fun_ty fun_ty - (buildPatsModeTypes (tcTyModeFamArgType mode) hs_args) + hs_args (cycle [FreeArg]) ; checkExpKind rn_ty ty infered_kind exp_kind } where (hs_fun_ty, hs_args) = splitHsAppTys rn_ty @@ -1576,15 +1576,16 @@ tcInferTyApps, tcInferTyApps_nosat :: TcTyMode -> LHsType GhcRn -- ^ Function (for printing only) -> TcType -- ^ Function - -> [(LHsTypeArg GhcRn, FamArgType)] -- ^ Args + -> [LHsTypeArg GhcRn] -- ^ Args + -> [FamArgFlavour] -- ^ Args -> TcM (TcType, TcKind) -- ^ (f args, result kind) -tcInferTyApps mode hs_ty fun hs_args - = do { (f_args, res_k) <- tcInferTyApps_nosat mode hs_ty fun hs_args +tcInferTyApps mode hs_ty fun hs_args famArgFlvs + = do { (f_args, res_k) <- tcInferTyApps_nosat mode hs_ty fun hs_args famArgFlvs ; saturateFamApp f_args res_k } -tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args +tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args fam_arg_flvs = do { traceTc "tcInferTyApps {" (ppr orig_hs_ty $$ ppr orig_hs_args) - ; (f_args, res_k) <- go_init 1 fun orig_hs_args + ; (f_args, res_k) <- go_init 1 fun orig_hs_args fam_arg_flvs ; traceTc "tcInferTyApps }" (ppr f_args <+> dcolon <+> ppr res_k) ; return (f_args, res_k) } where @@ -1608,7 +1609,8 @@ tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args -> TcType -- Function applied to some args -> Subst -- Applies to function kind -> TcKind -- Function kind - -> [(LHsTypeArg GhcRn, FamArgType)] -- Un-type-checked args + -> [LHsTypeArg GhcRn] -- Un-type-checked args + -> [FamArgFlavour] -- Un-type-checked args -> TcM (TcType, TcKind) -- Result type and its kind -- INVARIANT: in any call (go n fun subst fun_ki args) -- typeKind fun = subst(fun_ki) @@ -1621,14 +1623,14 @@ tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args -- is apply 'fun' to an argument type. -- Dispatch on all_args first, for performance reasons - go n fun subst fun_ki all_args = case (all_args, tcSplitPiTy_maybe fun_ki) of - + go n fun subst fun_ki all_args [] = error "tcInferTyApps_nosat: empty all_args" + go n fun subst fun_ki all_args arg_flvs@(arg_flv:rest_arg_flvs) = case (all_args, tcSplitPiTy_maybe fun_ki) of ---------------- No user-written args left. We're done! ([], _) -> return (fun, substTy subst fun_ki) - ((arg,famArgTy):argtys, kb) -> do + (arg:argtys, kb) -> do case (arg, kb) of ---------------- HsArgPar: We don't care about parens here - (HsArgPar _, _) -> go n fun subst fun_ki argtys + (HsArgPar _, _) -> go n fun subst fun_ki argtys arg_flvs ---------------- HsTypeArg: a kind application (fun @ki) (HsTypeArg _ hs_ki_arg, Just (ki_binder, inner_ki)) -> @@ -1640,6 +1642,7 @@ tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args Named (Bndr _ Specified) -> -- Visible kind application do { traceTc "tcInferTyApps (vis kind app)" (vcat [ ppr ki_binder, ppr hs_ki_arg + , ppr arg_flv , ppr (piTyBinderType ki_binder) , ppr subst ]) @@ -1651,7 +1654,7 @@ tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args ; traceTc "tcInferTyApps (vis kind app)" (ppr exp_kind) ; (subst', fun') <- mkAppTyM subst fun ki_binder ki_arg - ; go (n+1) fun' subst' inner_ki argtys } + ; go (n+1) fun' subst' inner_ki argtys rest_arg_flvs } -- Attempted visible kind application (fun @ki), but fun_ki is -- forall k -> blah or k1 -> k2 @@ -1674,20 +1677,20 @@ tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args -> do { traceTc "tcInferTyApps (vis normal app)" (vcat [ ppr ki_binder , ppr arg - , ppr famArgTy + , ppr arg_flv , ppr (piTyBinderType ki_binder) , ppr subst ]) ; let exp_kind = substTy subst $ piTyBinderType ki_binder ; arg' <- addErrCtxt (FunAppCtxt (FunAppCtxtTy orig_hs_ty arg) n) $ - tc_check_lhs_type (updateFamArgType famArgTy mode) arg exp_kind + tc_check_lhs_type (updateFamArgFlavour arg_flv mode) arg exp_kind ; traceTc "tcInferTyApps (vis normal app) 2" (ppr exp_kind) ; (subst', fun') <- mkAppTyM subst fun ki_binder arg' - ; go (n+1) fun' subst' inner_ki argtys } + ; go (n+1) fun' subst' inner_ki argtys rest_arg_flvs} -- no binder; try applying the substitution, or infer another arrow in fun kind (HsValArg _ _, Nothing) -> try_again_after_substing_or $ - do { let arrows_needed = n_initial_val_args (fst <$> all_args) + do { let arrows_needed = n_initial_val_args all_args ; co <- matchExpectedFunKind (HsTypeRnThing $ unLoc hs_ty) arrows_needed substed_fun_ki ; fun' <- liftZonkM $ zonkTcType (fun `mkCastTy` co) @@ -1699,27 +1702,27 @@ tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args , ppr arrows_needed , ppr co , ppr fun' <+> dcolon <+> ppr (typeKind fun')] - ; go_init n fun' all_args } + ; go_init n fun' all_args arg_flvs} -- Use go_init to establish go's INVARIANT where instantiate ki_binder inner_ki = do { traceTc "tcInferTyApps (need to instantiate)" - (vcat [ ppr ki_binder, ppr subst]) + (vcat [ ppr ki_binder, ppr arg_flv, ppr subst ]) ; (subst', arg') <- tcInstInvisibleTyBinder subst ki_binder - ; go n (mkAppTy fun arg') subst' inner_ki all_args } + ; go n (mkAppTy fun arg') subst' inner_ki all_args rest_arg_flvs} -- Because tcInvisibleTyBinder instantiate ki_binder, -- the kind of arg' will have the same shape as the kind -- of ki_binder. So we don't need mkAppTyM here. try_again_after_substing_or fallthrough | not (isEmptyTCvSubst subst) - = go n fun zapped_subst substed_fun_ki all_args + = go n fun zapped_subst substed_fun_ki all_args arg_flvs | otherwise = fallthrough zapped_subst = zapSubst subst substed_fun_ki = substTy subst fun_ki - hs_ty = appTypeToArg orig_hs_ty (take (n-1) $ fst <$> orig_hs_args) + hs_ty = appTypeToArg orig_hs_ty (take (n-1) orig_hs_args) n_initial_val_args :: [HsArg p tm ty] -> Arity -- Count how many leading HsValArgs we have @@ -2258,7 +2261,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) } HM_TyAppPat -> fsLit "_" mk_wc_details = case hole_mode of HM_FamPat FreeArg -> newTyVarMetaVarDetailsAtLevel - HM_FamPat ClassArg -> newTyVarMetaVarDetailsAtLevel + HM_FamPat ClassArg -> newTauTvDetailsAtLevel HM_FamPat SigArg -> newTauTvDetailsAtLevel _ -> newTauTvDetailsAtLevel emit_holes = case hole_mode of ===================================== compiler/GHC/Tc/Instance/Class.hs ===================================== @@ -6,9 +6,7 @@ module GHC.Tc.Instance.Class ( ClsInstResult(..), InstanceWhat(..), safeOverlap, instanceReturnsDictCon, AssocInstInfo(..), isNotAssociated, - lookupHasFieldLabel, FamArgType(..), PartialAssocInstInfo, - buildAssocInstInfo, buildPatsArgTypes, - assocInstInfoPartialAssocInstInfo, buildPatsModeTypes + lookupHasFieldLabel ) where import GHC.Prelude @@ -92,33 +90,7 @@ data AssocInstInfo -- 'GHC.Tc.Validity.checkConsistentFamInst' , ai_inst_env :: VarEnv Type -- ^ Maps /class/ tyvars to their instance types -- See Note [Matching in the consistent-instantiation check] - , ai_arg_types :: [FamArgType] -- ^ The types of the arguments to the associated type } -type PartialAssocInstInfo = Maybe (Class, [TyVar], VarEnv Type) - -assocInstInfoPartialAssocInstInfo :: AssocInstInfo -> PartialAssocInstInfo -assocInstInfoPartialAssocInstInfo NotAssociated = Nothing -assocInstInfoPartialAssocInstInfo (InClsInst {..}) = Just (ai_class, ai_tyvars, ai_inst_env) - -buildAssocInstInfo :: TyCon -> PartialAssocInstInfo -> AssocInstInfo -buildAssocInstInfo _fam_tc Nothing = NotAssociated -buildAssocInstInfo fam_tc (Just (cls, tvs, env)) - = InClsInst cls tvs env - [ if elemVarEnv fam_tc_tv env then ClassArg else FreeArg | fam_tc_tv <- tyConTyVars fam_tc] - -buildPatsArgTypes :: (Outputable x) => AssocInstInfo -> [x] -> [(x, FamArgType)] -buildPatsArgTypes NotAssociated xs = buildPatsModeTypes FreeArg xs -buildPatsArgTypes (InClsInst {..}) xs = zip xs (ai_arg_types ++ cycle [FreeArg]) - -buildPatsModeTypes :: FamArgType -> [x] -> [(x, FamArgType)] -buildPatsModeTypes fa xs = (,fa) <$> xs - -data FamArgType = ClassArg | FreeArg | SigArg deriving (Eq, Show) - -instance Outputable FamArgType where - ppr ClassArg = text "ClassArg" - ppr FreeArg = text "FreeArg" - ppr SigArg = text "SigArg" isNotAssociated :: AssocInstInfo -> Bool isNotAssociated (NotAssociated {}) = True ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -49,7 +49,7 @@ import {-# SOURCE #-} GHC.Tc.TyCl.Instance( tcInstDecls1 ) import {-# SOURCE #-} GHC.Tc.Module( checkBootDeclM ) import GHC.Tc.Deriv (DerivInfo(..)) import GHC.Tc.Gen.HsType -import GHC.Tc.Instance.Class( AssocInstInfo(..), PartialAssocInstInfo) +import GHC.Tc.Instance.Class( AssocInstInfo(..)) import GHC.Tc.Utils.TcMType import GHC.Tc.Utils.TcType import GHC.Tc.Instance.Family @@ -2659,68 +2659,79 @@ tcClassDecl1 :: RolesInfo -> Name -> Maybe (LHsContext GhcRn) -> [LFamilyDecl GhcRn] -> [LTyFamDefltDecl GhcRn] -> TcM Class tcClassDecl1 roles_info class_name hs_ctxt meths fundeps sigs ats at_defs - = fixM $ \ clas -> -- We need the knot because 'clas' is passed into tcClassATs - bindTyClTyVars class_name $ \ tc_bndrs res_kind -> - do { checkClassKindSig res_kind - ; traceTc "tcClassDecl 1" (ppr class_name $$ ppr tc_bndrs) - ; let tycon_name = class_name -- We use the same name - roles = roles_info tycon_name -- for TyCon and Class - - ; (ctxt, fds, sig_stuff, at_stuff) - <- pushLevelAndSolveEqualities skol_info tc_bndrs $ - -- The (binderVars tc_bndrs) is needed bring into scope the - -- skolems bound by the class decl header (#17841) - do { ctxt <- tcHsContext hs_ctxt - ; fds <- mapM (addLocM tc_fundep) fundeps - ; sig_stuff <- tcClassSigs class_name sigs meths - ; at_stuff <- tcClassATs class_name clas ats at_defs - ; return (ctxt, fds, sig_stuff, at_stuff) } - - -- See Note [Error on unconstrained meta-variables] in GHC.Tc.Utils.TcMType - -- Example: (typecheck/should_fail/T17562) - -- type C :: Type -> Type -> Constraint - -- class (forall a. a b ~ a c) => C b c - -- The kind of `a` is unconstrained. - ; dvs <- candidateQTyVarsOfTypes ctxt - ; let err_ctx tidy_env = do { (tidy_env2, ctxt) <- zonkTidyTcTypes tidy_env ctxt - ; return (tidy_env2, UninfTyCtx_ClassContext ctxt) } - ; doNotQuantifyTyVars dvs err_ctx - - -- The pushLevelAndSolveEqualities will report errors for any - -- unsolved equalities, so these zonks should not encounter - -- any unfilled coercion variables unless there is such an error - -- The zonk also squeeze out the TcTyCons, and converts - -- Skolems to tyvars. - ; (bndrs, ctxt, sig_stuff) <- initZonkEnv NoFlexi $ - runZonkBndrT (zonkTyVarBindersX tc_bndrs) $ \ bndrs -> - do { ctxt <- zonkTcTypesToTypesX ctxt - ; sig_stuff <- mapM zonkTcMethInfoToMethInfoX sig_stuff - -- ToDo: do we need to zonk at_stuff? - ; return (bndrs, ctxt, sig_stuff) } - - -- TODO: Allow us to distinguish between abstract class, - -- and concrete class with no methods (maybe by - -- specifying a trailing where or not - - ; mindef <- tcClassMinimalDef class_name sigs sig_stuff - ; is_boot <- tcIsHsBootOrSig - ; let body | is_boot, isNothing hs_ctxt, null at_stuff, null sig_stuff - -- We use @isNothing hs_ctxt@ rather than @null ctxt@, - -- so that a declaration in an hs-boot file such as: - -- - -- class () => C a b | a -> b - -- - -- is not considered abstract; it's sometimes useful - -- to be able to declare such empty classes in hs-boot files. - -- See #20661. - = Nothing - | otherwise - = Just (ctxt, at_stuff, sig_stuff, mindef) - - ; clas <- buildClass class_name bndrs roles fds body - ; traceTc "tcClassDecl" (ppr fundeps $$ ppr bndrs $$ - ppr fds) - ; return clas } + = do { cls <- + fixM $ \ clas -> -- We need the knot because 'clas' is passed into tcClassATs + bindTyClTyVars class_name $ \ tc_bndrs res_kind -> + do { checkClassKindSig res_kind + ; traceTc "tcClassDecl 1" (ppr class_name $$ ppr tc_bndrs) + ; let tycon_name = class_name -- We use the same name + roles = roles_info tycon_name -- for TyCon and Class + + ; (ctxt, fds, sig_stuff, at_stuff) + <- pushLevelAndSolveEqualities skol_info tc_bndrs $ + -- The (binderVars tc_bndrs) is needed bring into scope the + -- skolems bound by the class decl header (#17841) + do { ctxt <- tcHsContext hs_ctxt + ; fds <- mapM (addLocM tc_fundep) fundeps + ; sig_stuff <- tcClassSigs class_name sigs meths + ; at_stuff <- tcClassATs class_name clas ats at_defs + ; return (ctxt, fds, sig_stuff, at_stuff) } + + -- See Note [Error on unconstrained meta-variables] in GHC.Tc.Utils.TcMType + -- Example: (typecheck/should_fail/T17562) + -- type C :: Type -> Type -> Constraint + -- class (forall a. a b ~ a c) => C b c + -- The kind of `a` is unconstrained. + ; dvs <- candidateQTyVarsOfTypes ctxt + ; let err_ctx tidy_env = do { (tidy_env2, ctxt) <- zonkTidyTcTypes tidy_env ctxt + ; return (tidy_env2, UninfTyCtx_ClassContext ctxt) } + ; doNotQuantifyTyVars dvs err_ctx + + -- The pushLevelAndSolveEqualities will report errors for any + -- unsolved equalities, so these zonks should not encounter + -- any unfilled coercion variables unless there is such an error + -- The zonk also squeeze out the TcTyCons, and converts + -- Skolems to tyvars. + ; (bndrs, ctxt, sig_stuff) <- initZonkEnv NoFlexi $ + runZonkBndrT (zonkTyVarBindersX tc_bndrs) $ \ bndrs -> + do { ctxt <- zonkTcTypesToTypesX ctxt + ; sig_stuff <- mapM zonkTcMethInfoToMethInfoX sig_stuff + -- ToDo: do we need to zonk at_stuff? + ; return (bndrs, ctxt, sig_stuff) } + + -- TODO: Allow us to distinguish between abstract class, + -- and concrete class with no methods (maybe by + -- specifying a trailing where or not + + ; mindef <- tcClassMinimalDef class_name sigs sig_stuff + ; is_boot <- tcIsHsBootOrSig + ; let body | is_boot, isNothing hs_ctxt, null at_stuff, null sig_stuff + -- We use @isNothing hs_ctxt@ rather than @null ctxt@, + -- so that a declaration in an hs-boot file such as: + -- + -- class () => C a b | a -> b + -- + -- is not considered abstract; it's sometimes useful + -- to be able to declare such empty classes in hs-boot files. + -- See #20661. + = Nothing + | otherwise + = Just (ctxt, at_stuff, sig_stuff, mindef) + + ; clas <- buildClass class_name bndrs roles fds body + ; traceTc "tcClassDecl" (ppr fundeps $$ ppr bndrs $$ ppr fds) + ; return clas } + ; mapM_ + (\tc -> + traceTc "tcClassDecl assoc type class:" + (vcat + [ ppr tc + , text "tyConBinders:" <+> ppr (tyConBinders tc) + , text "tyConTyVars:" <+> ppr (tyConTyVars tc) + , text "tyConFamArgFlavours:" <+> ppr (tyConFamArgFlavours tc) + ])) + $ map (\(ATI ty _) -> ty) $ classATItems cls + ; return cls } where skol_info = TyConSkol ClassFlavour class_name @@ -3253,7 +3264,7 @@ kcTyFamInstEqn tc_fam_tc ; discardResult $ bindOuterFamEqnTKBndrs_Q_Tv outer_bndrs $ - do { (_fam_app, res_kind) <- tcFamTyPats tc_fam_tc hs_pats NotAssociated + do { (_fam_app, res_kind) <- tcFamTyPats tc_fam_tc hs_pats ; tcCheckLHsTypeInContext hs_rhs_ty (TheKind res_kind) } -- Why "_Tv" here? Consider (#14066) -- type family Bar x y where @@ -3279,7 +3290,7 @@ tcTyFamInstEqn fam_tc mb_clsinfo , text "fam tc bndrs" <+> pprTyVars (tyConTyVars fam_tc) , case mb_clsinfo of NotAssociated {} -> empty - InClsInst { ai_class = cls, ai_arg_types = arg_types } -> text "class" <+> ppr cls <+> pprTyVars (classTyVars cls) <+> ppr arg_types] + InClsInst { ai_class = cls } -> text "class" <+> ppr cls <+> pprTyVars (classTyVars cls) ] ; checkTyFamInstEqn fam_tc eqn_tc_name hs_pats @@ -3430,7 +3441,7 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty ; (tclvl, wanted, (outer_bndrs, (lhs_ty, rhs_ty))) <- pushLevelAndSolveEqualitiesX "tcTyFamInstEqnGuts" $ bindOuterFamEqnTKBndrs skol_info outer_hs_bndrs $ - do { (lhs_ty, rhs_kind) <- tcFamTyPats fam_tc hs_pats mb_clsinfo + do { (lhs_ty, rhs_kind) <- tcFamTyPats fam_tc hs_pats -- Ensure that the instance is consistent with its -- parent class (#16008) ; addConsistencyConstraints mb_clsinfo lhs_ty @@ -5539,19 +5550,19 @@ tcAddDeclCtxt :: TyClDecl GhcRn -> TcM a -> TcM a tcAddDeclCtxt decl thing_inside = addErrCtxt (tcMkDeclCtxt decl) thing_inside -tcAddOpenTyFamInstCtxt :: PartialAssocInstInfo -> TyFamInstDecl GhcRn -> TcM a -> TcM a +tcAddOpenTyFamInstCtxt :: AssocInstInfo -> TyFamInstDecl GhcRn -> TcM a -> TcM a tcAddOpenTyFamInstCtxt mb_assoc decl = tcAddFamInstCtxt flav (tyFamInstDeclName decl) where assoc = case mb_assoc of - Nothing -> Nothing - Just (cls,_,_) -> Just $ classTyCon cls + NotAssociated -> Nothing + InClsInst { ai_class = cls } -> Just $ classTyCon cls flav = TyConInstFlavour { tyConInstFlavour = OpenFamilyFlavour IAmType assoc , tyConInstIsDefault = False } -tcMkDataFamInstCtxt :: PartialAssocInstInfo -> NewOrData -> DataFamInstDecl GhcRn -> ErrCtxtMsg +tcMkDataFamInstCtxt :: AssocInstInfo -> NewOrData -> DataFamInstDecl GhcRn -> ErrCtxtMsg tcMkDataFamInstCtxt mb_assoc new_or_data (DataFamInstDecl { dfid_eqn = eqn }) = TyConInstCtxt (unLoc (feqn_tycon eqn)) (TyConInstFlavour @@ -5560,10 +5571,10 @@ tcMkDataFamInstCtxt mb_assoc new_or_data (DataFamInstDecl { dfid_eqn = eqn }) }) where assoc = case mb_assoc of - Nothing -> Nothing - Just (cls,_,_) -> Just $ classTyCon cls + NotAssociated -> Nothing + InClsInst { ai_class = cls } -> Just $ classTyCon cls -tcAddDataFamInstCtxt :: PartialAssocInstInfo -> NewOrData -> DataFamInstDecl GhcRn -> TcM a -> TcM a +tcAddDataFamInstCtxt :: AssocInstInfo -> NewOrData -> DataFamInstDecl GhcRn -> TcM a -> TcM a tcAddDataFamInstCtxt assoc new_or_data decl = addErrCtxt (tcMkDataFamInstCtxt assoc new_or_data decl) ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -43,7 +43,7 @@ import GHC.Tc.Types.Constraint import GHC.Tc.Types.Origin import GHC.Tc.TyCl.Build import GHC.Tc.Utils.Instantiate -import GHC.Tc.Instance.Class( AssocInstInfo(..), isNotAssociated, PartialAssocInstInfo, buildAssocInstInfo, assocInstInfoPartialAssocInstInfo ) +import GHC.Tc.Instance.Class( AssocInstInfo(..), isNotAssociated ) import GHC.Core.Multiplicity import GHC.Core.InstEnv import GHC.Tc.Instance.Family @@ -472,11 +472,11 @@ tcLocalInstDecl :: LInstDecl GhcRn -- -- We check for respectable instance type, and context tcLocalInstDecl (L loc (TyFamInstD { tfid_inst = decl })) - = do { fam_inst <- tcTyFamInstDecl Nothing (L loc decl) + = do { fam_inst <- tcTyFamInstDecl NotAssociated (L loc decl) ; return ([], [fam_inst], []) } tcLocalInstDecl (L loc (DataFamInstD { dfid_inst = decl })) - = do { (fam_inst, m_deriv_info) <- tcDataFamInstDecl Nothing emptyVarEnv (L loc decl) + = do { (fam_inst, m_deriv_info) <- tcDataFamInstDecl NotAssociated emptyVarEnv (L loc decl) ; return ([], [fam_inst], maybeToList m_deriv_info) } tcLocalInstDecl (L loc (ClsInstD { cid_inst = decl })) @@ -515,7 +515,9 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_ext = lwarn <- tcExtendNameTyVarEnv tv_skol_prs $ do { let mini_env = mkVarEnv (classTyVars clas `zip` substTys subst inst_tys) mini_subst = mkTvSubst (mkInScopeSet (mkVarSet skol_tvs)) mini_env - mb_info = Just (clas, visible_skol_tvs, mini_env) + mb_info = InClsInst { ai_class = clas + , ai_tyvars = visible_skol_tvs + , ai_inst_env = mini_env } ; df_stuff <- mapAndRecoverM (tcDataFamInstDecl mb_info tv_skol_env) adts ; tf_insts1 <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats @@ -585,16 +587,15 @@ lot of kinding and type checking code with ordinary algebraic data types (and GADTs). -} -tcTyFamInstDecl :: PartialAssocInstInfo +tcTyFamInstDecl :: AssocInstInfo -> LTyFamInstDecl GhcRn -> TcM FamInst -- "type instance"; open type families only -- See Note [Associated type instances] -tcTyFamInstDecl partial_mb_clsinfo (L loc decl@(TyFamInstDecl { tfid_eqn = eqn })) +tcTyFamInstDecl mb_clsinfo (L loc decl@(TyFamInstDecl { tfid_eqn = eqn })) = setSrcSpanA loc $ - tcAddOpenTyFamInstCtxt partial_mb_clsinfo decl $ + tcAddOpenTyFamInstCtxt mb_clsinfo decl $ do { let fam_lname = feqn_tycon eqn ; fam_tc <- tcLookupLocatedTyCon fam_lname - ; let mb_clsinfo = buildAssocInstInfo fam_tc partial_mb_clsinfo ; tcFamInstDeclChecks mb_clsinfo IAmType fam_tc -- (0) Check it's an open type family @@ -681,7 +682,7 @@ than type family instances -} tcDataFamInstDecl :: - PartialAssocInstInfo + AssocInstInfo -> TyVarEnv Name -- If this is an associated data family instance, maps the -- parent class's skolemized type variables to their -- original Names. If this is a non-associated instance, @@ -689,7 +690,7 @@ tcDataFamInstDecl :: -- See Note [Associated data family instances and di_scoped_tvs]. -> LDataFamInstDecl GhcRn -> TcM (FamInst, Maybe DerivInfo) -- "newtype instance" and "data instance" -tcDataFamInstDecl partial_mb_clsinfo tv_skol_env +tcDataFamInstDecl mb_clsinfo tv_skol_env (L loc decl@(DataFamInstDecl { dfid_eqn = FamEqn { feqn_bndrs = outer_bndrs , feqn_pats = hs_pats @@ -701,9 +702,9 @@ tcDataFamInstDecl partial_mb_clsinfo tv_skol_env , dd_kindSig = m_ksig , dd_derivs = derivs } }})) = setSrcSpanA loc $ - tcAddDataFamInstCtxt partial_mb_clsinfo new_or_data decl $ + tcAddDataFamInstCtxt mb_clsinfo new_or_data decl $ do { fam_tc <- tcLookupLocatedTyCon lfam_name - ; let mb_clsinfo = buildAssocInstInfo fam_tc partial_mb_clsinfo + ; tcFamInstDeclChecks mb_clsinfo (IAmData new_or_data) fam_tc -- Check that the family declaration is for the right kind @@ -843,7 +844,7 @@ tcDataFamInstDecl partial_mb_clsinfo tv_skol_env Just $ DerivInfo { di_rep_tc = rep_tc , di_scoped_tvs = scoped_tvs , di_clauses = preds - , di_ctxt = tcMkDataFamInstCtxt (assocInstInfoPartialAssocInstInfo mb_clsinfo) new_or_data decl + , di_ctxt = tcMkDataFamInstCtxt mb_clsinfo new_or_data decl } ; fam_inst <- newFamInst (DataFamilyInst rep_tc) axiom @@ -933,7 +934,7 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $ bindOuterFamEqnTKBndrs skol_info hs_outer_bndrs $ -- Binds skolem TcTyVars do { stupid_theta <- tcHsContext hs_ctxt - ; (lhs_ty, lhs_kind) <- tcFamTyPats fam_tc hs_pats mb_clsinfo + ; (lhs_ty, lhs_kind) <- tcFamTyPats fam_tc hs_pats ; (lhs_applied_ty, lhs_applied_kind) <- tcInstInvisibleTyBinders lhs_ty lhs_kind -- See Note [Data family/instance return kinds] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9869fe5d2bda18d7d5624ebeeff7ab6e7ff0b0ac...dbe81ead0bf274ecd7039be8df39624a9e2b1aa3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9869fe5d2bda18d7d5624ebeeff7ab6e7ff0b0ac...dbe81ead0bf274ecd7039be8df39624a9e2b1aa3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/abe66a3c/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 19:42:27 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 04 Mar 2025 14:42:27 -0500 Subject: [Git][ghc/ghc][wip/T25647] refactor documentation for FamArgFlavour and clean up comments Message-ID: <67c757a3d2652_17b19ab6c81c2819d@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 9a1136f5 by Patrick at 2025-03-05T03:42:17+08:00 refactor documentation for FamArgFlavour and clean up comments - - - - - 3 changed files: - compiler/GHC/Core/TyCon.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2980,7 +2980,7 @@ tyConSkolem = isHoleName . tyConName -{- Note [FamArgFlavour and family instance decl type checking] +{- Note [FamArgFlavour] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The FamArgFlavour is used to distinguish the different kinds of arguments that may appear in an associated type family declaration/instance. In an associated type family, @@ -3022,7 +3022,7 @@ the signature arguments. For more discussion, see #13908. -} --- see Note [FamArgFlavour and family instance decl type checking] +-- see Note [FamArgFlavour] data FamArgFlavour = ClassArg | FreeArg | SigArg deriving (Eq, Show) instance Outputable FamArgFlavour where ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -3409,8 +3409,7 @@ without treating the explicitly-quantified ones specially. Wrinkles: In step 1 we do /not/ want to get newtype instance forall r . Fix2 (f :: TYPE r -> TYPE r) :: TYPE r where If we do, we'll get that same "newtype must not be GADT" error as for N above. - Rather, we want to default the RuntimeRep variable r := LiftedRep. Hence - the use of `DefaultNonStandardTyVars` in `tcDataFamInstHeader`. The key thing + Rather, we want to default the RuntimeRep variable r := LiftedRep. The key thing is that we must make the /same/ choice here as we do in kind-checking the data constructor's type. ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -977,7 +977,7 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] ; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty ; qtvs <- quantifyTyVars skol_info dvs - -- DefaultNonStandardTyVars: see (GT4) in + -- see (GT4) in -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] ; let final_tvs = scopedSort (qtvs ++ outer_tvs) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9a1136f5e42cd4fa8599551f8c8bdabd7050b4dc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9a1136f5e42cd4fa8599551f8c8bdabd7050b4dc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/82e7bdd3/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 21:23:48 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 04 Mar 2025 16:23:48 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/backports-9.10 Message-ID: <67c76f642563b_1ce61913fc18787e5@gitlab.mail> Ben Gamari pushed new branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports-9.10 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/73df8bde/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 4 21:42:32 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 04 Mar 2025 16:42:32 -0500 Subject: [Git][ghc/ghc][wip/backports-9.10] 2 commits: Bump text submodule to current `master` Message-ID: <67c773c8e6ad8_1ce61974ad74793e1@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: 877895d2 by Ben Gamari at 2025-03-03T14:31:03-05:00 Bump text submodule to current `master` This will be a revision of 2.1.2. - - - - - 716e4c92 by Ben Gamari at 2025-03-04T16:42:21-05:00 Revert "testsuite: expand size testing infrastructure" This reverts commit a15b3383c95864eb1ca9df4f7065ef6f6fe84393. - - - - - 4 changed files: - libraries/text - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/tests/perf/size/all.T Changes: ===================================== libraries/text ===================================== @@ -1 +1 @@ -Subproject commit 991b7e34efacc44a8a8b60e28ae737c45bc5942e +Subproject commit a721bf58a3b9591473ceae938ac916cb9b0de2c0 ===================================== testsuite/driver/testglobals.py ===================================== @@ -223,10 +223,6 @@ class TestConfig: # I have no idea what this does self.package_conf_cache_file = None # type: Optional[Path] - # the libdir for the test compiler. Set by hadrian, see - # Setting.Builders.RunTest - self.libdir = '' - # The extra hadrian dependencies we need for all configured tests self.hadrian_deps = set() # type: Set[str] ===================================== testsuite/driver/testlib.py ===================================== @@ -143,15 +143,6 @@ def js_skip( name, opts ): if js_arch(): skip(name,opts) -# disable test on WASM arch -def wasm_skip( name, opts ): - if wasm_arch(): - skip(name,opts) - -def windows_skip(name,opts): - if on_windows(): - skip(name,opts) - # expect broken for the JS backend def js_broken( bug: IssueNumber ): if js_arch(): @@ -248,15 +239,6 @@ def req_dynamic_hs( name, opts ): if not config.supports_dynamic_hs: opts.expect = 'fail' -def req_dynamic_ghc( name, opts ): - ''' - Require that the GHC is dynamically linked, if static then skip. - See tests/perf/size/all.T, specifically foo.so tests for use case - and example - ''' - if not config.ghc_dynamic: - skip(name,opts) - def req_interp( name, opts ): if not config.have_interp or isCross(): opts.expect = 'fail' @@ -275,10 +257,6 @@ def req_bco( name, opts ): # JS backend doesn't support ByteCode js_skip(name, opts) -def req_c_rts( name, opts ): - """ Require the C runtime system (rather than, e.g. the Javascript RTS). """ - js_skip(name, opts) - def req_rts_linker( name, opts ): if not config.have_RTS_linker: opts.expect = 'fail' @@ -628,24 +606,15 @@ def collect_size ( deviation, path ): def get_dir_size(path): total = 0 - try: - with os.scandir(path) as it: - for entry in it: - if entry.is_file(): - total += entry.stat().st_size - elif entry.is_dir(): - total += get_dir_size(entry.path) - return total - except FileNotFoundError: - print("Exception: Could not find: " + path) + with os.scandir(path) as it: + for entry in it: + if entry.is_file(): + total += entry.stat().st_size + elif entry.is_dir(): + total += get_dir_size(entry.path) + return total def collect_size_dir ( deviation, path ): - - ## os.path.join joins the path with slashes (not backslashes) on windows - ## CI...for some reason, so we manually detect it here - sep = r"/" - if on_windows(): - sep = r"\\" return collect_generic_stat ( 'size', deviation, lambda way: get_dir_size(path) ) # Read a number from a specific file @@ -662,92 +631,7 @@ def collect_generic_stats ( metric_info ): return _collect_generic_stat(name, opts, metric_info) return f -# wrap the call to collect_size_dir with path_from_ghcPkg in a function. Python -# is call-by-value so if we placed the call in an all.T file then the python -# interpreter would evaluate the call to path_from_ghcPkg -def collect_size_ghc_pkg (deviation, library): - return collect_size_dir(deviation, path_from_ghcPkg(library, "library-dirs")) - -# same for collect_size and find_so -def collect_object_size (deviation, library, use_non_inplace=False): - if use_non_inplace: - return collect_size(deviation, find_non_inplace_so(library)) - else: - return collect_size(deviation, find_so(library)) - -def path_from_ghcPkg (library, field): - """Find the field as a path for a library via a call to ghc-pkg. This is a - testsuite wrapper around a call to ghc-pkg field {library} {field}. - """ - - ### example output from ghc-pkg: - ### $ ./ghc-pkg field Cabal library-dirs - ### library-dirs: /home/doyougnu/programming/haskell/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240424/Cabal-3.11.0.0-inplace - ### so we split the string and drop the 'library-dirs' - ghcPkgCmd = fr"{config.ghc_pkg} field {library} {field}" - - try: - result = subprocess.run(ghcPkgCmd, capture_output=True, shell=True) - - # check_returncode throws an exception if the return code is not 0. - result.check_returncode() - - # if we get here then the call worked and we have the path we split by - # whitespace and then return the path which becomes the second element - # in the array - return re.split(r'\s+', result.stdout.decode("utf-8"))[1] - except Exception as e: - message = f""" - Attempt to find {field} of {library} using ghc-pkg failed. - ghc-pkg path: {config.ghc_pkg} - error" {e} - """ - print(message) - - -def _find_so(lib, directory, in_place): - """Find a shared object file (.so) for lib in directory. We deliberately - keep the regex simple, just removing the ghc version and project version. - Example: - - _find_so("Cabal-syntax-3.11.0.0", path-from-ghc-pkg, True) ==> - /builds/ghc/ghc/_build/install/lib/ghc-9.11.20240410/lib/x86_64-linux-ghc-9.11.20240410/libHSCabal-syntax-3.11.0.0-inplace-ghc9.11.20240410.so - """ - - # produce the suffix for the CI operating system - suffix = "so" - if config.os == "mingw32": - suffix = "dll" - elif config.os == "darwin": - suffix = "dylib" - - # Most artfacts are of the form foo-inplace, except for the rts. - if in_place: - to_match = r'libHS{}-\d+(\.\d+)+-inplace-\S+\.' + suffix - else: - to_match = r'libHS{}-\d+(\.\d+)+\S+\.' + suffix - - matches = [] - # wrap this in some exception handling, hadrian test will error out because - # these files don't exist yet, so we pass when this occurs - try: - for f in os.listdir(directory): - if f.endswith(suffix): - pattern = re.compile(to_match.format(re.escape(lib))) - match = re.match(pattern, f) - if match: - matches.append(match.group()) - return os.path.join(directory, matches[0]) - except: - failBecause('Could not find shared object file: ' + lib) - -def find_so(lib): - return _find_so(lib,path_from_ghcPkg(lib, "dynamic-library-dirs"),True) - -def find_non_inplace_so(lib): - return _find_so(lib,path_from_ghcPkg(lib, "dynamic-library-dirs"),False) - -# Define a generic stat test, which computes the statistic by calling the function +# Define the a generic stat test, which computes the statistic by calling the function # given as the third argument. def collect_generic_stat ( metric, deviation, get_stat ): return collect_generic_stats ( { metric: { 'deviation': deviation, 'current': get_stat } } ) @@ -915,9 +799,9 @@ KNOWN_OPERATING_SYSTEMS = set([ ]) def exe_extension() -> str: - if wasm_arch(): + if config.arch == 'wasm32': return '.wasm' - elif on_windows(): + elif config.os == "mingw32": return '.exe' return '' @@ -940,9 +824,6 @@ def cygwin( ) -> bool: def js_arch() -> bool: return arch("javascript"); -def on_windows() -> bool: - return config.os == "mingw32" - def wasm_arch() -> bool: return arch("wasm32") @@ -995,10 +876,6 @@ def llvm_build ( ) -> bool: def have_thread_sanitizer( ) -> bool: return config.have_thread_sanitizer - -def gcc_as_cmmp() -> bool: - return config.cmm_cpp_is_gcc - # --- # Note [Measuring residency] ===================================== testsuite/tests/perf/size/all.T ===================================== @@ -3,80 +3,4 @@ test('size_hello_obj', [collect_size(5, 'size_hello_obj.o')], compile, ['']) test('size_hello_artifact', [collect_size(5, 'size_hello_artifact' + exe_extension())], compile_artifact, ['']) -size_acceptance_threshold = 100 - -test('array_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'array')] , static_stats , [] ) -test('base_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'base')] , static_stats , [] ) -test('binary_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'binary')] , static_stats , [] ) -test('bytestring_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'bytestring')] , static_stats , [] ) -test('cabal_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'Cabal')] , static_stats , [] ) -test('cabal_syntax_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'Cabal-syntax')] , static_stats , [] ) -test('containers_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'containers')] , static_stats , [] ) -test('deepseq_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'deepseq')] , static_stats , [] ) -test('directory_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'directory')] , static_stats , [] ) -test('exceptions_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'exceptions')] , static_stats , [] ) -test('ghc_bignum_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-bignum')] , static_stats , [] ) -test('ghc_boot_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-boot')] , static_stats , [] ) -test('ghc_boot_th_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-boot-th')] , static_stats , [] ) -test('ghc_compact_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-compact')] , static_stats , [] ) -test('ghc_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc')] , static_stats , [] ) -test('ghc_experimental_dir',[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-experimental')], static_stats , [] ) -test('ghc_heap_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-heap')] , static_stats , [] ) -test('ghc_internal_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-internal')] , static_stats , [] ) -test('ghc_platform_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-platform')] , static_stats , [] ) -test('ghc_prim_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-prim')] , static_stats , [] ) -test('ghc_toolchain_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-toolchain')] , static_stats , [] ) -test('haskeline_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'haskeline')] , static_stats , [] ) -test('hpc_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'hpc')] , static_stats , [] ) -test('integer_gmp_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'integer-gmp')] , static_stats , [] ) -test('mtl_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'mtl')] , static_stats , [] ) -test('os_string_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'os-string')] , static_stats , [] ) -test('parsec_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'parsec')] , static_stats , [] ) -test('pretty_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'pretty')] , static_stats , [] ) -test('process_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'process')] , static_stats , [] ) -test('time_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'time')] , static_stats , [] ) -test('xhtml_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'xhtml')] , static_stats , [] ) - -# size of the entire libdir -test('libdir' ,[collect_size_dir(10, config.libdir)] , static_stats , [] ) - -# skip these on windows -test('unix_dir' ,[windows_skip, collect_size_ghc_pkg(size_acceptance_threshold, 'unix')] , static_stats, [] ) -test('terminfo_dir' ,[windows_skip, js_skip, collect_size_ghc_pkg(size_acceptance_threshold, 'terminfo')], static_stats, [] ) - -# skip the shared object file tests on windows -test('array_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "array")] , static_stats, [] ) -test('base_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "base")] , static_stats, [] ) -test('binary_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "binary")] , static_stats, [] ) -test('bytestring_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "bytestring")] , static_stats, [] ) -test('cabal_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "Cabal")] , static_stats, [] ) -test('cabal_syntax_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "Cabal-syntax")] , static_stats, [] ) -test('containers_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "containers")] , static_stats, [] ) -test('deepseq_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "deepseq")] , static_stats, [] ) -test('directory_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "directory")] , static_stats, [] ) -test('exceptions_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "exceptions")] , static_stats, [] ) -test('filepath_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "filepath")] , static_stats, [] ) -test('ghc_bignum_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-bignum")] , static_stats, [] ) -test('ghc_boot_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-boot")] , static_stats, [] ) -test('ghc_boot_th_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-boot-th")] , static_stats, [] ) -test('ghc_experimental_so',[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-experimental")] , static_stats, [] ) -test('ghc_heap_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-heap")] , static_stats, [] ) -test('ghc_platform_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-platform")] , static_stats, [] ) -test('ghc_prim_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-prim")] , static_stats, [] ) -test('ghc_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc")] , static_stats, [] ) -test('ghc_toolchain_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-toolchain")] , static_stats, [] ) -test('ghci_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghci")] , static_stats, [] ) -test('haskeline_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "haskeline")] , static_stats, [] ) -test('hpc_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "hpc")] , static_stats, [] ) -test('mtl_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "mtl")] , static_stats, [] ) -test('os_string_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "os-string")] , static_stats, [] ) -test('parsec_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "parsec")] , static_stats, [] ) -test('process_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "process")] , static_stats, [] ) -# Disabled as extremely unstable -#test('rts_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "rts", True)] , static_stats, [] ) -test('template_haskell_so',[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "template-haskell")] , static_stats, [] ) -test('terminfo_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "terminfo")] , static_stats, [] ) -test('text_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "text")] , static_stats, [] ) -test('time_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "time")] , static_stats, [] ) -test('transformers_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "transformers")] , static_stats, [] ) -test('xhtml_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "xhtml")] , static_stats, [] ) +test('libdir',[collect_size_dir(10, config.libdir)], static_stats, [] ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fb855f87e8276c1e0d7fb28668294825eff027cf...716e4c92e65d2c4a23f33c011d3441149b605936 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fb855f87e8276c1e0d7fb28668294825eff027cf...716e4c92e65d2c4a23f33c011d3441149b605936 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/a2d93278/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 22:11:30 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 04 Mar 2025 17:11:30 -0500 Subject: [Git][ghc/ghc][wip/compress-iface] 19 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67c77a928628e_1ce619b72654811d9@gitlab.mail> Matthew Pickering pushed to branch wip/compress-iface at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - e3eaf6c1 by Matthew Pickering at 2025-03-04T17:55:01+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-self-recomp-info which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - ffafd83d by Matthew Pickering at 2025-03-04T17:55:02+00:00 Disable self recomp in release flavour - - - - - b0598321 by Matthew Pickering at 2025-03-04T17:55:02+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 2c6ed486 by Matthew Pickering at 2025-03-04T17:55:02+00:00 WIP: Compress interface files - - - - - 7b482ff1 by Matthew Pickering at 2025-03-04T22:10:41+00:00 Fix - - - - - 75 changed files: - compiler/GHC.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/StgToCmm/InfoTableProv.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/GHC/Utils/Binary.hs - + compiler/GHC/Utils/Compress.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/src/Flavour.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - m4/fp_find_libzstd.m4 - rts/include/RtsAPI.h - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/75d6c9918a8007de3e5835e81538e35ce022f92f...7b482ff1fb03165e627f4dff8a2a86b4c8bc0fc7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/75d6c9918a8007de3e5835e81538e35ce022f92f...7b482ff1fb03165e627f4dff8a2a86b4c8bc0fc7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/98a88ad3/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 22:18:00 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 04 Mar 2025 17:18:00 -0500 Subject: [Git][ghc/ghc][wip/backports-9.10] Partially revert "testsuite: expand size testing infrastructure" Message-ID: <67c77c18850ac_1ce619b85150833c2@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: 457055f8 by Ben Gamari at 2025-03-04T17:02:00-05:00 Partially revert "testsuite: expand size testing infrastructure" This reverts the size testing infrastructure from commit a15b3383c95864eb1ca9df4f7065ef6f6fe84393 as it has broken the testsuite. - - - - - 3 changed files: - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/tests/perf/size/all.T Changes: ===================================== testsuite/driver/testglobals.py ===================================== @@ -223,10 +223,6 @@ class TestConfig: # I have no idea what this does self.package_conf_cache_file = None # type: Optional[Path] - # the libdir for the test compiler. Set by hadrian, see - # Setting.Builders.RunTest - self.libdir = '' - # The extra hadrian dependencies we need for all configured tests self.hadrian_deps = set() # type: Set[str] ===================================== testsuite/driver/testlib.py ===================================== @@ -628,24 +628,15 @@ def collect_size ( deviation, path ): def get_dir_size(path): total = 0 - try: - with os.scandir(path) as it: - for entry in it: - if entry.is_file(): - total += entry.stat().st_size - elif entry.is_dir(): - total += get_dir_size(entry.path) - return total - except FileNotFoundError: - print("Exception: Could not find: " + path) + with os.scandir(path) as it: + for entry in it: + if entry.is_file(): + total += entry.stat().st_size + elif entry.is_dir(): + total += get_dir_size(entry.path) + return total def collect_size_dir ( deviation, path ): - - ## os.path.join joins the path with slashes (not backslashes) on windows - ## CI...for some reason, so we manually detect it here - sep = r"/" - if on_windows(): - sep = r"\\" return collect_generic_stat ( 'size', deviation, lambda way: get_dir_size(path) ) # Read a number from a specific file @@ -662,92 +653,7 @@ def collect_generic_stats ( metric_info ): return _collect_generic_stat(name, opts, metric_info) return f -# wrap the call to collect_size_dir with path_from_ghcPkg in a function. Python -# is call-by-value so if we placed the call in an all.T file then the python -# interpreter would evaluate the call to path_from_ghcPkg -def collect_size_ghc_pkg (deviation, library): - return collect_size_dir(deviation, path_from_ghcPkg(library, "library-dirs")) - -# same for collect_size and find_so -def collect_object_size (deviation, library, use_non_inplace=False): - if use_non_inplace: - return collect_size(deviation, find_non_inplace_so(library)) - else: - return collect_size(deviation, find_so(library)) - -def path_from_ghcPkg (library, field): - """Find the field as a path for a library via a call to ghc-pkg. This is a - testsuite wrapper around a call to ghc-pkg field {library} {field}. - """ - - ### example output from ghc-pkg: - ### $ ./ghc-pkg field Cabal library-dirs - ### library-dirs: /home/doyougnu/programming/haskell/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240424/Cabal-3.11.0.0-inplace - ### so we split the string and drop the 'library-dirs' - ghcPkgCmd = fr"{config.ghc_pkg} field {library} {field}" - - try: - result = subprocess.run(ghcPkgCmd, capture_output=True, shell=True) - - # check_returncode throws an exception if the return code is not 0. - result.check_returncode() - - # if we get here then the call worked and we have the path we split by - # whitespace and then return the path which becomes the second element - # in the array - return re.split(r'\s+', result.stdout.decode("utf-8"))[1] - except Exception as e: - message = f""" - Attempt to find {field} of {library} using ghc-pkg failed. - ghc-pkg path: {config.ghc_pkg} - error" {e} - """ - print(message) - - -def _find_so(lib, directory, in_place): - """Find a shared object file (.so) for lib in directory. We deliberately - keep the regex simple, just removing the ghc version and project version. - Example: - - _find_so("Cabal-syntax-3.11.0.0", path-from-ghc-pkg, True) ==> - /builds/ghc/ghc/_build/install/lib/ghc-9.11.20240410/lib/x86_64-linux-ghc-9.11.20240410/libHSCabal-syntax-3.11.0.0-inplace-ghc9.11.20240410.so - """ - - # produce the suffix for the CI operating system - suffix = "so" - if config.os == "mingw32": - suffix = "dll" - elif config.os == "darwin": - suffix = "dylib" - - # Most artfacts are of the form foo-inplace, except for the rts. - if in_place: - to_match = r'libHS{}-\d+(\.\d+)+-inplace-\S+\.' + suffix - else: - to_match = r'libHS{}-\d+(\.\d+)+\S+\.' + suffix - - matches = [] - # wrap this in some exception handling, hadrian test will error out because - # these files don't exist yet, so we pass when this occurs - try: - for f in os.listdir(directory): - if f.endswith(suffix): - pattern = re.compile(to_match.format(re.escape(lib))) - match = re.match(pattern, f) - if match: - matches.append(match.group()) - return os.path.join(directory, matches[0]) - except: - failBecause('Could not find shared object file: ' + lib) - -def find_so(lib): - return _find_so(lib,path_from_ghcPkg(lib, "dynamic-library-dirs"),True) - -def find_non_inplace_so(lib): - return _find_so(lib,path_from_ghcPkg(lib, "dynamic-library-dirs"),False) - -# Define a generic stat test, which computes the statistic by calling the function +# Define the a generic stat test, which computes the statistic by calling the function # given as the third argument. def collect_generic_stat ( metric, deviation, get_stat ): return collect_generic_stats ( { metric: { 'deviation': deviation, 'current': get_stat } } ) ===================================== testsuite/tests/perf/size/all.T ===================================== @@ -3,80 +3,4 @@ test('size_hello_obj', [collect_size(5, 'size_hello_obj.o')], compile, ['']) test('size_hello_artifact', [collect_size(5, 'size_hello_artifact' + exe_extension())], compile_artifact, ['']) -size_acceptance_threshold = 100 - -test('array_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'array')] , static_stats , [] ) -test('base_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'base')] , static_stats , [] ) -test('binary_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'binary')] , static_stats , [] ) -test('bytestring_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'bytestring')] , static_stats , [] ) -test('cabal_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'Cabal')] , static_stats , [] ) -test('cabal_syntax_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'Cabal-syntax')] , static_stats , [] ) -test('containers_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'containers')] , static_stats , [] ) -test('deepseq_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'deepseq')] , static_stats , [] ) -test('directory_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'directory')] , static_stats , [] ) -test('exceptions_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'exceptions')] , static_stats , [] ) -test('ghc_bignum_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-bignum')] , static_stats , [] ) -test('ghc_boot_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-boot')] , static_stats , [] ) -test('ghc_boot_th_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-boot-th')] , static_stats , [] ) -test('ghc_compact_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-compact')] , static_stats , [] ) -test('ghc_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc')] , static_stats , [] ) -test('ghc_experimental_dir',[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-experimental')], static_stats , [] ) -test('ghc_heap_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-heap')] , static_stats , [] ) -test('ghc_internal_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-internal')] , static_stats , [] ) -test('ghc_platform_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-platform')] , static_stats , [] ) -test('ghc_prim_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-prim')] , static_stats , [] ) -test('ghc_toolchain_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-toolchain')] , static_stats , [] ) -test('haskeline_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'haskeline')] , static_stats , [] ) -test('hpc_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'hpc')] , static_stats , [] ) -test('integer_gmp_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'integer-gmp')] , static_stats , [] ) -test('mtl_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'mtl')] , static_stats , [] ) -test('os_string_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'os-string')] , static_stats , [] ) -test('parsec_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'parsec')] , static_stats , [] ) -test('pretty_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'pretty')] , static_stats , [] ) -test('process_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'process')] , static_stats , [] ) -test('time_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'time')] , static_stats , [] ) -test('xhtml_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'xhtml')] , static_stats , [] ) - -# size of the entire libdir -test('libdir' ,[collect_size_dir(10, config.libdir)] , static_stats , [] ) - -# skip these on windows -test('unix_dir' ,[windows_skip, collect_size_ghc_pkg(size_acceptance_threshold, 'unix')] , static_stats, [] ) -test('terminfo_dir' ,[windows_skip, js_skip, collect_size_ghc_pkg(size_acceptance_threshold, 'terminfo')], static_stats, [] ) - -# skip the shared object file tests on windows -test('array_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "array")] , static_stats, [] ) -test('base_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "base")] , static_stats, [] ) -test('binary_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "binary")] , static_stats, [] ) -test('bytestring_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "bytestring")] , static_stats, [] ) -test('cabal_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "Cabal")] , static_stats, [] ) -test('cabal_syntax_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "Cabal-syntax")] , static_stats, [] ) -test('containers_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "containers")] , static_stats, [] ) -test('deepseq_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "deepseq")] , static_stats, [] ) -test('directory_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "directory")] , static_stats, [] ) -test('exceptions_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "exceptions")] , static_stats, [] ) -test('filepath_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "filepath")] , static_stats, [] ) -test('ghc_bignum_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-bignum")] , static_stats, [] ) -test('ghc_boot_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-boot")] , static_stats, [] ) -test('ghc_boot_th_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-boot-th")] , static_stats, [] ) -test('ghc_experimental_so',[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-experimental")] , static_stats, [] ) -test('ghc_heap_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-heap")] , static_stats, [] ) -test('ghc_platform_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-platform")] , static_stats, [] ) -test('ghc_prim_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-prim")] , static_stats, [] ) -test('ghc_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc")] , static_stats, [] ) -test('ghc_toolchain_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-toolchain")] , static_stats, [] ) -test('ghci_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghci")] , static_stats, [] ) -test('haskeline_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "haskeline")] , static_stats, [] ) -test('hpc_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "hpc")] , static_stats, [] ) -test('mtl_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "mtl")] , static_stats, [] ) -test('os_string_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "os-string")] , static_stats, [] ) -test('parsec_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "parsec")] , static_stats, [] ) -test('process_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "process")] , static_stats, [] ) -# Disabled as extremely unstable -#test('rts_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "rts", True)] , static_stats, [] ) -test('template_haskell_so',[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "template-haskell")] , static_stats, [] ) -test('terminfo_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "terminfo")] , static_stats, [] ) -test('text_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "text")] , static_stats, [] ) -test('time_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "time")] , static_stats, [] ) -test('transformers_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "transformers")] , static_stats, [] ) -test('xhtml_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "xhtml")] , static_stats, [] ) +test('libdir',[collect_size_dir(10, config.libdir)], static_stats, [] ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/457055f8a746191acea5537f737cbd459a6acd5e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/457055f8a746191acea5537f737cbd459a6acd5e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/8bfac929/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 22:19:37 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 04 Mar 2025 17:19:37 -0500 Subject: [Git][ghc/ghc][wip/T25647] enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging Message-ID: <67c77c798a328_1ce619769da08622a@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: d8258877 by Patrick at 2025-03-05T06:19:27+08:00 enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging - - - - - 3 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -3409,9 +3409,10 @@ without treating the explicitly-quantified ones specially. Wrinkles: In step 1 we do /not/ want to get newtype instance forall r . Fix2 (f :: TYPE r -> TYPE r) :: TYPE r where If we do, we'll get that same "newtype must not be GADT" error as for N above. - Rather, we want to default the RuntimeRep variable r := LiftedRep. The key thing - is that we must make the /same/ choice here as we do in kind-checking the data - constructor's type. + Rather, we want to default the RuntimeRep variable r := LiftedRep. See the call + to `quantifyTyVars` in `tcDataFamInstHeader`. The key thing is that we must make + the /same/ choice here as we do in kind-checking the data constructor's type + in `kindGeneralizeAll` in `tcConDecl`. See also Note [Re-quantify type variables in rules] in GHC.Tc.Gen.Rule, which explains a /very/ similar design when generalising over the type of a rewrite @@ -4034,10 +4035,10 @@ tcConArg :: ConArgKind -- expected kind for args; always OpenKind for datatype -- but might be an unlifted type with UnliftedNewtypes -> HsScaled GhcRn (LHsType GhcRn) -> TcM (Scaled TcType, HsSrcBang) tcConArg exp_kind (HsScaled w bty) - = do { traceTc "tcConArg 1" (ppr bty) + = do { traceTc "tcConArg 1: " (ppr bty <+> ppr exp_kind) ; arg_ty <- tcCheckLHsTypeInContext (getBangType bty) exp_kind ; w' <- tcDataConMult w - ; traceTc "tcConArg 2" (ppr bty) + ; traceTc "tcConArg 2: " (ppr bty <+> ppr arg_ty) ; return (Scaled w' arg_ty, getBangStrictness bty) } tcRecConDeclFields :: ConArgKind ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -977,6 +977,8 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] ; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty ; qtvs <- quantifyTyVars skol_info dvs + -- Have to make a same defaulting choice for reuslt kind here + -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -827,7 +827,7 @@ cloneAnonMetaTyVar info tv kind = do { details <- newMetaDetails info ; name <- cloneMetaTyVarName (tyVarName tv) ; let tyvar = mkTcTyVar name kind details - ; traceTc "cloneAnonMetaTyVar" (ppr tyvar <+> dcolon <+> ppr (tyVarKind tyvar)) + ; traceTc "cloneAnonMetaTyVar" (ppr tyvar <+> dcolon <+> ppr (tyVarKind tyvar) <+> text "from" <+> ppr tv) ; return tyvar } -- Make a new CycleBreakerTv. See Note [Type equality cycles] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d82588777cc57efd47036da3568197616cf07908 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d82588777cc57efd47036da3568197616cf07908 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/ac8ee0d0/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 4 22:27:17 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 17:27:17 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: perf: Speed up the bytecode assembler Message-ID: <67c77e45d15f0_1ce619769da09092c@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: f8b4ade2 by Matthew Pickering at 2025-03-04T17:27:00-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2c16da6 by Ben Gamari at 2025-03-04T17:27:00-05:00 testsuite: Add testcase for #25577 - - - - - 0061d3f5 by Ben Gamari at 2025-03-04T17:27:00-05:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - aa34fda5 by Ben Gamari at 2025-03-04T17:27:00-05:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - c9ed22aa by Ben Gamari at 2025-03-04T17:27:00-05:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 5c89d2bf by Teo Camarasu at 2025-03-04T17:27:01-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 5ad28381 by Teo Camarasu at 2025-03-04T17:27:01-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - 7d09d27a by Brandon Chinn at 2025-03-04T17:27:03-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 36fb03e2 by Cheng Shao at 2025-03-04T17:27:04-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 8998ad8c by Cheng Shao at 2025-03-04T17:27:04-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 584c54ee by Cheng Shao at 2025-03-04T17:27:04-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - fe95b4c6 by Matthew Pickering at 2025-03-04T17:27:04-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 59 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/94f008346075970901359d5fb713958ea4006ede...fe95b4c6e630e4307600cbb249aac52fb2dc3def -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/94f008346075970901359d5fb713958ea4006ede...fe95b4c6e630e4307600cbb249aac52fb2dc3def You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/02ed5e96/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 00:33:10 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 04 Mar 2025 19:33:10 -0500 Subject: [Git][ghc/ghc][wip/T25647] Ensure wildcard behave correctly Message-ID: <67c79bc62fb27_2102c4a45f74258d6@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 6687b241 by Patrick at 2025-03-05T08:32:59+08:00 Ensure wildcard behave correctly - - - - - 3 changed files: - compiler/GHC/Tc/Gen/HsType.hs - + testsuite/tests/typecheck/should_compile/T25647c.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -888,7 +888,7 @@ tcInferLHsTypeUnsaturated hs_ty ; case splitHsAppTys_maybe (unLoc hs_ty) of Just (hs_fun_ty, hs_args) -> do { (fun_ty, _ki) <- tcInferTyAppHead mode hs_fun_ty - ; tcInferTyApps_nosat mode hs_fun_ty fun_ty hs_args (cycle [FreeArg])} + ; tcInferTyApps_nosat mode hs_fun_ty fun_ty hs_args (cycle [tcTyModeFamArgFlavour mode])} -- Notice the 'nosat'; do not instantiate trailing -- invisible arguments of a type family. -- See Note [Dealing with :kind] @@ -1286,6 +1286,7 @@ tcHsType mode rn_ty@(HsOpTy{}) exp_kind = tc_app_ty mode rn_ty exp_kind tcHsType mode rn_ty@(HsKindSig _ ty sig) exp_kind = do { let mode' = (updateFamArgFlavour SigArg $ mode { mode_tyki = KindLevel}) + ; traceTc "tcHsType:sig0" (ppr ty <+> ppr (mode_holes mode')) ; sig' <- tc_lhs_kind_sig mode' KindSigCtxt sig -- We must typecheck the kind signature, and solve all -- its equalities etc; from this point on we may do @@ -1555,7 +1556,7 @@ tc_app_ty :: TcTyMode -> HsType GhcRn -> ExpKind -> TcM TcType tc_app_ty mode rn_ty exp_kind = do { (fun_ty, _ki) <- tcInferTyAppHead mode hs_fun_ty ; (ty, infered_kind) <- tcInferTyApps mode hs_fun_ty fun_ty - hs_args (cycle [FreeArg]) + hs_args (cycle [tcTyModeFamArgFlavour mode]) ; checkExpKind rn_ty ty infered_kind exp_kind } where (hs_fun_ty, hs_args) = splitHsAppTys rn_ty @@ -1610,7 +1611,7 @@ tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args fam_arg_flvs -> Subst -- Applies to function kind -> TcKind -- Function kind -> [LHsTypeArg GhcRn] -- Un-type-checked args - -> [FamArgFlavour] -- Un-type-checked args + -> [FamArgFlavour] -- Flavours of the args see Note [FamArgFlavour] -> TcM (TcType, TcKind) -- Result type and its kind -- INVARIANT: in any call (go n fun subst fun_ki args) -- typeKind fun = subst(fun_ki) @@ -1623,7 +1624,7 @@ tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args fam_arg_flvs -- is apply 'fun' to an argument type. -- Dispatch on all_args first, for performance reasons - go n fun subst fun_ki all_args [] = error "tcInferTyApps_nosat: empty all_args" + go _ _ _ _ _ [] = error "tcInferTyApps: FamArgFlavour should be infinite" go n fun subst fun_ki all_args arg_flvs@(arg_flv:rest_arg_flvs) = case (all_args, tcSplitPiTy_maybe fun_ki) of ---------------- No user-written args left. We're done! ([], _) -> return (fun, substTy subst fun_ki) @@ -2241,7 +2242,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) } wc_kind = mkTyVarTy kv wc_tv = mkTcTyVar wc_name wc_kind wc_details - ; traceTc "tcAnonWildCardOcc" (ppr hole_lvl <+> ppr emit_holes) + ; traceTc "tcAnonWildCardOcc" (ppr hole_lvl <+> ppr emit_holes <+> ppr hole_mode) ; when emit_holes $ emitAnonTypeHole is_extra wc_tv -- Why the 'when' guard? ===================================== testsuite/tests/typecheck/should_compile/T25647c.hs ===================================== @@ -0,0 +1,71 @@ +{-# LANGUAGE DataKinds, TypeFamilies, PolyKinds, MagicHash #-} +{-# LANGUAGE AllowAmbiguousTypes #-} + +module T25647c where + +import GHC.Exts +import Data.Kind + +-- testing the behavior of anonymous wildcards in type family instances + +-- class position wildcard matching an non-type variable +-- free position wildcard in the type family instance +class CW2 a b where + type TW2 a b c + fun2 :: TW2 a b c -> Int +instance CW2 Int Int where + type TW2 _ Int _ = Int + fun2 :: TW2 Int Int Int -> Int + fun2 _ = 1 + +-- class wildcard matching an type variable +class CW5 a b where + type TW5 a b + fun5 :: TW5 a b -> Int +instance CW5 a Int where + type TW5 _ Int = Int + fun5 :: TW5 a Int -> Int + fun5 _ = 1 + +-- class position signature wildcard matching non-type variable +class CW3 (a :: RuntimeRep) b where + type TW3 (b :: TYPE a) + fun3 :: TW3 b -> Int +instance CW3 'IntRep Int# where + type TW3 (_ :: _) = Int + fun3 :: TW3 Int# -> Int + fun3 _ = 1 + +-- free wildcard, class wildcard, both position signature wildcard +class CW4 b where + type TW4 a b + fun4 :: TW4 a b -> TW4 d b -> Int +instance CW4 Int# where + type TW4 (_ :: _) (_ :: _) = Int + fun4 :: Int -> Int -> Int + fun4 1 _ = 1 + +-- class position wildcard matching type variable +-- class position signature wildcard matching type variable +-- free position signature wildcard +class CW7 (a :: RuntimeRep) b where + type TW7 (b :: TYPE a) (c :: RuntimeRep) (d::TYPE c) + fun7 :: TW7 b c d-> Int + funa7 :: TW7 b c d -> Int +instance CW7 aa bb where + type TW7 (_::TYPE _) _ _ = Int + funa7 :: TW7 Int 'IntRep d -> Int + funa7 _ = 1 + fun7 :: TW7 Int# LiftedRep d -> Int + fun7 _ = 1 + +-- class position wildcard matching non-type-variable +-- class position signature wildcard matching non-type-variable +-- free position signature wildcard +class CW8 (a :: RuntimeRep) b where + type TW8 (b :: TYPE a) (c :: RuntimeRep) (d::TYPE c) + fun8 :: TW8 b c d -> Int +instance CW8 'IntRep Int# where + type TW8 (_::TYPE _) _ _ = Int + fun8 :: TW8 Int# LiftedRep Int -> Int + fun8 _ = 1 ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -935,5 +935,6 @@ test('T25266b', normal, compile, ['']) test('T25597', normal, compile, ['']) test('T25647a', normal, compile, ['']) test('T25647b', normal, compile, ['']) +test('T25647c', normal, compile, ['']) test('T25647_fail', normal, compile_fail, ['']) test('T25725', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6687b241a745e3892849ce5e648cbd2543281cca -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6687b241a745e3892849ce5e648cbd2543281cca You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/e830d8c1/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 00:35:26 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 04 Mar 2025 19:35:26 -0500 Subject: [Git][ghc/ghc][wip/T25647] Revert "update ExplicitForAllFams4b" Message-ID: <67c79c4e4424a_2102c4b3634826674@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 779e90e3 by Patrick at 2025-03-05T08:35:08+08:00 Revert "update ExplicitForAllFams4b" This reverts commit 90a2858278668bc6ad66ef43a5651808d8f24a0f. - - - - - 1 changed file: - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr Changes: ===================================== testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr ===================================== @@ -56,11 +56,6 @@ ExplicitForAllFams4b.hs:24:17: error: [GHC-30337] • In the associated type family instance declaration for ‘CT’ In the instance declaration for ‘C Int’ -ExplicitForAllFams4b.hs:24:20: error: [GHC-34447] - Conflicting family instance declarations: - CT [a] (a, a) = Float -- Defined at ExplicitForAllFams4b.hs:24:20 - CT _ _ = Bool -- Defined at ExplicitForAllFams4b.hs:32:18 - ExplicitForAllFams4b.hs:25:3: error: [GHC-95424] • Type indexes must match class instance head Expected: CD Int _ @@ -74,67 +69,24 @@ ExplicitForAllFams4b.hs:25:17: error: [GHC-30337] • In the associated data family instance declaration for ‘CD’ In the instance declaration for ‘C Int’ -ExplicitForAllFams4b.hs:25:20: error: [GHC-34447] - Conflicting family instance declarations: - CD [a] (a, a) -- Defined at ExplicitForAllFams4b.hs:25:20 - CD _ _ -- Defined at ExplicitForAllFams4b.hs:33:18 - -ExplicitForAllFams4b.hs:28:3: error: [GHC-95424] - • Type indexes must match class instance head - Expected: CT Bool _ - Actual: CT _ _ - • In the associated type family instance declaration for ‘CT’ - In the instance declaration for ‘C Bool’ - ExplicitForAllFams4b.hs:28:15: error: [GHC-30337] • The type variable ‘b’ is bound by a forall, but does not appear in any of the LHS patterns of the family instance. • In the associated type family instance declaration for ‘CT’ In the instance declaration for ‘C Bool’ -ExplicitForAllFams4b.hs:28:20: error: [GHC-34447] - Conflicting family instance declarations: - CT _ _ = Maybe b -- Defined at ExplicitForAllFams4b.hs:28:20 - CT _ _ = Bool -- Defined at ExplicitForAllFams4b.hs:32:18 - -ExplicitForAllFams4b.hs:29:3: error: [GHC-95424] - • Type indexes must match class instance head - Expected: CD Bool _ - Actual: CD _ _ - • In the associated data family instance declaration for ‘CD’ - In the instance declaration for ‘C Bool’ - ExplicitForAllFams4b.hs:29:15: error: [GHC-30337] • The type variable ‘b’ is bound by a forall, but does not appear in any of the LHS patterns of the family instance. • In the associated data family instance declaration for ‘CD’ In the instance declaration for ‘C Bool’ -ExplicitForAllFams4b.hs:29:20: error: [GHC-34447] - Conflicting family instance declarations: - CD _ _ -- Defined at ExplicitForAllFams4b.hs:29:20 - CD _ _ -- Defined at ExplicitForAllFams4b.hs:33:18 - -ExplicitForAllFams4b.hs:32:3: error: [GHC-95424] - • Type indexes must match class instance head - Expected: CT Double _ - Actual: CT _ _ - • In the associated type family instance declaration for ‘CT’ - In the instance declaration for ‘C Double’ - ExplicitForAllFams4b.hs:32:15: error: [GHC-30337] • The type variable ‘b’ is bound by a forall, but it isn't used in the family instance. • In the associated type family instance declaration for ‘CT’ In the instance declaration for ‘C Double’ -ExplicitForAllFams4b.hs:33:3: error: [GHC-95424] - • Type indexes must match class instance head - Expected: CD Double _ - Actual: CD _ _ - • In the associated data family instance declaration for ‘CD’ - In the instance declaration for ‘C Double’ - ExplicitForAllFams4b.hs:33:15: error: [GHC-30337] • The type variable ‘b’ is bound by a forall, but does not appear in any of the LHS patterns of the family instance. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/779e90e30c580f56a296eb23a983a10a8ead463d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/779e90e30c580f56a296eb23a983a10a8ead463d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/dea45214/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 01:57:29 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 04 Mar 2025 20:57:29 -0500 Subject: [Git][ghc/ghc][wip/T25647] Add detailed notes on wildcard handling in type families and refine related documentation Message-ID: <67c7af89bd23_2102c413c61fc2765@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 571d1b49 by Patrick at 2025-03-05T09:57:19+08:00 Add detailed notes on wildcard handling in type families and refine related documentation - - - - - 2 changed files: - compiler/GHC/Core/TyCon.hs - compiler/GHC/Tc/Gen/HsType.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2979,6 +2979,36 @@ tyConSkolem = isHoleName . tyConName -- not whether it is abstract or not. +{- Note [WildCard in type families] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Wildcards in type families are used to represent type/kind information that +are not specified by the user. It is controversial how to interpret wildcards +in type families. Hence We classify kinds of wildcards in type families into +three categories represented by the FamArgFlavour data type: ClassArg, FreeArg, +and SigArg, see Note [FamArgFlavour] for more detail. This flexibility allows +us to flip the interpretation of wildcards in type families. + +Some common agreements: + +* Wildcards should be not defaulted. + +* For `ClassArg`, it should be able to represent atleast arbitrary type variables, it is + used in our codebase. + + instance (HasDefaultDiagnosticOpts opts, Outputable hint) => Diagnostic (UnknownDiagnostic opts hint) where + type DiagnosticOpts (UnknownDiagnostic opts _) = opts + type DiagnosticHint (UnknownDiagnostic _ hint) = hint + +* For `SigArg`, it should be able to represent atleast arbitrary type variables. + +We have two design choices: +1. Wildcards can represet arbitrary types, including type variables. +2. Wildcards can only represent type variables. + +... todo add more + +For more discussion, see #13908. +-} {- Note [FamArgFlavour] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2995,7 +3025,8 @@ We can conceptually view the kinds of arguments for a type family as a famArgFla with one flavour per argument of the family. Each flavour indicates whether the corresponding argument is a ClassArg or a FreeArg. We also introduce a third flavour, SigArg, to flag arguments that appear only in a kind signature for a type instance (i.e. when -a wildcard is provided along with a kind annotation, as in @(_ :: _)@). +a wildcard is provided along with a kind annotation, as in @(_ :: _)@). See [More on SigArg] +Session. Under the current design, when type-checking an instance the interpretation of wildcards depends on their position: @@ -3014,9 +3045,19 @@ argument and a signature argument) would produce TauTv's. This design provides flexibility in handling wildcards in type families. -Side note: -we maintain diffirent flavours between class arguments and signature arguments because -we might want to be able to flip only the class arguments to use TyVarTv without affecting +[More on SigArg] +Example from T14366 + +type family F (a :: Type) :: Type where + F (a :: _) = a + +Imagine without SigArg, since F is non-associated, every argument is freeVar, +now let's consider _ here as a freeVar then TyVarTv, then it would not match Type. +Say if we assign ClassArg to _ here, if we want to flip class arguments in associated +type family to only match Type variables. Then this example would not work. + +Hence we maintain diffirent flavours between class arguments and signature arguments +because we want to be able to flip only the true class arguments without affecting the signature arguments. For more discussion, see #13908. ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -1294,7 +1294,7 @@ tcHsType mode rn_ty@(HsKindSig _ ty sig) exp_kind -- to be fully determined (#14904) ; traceTc "tcHsType:sig" (ppr ty $$ ppr sig') ; ty' <- tcAddKindSigPlaceholders sig $ - tc_check_lhs_type mode ty sig' + tc_check_lhs_type mode' ty sig' ; checkExpKind rn_ty ty' sig' exp_kind } -- See Note [Typechecking HsCoreTys] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/571d1b498453d618bb817a02c15d2fba207e095f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/571d1b498453d618bb817a02c15d2fba207e095f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/53fee368/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 02:45:47 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 04 Mar 2025 21:45:47 -0500 Subject: [Git][ghc/ghc][wip/T25647] Refine documentation on wildcard handling in type families and clarify design... Message-ID: <67c7badbf1b64_2102c41ac6b8c290b@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 4e87344b by Patrick at 2025-03-05T10:45:34+08:00 Refine documentation on wildcard handling in type families and clarify design choices for FamArgFlavour - - - - - 1 changed file: - compiler/GHC/Core/TyCon.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2985,27 +2985,31 @@ Wildcards in type families are used to represent type/kind information that are not specified by the user. It is controversial how to interpret wildcards in type families. Hence We classify kinds of wildcards in type families into three categories represented by the FamArgFlavour data type: ClassArg, FreeArg, -and SigArg, see Note [FamArgFlavour] for more detail. This flexibility allows +and SigArg, see Note [FamArgFlavour] for more detail. This flexibility allows us to flip the interpretation of wildcards in type families. Some common agreements: -* Wildcards should be not defaulted. +* FreeArg wildcards should be not defaulted. -* For `ClassArg`, it should be able to represent atleast arbitrary type variables, it is +* For `ClassArg`, it should be able to represent at least arbitrary type variables, it is used in our codebase. instance (HasDefaultDiagnosticOpts opts, Outputable hint) => Diagnostic (UnknownDiagnostic opts hint) where type DiagnosticOpts (UnknownDiagnostic opts _) = opts type DiagnosticHint (UnknownDiagnostic _ hint) = hint -* For `SigArg`, it should be able to represent atleast arbitrary type variables. +By picking different type var for different flavours of wildcards in `tcAnonWildCardOcc`, we can +explore different design spaces. For example, we can have the following design spaces: +1. Wildcards can represet arbitrary types, including type variables, picks TauTv. +2. Wildcards can only represent type variables, picks TyVarTv. +3. Wildcards stand alone, pick skolemTv variables. +... and so on. -We have two design choices: -1. Wildcards can represet arbitrary types, including type variables. -2. Wildcards can only represent type variables. - -... todo add more +Maintaining backward compatibility, the current picks: +- TyVarTv for FreeArg +- TauTv for ClassArg +- TauTv for SigArg For more discussion, see #13908. -} @@ -3043,22 +3047,19 @@ For instance, for an instance declaration like the first two underscores (free arguments) would yield TyVarTv’s while the last two underscores (a class argument and a signature argument) would produce TauTv's. -This design provides flexibility in handling wildcards in type families. - [More on SigArg] Example from T14366 type family F (a :: Type) :: Type where F (a :: _) = a -Imagine without SigArg, since F is non-associated, every argument is freeVar, -now let's consider _ here as a freeVar then TyVarTv, then it would not match Type. +Imagine without SigArg, since F is non-associated, every argument is FreeArg, +now let's consider _ here as a FreeArg then TyVarTv, then it would not match Type. Say if we assign ClassArg to _ here, if we want to flip class arguments in associated type family to only match Type variables. Then this example would not work. -Hence we maintain diffirent flavours between class arguments and signature arguments -because we want to be able to flip only the true class arguments without affecting -the signature arguments. +Hence we maintain three different flavours of wildcards in type families. This provides +a flexibility to interpret wildcards in type families. For more discussion, see #13908. -} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e87344bac87bf9350453c222ab670a32ed24815 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e87344bac87bf9350453c222ab670a32ed24815 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/41f61c4d/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 02:54:58 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 04 Mar 2025 21:54:58 -0500 Subject: [Git][ghc/ghc][wip/T25647] Fix typos in documentation regarding wildcards in type families and clarify references Message-ID: <67c7bd0255e1e_2102c41ec7ce0300e9@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 92ce46e4 by Patrick at 2025-03-05T10:54:49+08:00 Fix typos in documentation regarding wildcards in type families and clarify references - - - - - 2 changed files: - compiler/GHC/Core/TyCon.hs - compiler/GHC/Tc/Gen/HsType.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2979,7 +2979,7 @@ tyConSkolem = isHoleName . tyConName -- not whether it is abstract or not. -{- Note [WildCard in type families] +{- Note [WildCards in type families] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Wildcards in type families are used to represent type/kind information that are not specified by the user. It is controversial how to interpret wildcards @@ -3006,11 +3006,14 @@ explore different design spaces. For example, we can have the following design s 3. Wildcards stand alone, pick skolemTv variables. ... and so on. -Maintaining backward compatibility, the current picks: +Maintaining backward compatibility from 8.6.4 to 9.10.2, the picks would be: - TyVarTv for FreeArg - TauTv for ClassArg - TauTv for SigArg +See <More on SigArg> session in Note [FamArgFlavour] for why not just merge SigArg +and ClassArg. + For more discussion, see #13908. -} @@ -3029,7 +3032,7 @@ We can conceptually view the kinds of arguments for a type family as a famArgFla with one flavour per argument of the family. Each flavour indicates whether the corresponding argument is a ClassArg or a FreeArg. We also introduce a third flavour, SigArg, to flag arguments that appear only in a kind signature for a type instance (i.e. when -a wildcard is provided along with a kind annotation, as in @(_ :: _)@). See [More on SigArg] +a wildcard is provided along with a kind annotation, as in @(_ :: _)@). See <More on SigArg> Session. Under the current design, when type-checking an instance the interpretation of wildcards @@ -3047,7 +3050,7 @@ For instance, for an instance declaration like the first two underscores (free arguments) would yield TyVarTv’s while the last two underscores (a class argument and a signature argument) would produce TauTv's. -[More on SigArg] +<More on SigArg> Example from T14366 type family F (a :: Type) :: Type where ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -2265,6 +2265,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) } HM_FamPat ClassArg -> newTauTvDetailsAtLevel HM_FamPat SigArg -> newTauTvDetailsAtLevel _ -> newTauTvDetailsAtLevel + -- see Note [WildCards in type families] emit_holes = case hole_mode of HM_Sig -> True HM_FamPat _ -> False View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92ce46e4a64611465a19698fd77dab15bfda64a3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92ce46e4a64611465a19698fd77dab15bfda64a3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/dd33f490/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 04:38:08 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Mar 2025 23:38:08 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: perf: Speed up the bytecode assembler Message-ID: <67c7d53083520_2a106d4ef2506627f@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 87459cbc by Matthew Pickering at 2025-03-04T23:37:47-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - 26ee501b by Teo Camarasu at 2025-03-04T23:37:48-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - aa44b84b by Teo Camarasu at 2025-03-04T23:37:48-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - 050b0a2a by Brandon Chinn at 2025-03-04T23:37:50-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - e27bf031 by Cheng Shao at 2025-03-04T23:37:51-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - a081c862 by Cheng Shao at 2025-03-04T23:37:51-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - a7a48d21 by Cheng Shao at 2025-03-04T23:37:51-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 08423465 by Matthew Pickering at 2025-03-04T23:37:51-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - fa358306 by Rodrigo Mesquita at 2025-03-04T23:37:52-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - 55 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - docs/users_guide/ghci.rst - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/wasm/JSFFI.c - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe95b4c6e630e4307600cbb249aac52fb2dc3def...fa358306e0ea578577c7113ac68614b4a479ab00 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe95b4c6e630e4307600cbb249aac52fb2dc3def...fa358306e0ea578577c7113ac68614b4a479ab00 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250304/8aa64390/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 08:53:32 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 05 Mar 2025 03:53:32 -0500 Subject: [Git][ghc/ghc][wip/compress-iface] fix Message-ID: <67c8110c71823_31e0ba61ffe4575c1@gitlab.mail> Matthew Pickering pushed to branch wip/compress-iface at Glasgow Haskell Compiler / GHC Commits: 41bd0c91 by Matthew Pickering at 2025-03-05T08:53:22+00:00 fix - - - - - 1 changed file: - compiler/GHC/Utils/Compress.hs Changes: ===================================== compiler/GHC/Utils/Compress.hs ===================================== @@ -60,8 +60,6 @@ decompress (BSI.PS srcForeignPtr off len) = unsafePerformIO $ do decompressPtr srcForeignPtr srcSize = do withForeignPtr srcForeignPtr $ \srcPtr -> do decompressedSizeM <- getDecompressedSize srcPtr (fromIntegral srcSize) - print decompressedSizeM - printFirstBytes srcPtr case decompressedSizeM of Nothing -> error "Decompression failed" Just decompressedSize -> do View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/41bd0c91d0fb6345fa780e95d55255f157f9fc05 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/41bd0c91d0fb6345fa780e95d55255f157f9fc05 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/4c5016ee/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 09:25:44 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 05 Mar 2025 04:25:44 -0500 Subject: [Git][ghc/ghc][wip/22188] 2 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67c818982eb75_343add37a0b4142f9@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: ab5119db by Matthew Pickering at 2025-03-05T09:24:09+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-self-recomp-info which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 782f4603 by Matthew Pickering at 2025-03-05T09:24:42+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 28 changed files: - compiler/GHC.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -104,10 +104,8 @@ module GHC ( mi_module, mi_sig_of, mi_hsc_src, - mi_src_hash, mi_hi_bytes, mi_deps, - mi_usages, mi_exports, mi_used_th, mi_fixities, ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1178,7 +1178,8 @@ defaultFlags settings Opt_ShowErrorContext, Opt_SuppressStgReps, Opt_UnoptimizedCoreForInterpreter, - Opt_SpecialiseIncoherents + Opt_SpecialiseIncoherents, + Opt_WriteSelfRecompInfo ] ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns] ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -692,6 +692,7 @@ data GeneralFlag | Opt_ExposeOverloadedUnfoldings | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code + | Opt_WriteSelfRecompInfo | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1243,11 +1243,11 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h (cg_guts, details) <- liftIO $ hscTidy hsc_env simplified_guts - let !partial_iface = + !partial_iface <- liftIO $ {-# SCC "GHC.Driver.Main.mkPartialIface" #-} -- This `force` saves 2M residency in test T10370 -- See Note [Avoiding space leaks in toIface*] for details. - force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) + fmap force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) return HscRecomp { hscs_guts = cg_guts, hscs_mod_location = ms_location summary, ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -875,10 +875,10 @@ pruneCache hpt summ modl = miKey iface linkable' | Just ms <- M.lookup modl ms_map - , mi_src_hash iface /= ms_hs_hash ms - = emptyHomeModInfoLinkable - | otherwise + , mi_src_hash iface == Just (ms_hs_hash ms) = linkable + | otherwise + = emptyHomeModInfoLinkable -- Using UFM Module is safe for determinism because the map is just used for a transient lookup. The cache should be unique and a key clash is an error. ms_map = M.fromListWith ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,6 +2528,7 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, + flagSpec "write-if-self-recomp" Opt_WriteSelfRecompInfo, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -22,14 +22,12 @@ import GHC.Driver.DynFlags import GHC.Driver.Config import GHC.Driver.Config.Core.Lint ( endPassHscEnvIO ) import GHC.Driver.Config.HsToCore.Ticks -import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env import GHC.Driver.Backend import GHC.Driver.Plugins import GHC.Hs -import GHC.HsToCore.Usage import GHC.HsToCore.Monad import GHC.HsToCore.Errors.Types import GHC.HsToCore.Expr @@ -42,7 +40,7 @@ import GHC.HsToCore.Docs import GHC.Tc.Types import GHC.Tc.Types.Origin ( Position(..) ) -import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceLoad ) +import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances ) import GHC.Tc.Module ( runTcInteractive ) import GHC.Core.Type @@ -100,6 +98,7 @@ import GHC.Unit.Module.Deps import Data.List (partition) import Data.IORef import Data.Traversable (for) +import GHC.Iface.Make (mkRecompUsageInfo) {- ************************************************************************ @@ -127,12 +126,10 @@ deSugar hsc_env tcg_fix_env = fix_env, tcg_inst_env = inst_env, tcg_fam_inst_env = fam_inst_env, - tcg_merged = merged, tcg_warns = warns, tcg_anns = anns, tcg_binds = binds, tcg_imp_specs = imp_specs, - tcg_dependent_files = dependent_files, tcg_ev_binds = ev_binds, tcg_th_foreign_files = th_foreign_files_var, tcg_fords = fords, @@ -228,8 +225,7 @@ deSugar hsc_env ; endPassHscEnvIO hsc_env name_ppr_ctx CoreDesugarOpt ds_binds ds_rules_for_imps - ; let used_names = mkUsedNames tcg_env - pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) + ; let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) home_unit = hsc_home_unit hsc_env ; let deps = mkDependencies home_unit (tcg_mod tcg_env) @@ -237,17 +233,10 @@ deSugar hsc_env (map mi_module pluginModules) ; used_th <- readIORef tc_splice_used - ; dep_files <- readIORef dependent_files ; safe_mode <- finalSafeMode dflags tcg_env - ; (needed_mods, needed_pkgs) <- readIORef (tcg_th_needed_deps tcg_env) - - ; let uc = initUsageConfig hsc_env - ; let plugins = hsc_plugins hsc_env - ; let fc = hsc_FC hsc_env - ; let unit_env = hsc_unit_env hsc_env - ; usages <- initIfaceLoad hsc_env $ - mkUsageInfo uc plugins fc unit_env mod (imp_mods imports) used_names - dep_files merged needed_mods needed_pkgs + + ; usages <- mkRecompUsageInfo hsc_env tcg_env + -- id_mod /= mod when we are processing an hsig, but hsigs -- never desugared and compiled (there's no code!) -- Consequently, this should hold for any ModGuts that make ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -49,7 +49,6 @@ import GHC.Types.Name.Cache import GHC.Types.SrcLoc import GHC.Platform import GHC.Settings.Constants -import GHC.Utils.Fingerprint import GHC.Iface.Type (IfaceType(..), getIfaceType, putIfaceType, ifaceTypeSharedByte) import Control.Monad @@ -114,7 +113,7 @@ readBinIfaceHeader -> CheckHiWay -> TraceBinIFace -> FilePath - -> IO (Fingerprint, ReadBinHandle) + -> IO ReadBinHandle readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do let platform = profilePlatform profile @@ -156,8 +155,7 @@ readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do when (checkHiWay == CheckHiWay) $ errorOnMismatch "mismatched interface file profile tag" tag check_tag - src_hash <- get bh - pure (src_hash, bh) + pure bh -- | Read an interface file. -- @@ -170,12 +168,11 @@ readBinIface -> FilePath -> IO ModIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do - (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path + bh <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path mod_iface <- getIfaceWithExtFields name_cache bh return $ mod_iface - & addSourceFingerprint src_hash getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface @@ -259,7 +256,6 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh (show hiVersion) let tag = profileBuildTag profile put_ bh tag - put_ bh (mi_src_hash mod_iface) putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1259,21 +1259,25 @@ pprModIfaceSimple unit_state iface = -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc pprModIface unit_state iface - = vcat [ text "interface" + = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) + <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash exts)) , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) + , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat + [ nest 2 (text "src_hash:" <+> ppr src) + , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "opt_hash:" <+> ppr opt_hash) + , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) + , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) + , vcat (map pprUsage usages) + ] , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) - , nest 2 (text "flag hash:" <+> ppr (mi_flag_hash exts)) - , nest 2 (text "opt_hash:" <+> ppr (mi_opt_hash exts)) - , nest 2 (text "hpc_hash:" <+> ppr (mi_hpc_hash exts)) - , nest 2 (text "plugin_hash:" <+> ppr (mi_plugin_hash exts)) - , nest 2 (text "src_hash:" <+> ppr (mi_src_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "used TH splices:" <+> ppr (mi_used_th iface)) , nest 2 (text "where") @@ -1282,7 +1286,6 @@ pprModIface unit_state iface , text "defaults:" , nest 2 (vcat (map ppr (mi_defaults iface))) , pprDeps unit_state (mi_deps iface) - , vcat (map pprUsage (mi_usages iface)) , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] @@ -1302,6 +1305,7 @@ pprModIface unit_state iface ] where exts = mi_final_exts iface + pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -13,6 +13,7 @@ module GHC.Iface.Make ( mkPartialIface , mkFullIface , mkIfaceTc + , mkRecompUsageInfo , mkIfaceExports ) where @@ -110,7 +111,7 @@ mkPartialIface :: HscEnv -> ModSummary -> [ImportUserSpec] -> ModGuts - -> PartialModIface + -> IO PartialModIface mkPartialIface hsc_env core_prog mod_details mod_summary import_decls ModGuts{ mg_module = this_mod , mg_hsc_src = hsc_src @@ -125,8 +126,10 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_trust_pkg = self_trust , mg_docs = docs } - = mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust - safe_mode usages docs mod_summary mod_details + = do + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages + return $ mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust + safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code -- generator produced information. @@ -181,9 +184,8 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = restoreFromOldModIface mi res - forceModIface resiface - return resiface + forceModIface res + return res -- | Initial ram buffer to allocate for writing interface files. initBinMemSize :: Int @@ -236,14 +238,11 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_merged = merged, tcg_warns = warns, tcg_hpc = other_hpc_info, - tcg_th_splice_used = tc_splice_used, - tcg_dependent_files = dependent_files + tcg_th_splice_used = tc_splice_used } = do - let used_names = mkUsedNames tc_result let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) let home_unit = hsc_home_unit hsc_env let deps = mkDependencies home_unit @@ -252,48 +251,59 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (map mi_module pluginModules) let hpc_info = emptyHpcInfo other_hpc_info used_th <- readIORef tc_splice_used - dep_files <- (readIORef dependent_files) - (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) - let uc = initUsageConfig hsc_env - plugins = hsc_plugins hsc_env - fc = hsc_FC hsc_env - unit_env = hsc_unit_env hsc_env - -- Do NOT use semantic module here; this_mod in mkUsageInfo - -- is used solely to decide if we should record a dependency - -- or not. When we instantiate a signature, the semantic - -- module is something we want to record dependencies for, - -- but if you pass that in here, we'll decide it's the local - -- module and does not need to be recorded as a dependency. - -- See Note [Identity versus semantic module] - usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env this_mod (imp_mods imports) used_names - dep_files merged needed_links needed_pkgs + usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usage let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info - (imp_trust_own_pkg imports) safe_mode usages - docs mod_summary + (imp_trust_own_pkg imports) safe_mode self_recomp + docs mod_details mkFullIface hsc_env partial_iface Nothing Nothing NoStubs [] +mkRecompUsageInfo :: HscEnv -> TcGblEnv -> IO (Maybe [Usage]) +mkRecompUsageInfo hsc_env tc_result = do + let dflags = hsc_dflags hsc_env + if not (gopt Opt_WriteSelfRecompInfo dflags) + then return Nothing + else do + let used_names = mkUsedNames tc_result + dep_files <- (readIORef (tcg_dependent_files tc_result)) + (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) + let uc = initUsageConfig hsc_env + plugins = hsc_plugins hsc_env + fc = hsc_FC hsc_env + unit_env = hsc_unit_env hsc_env + + -- Do NOT use semantic module here; this_mod in mkUsageInfo + -- is used solely to decide if we should record a dependency + -- or not. When we instantiate a signature, the semantic + -- module is something we want to record dependencies for, + -- but if you pass that in here, we'll decide it's the local + -- module and does not need to be recorded as a dependency. + -- See Note [Identity versus semantic module] + usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env (tcg_mod tc_result) (imp_mods (tcg_imports tc_result)) used_names + dep_files (tcg_merged tc_result) needed_links needed_pkgs + return (Just usages) + mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Bool -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo -> Bool -> SafeHaskellMode - -> [Usage] + -> Maybe ModIfaceSelfRecomp -> Maybe Docs - -> ModSummary -> ModDetails -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode usages - docs mod_summary + hpc_info pkg_trust_req safe_mode self_recomp + docs ModDetails{ md_defaults = defaults, md_insts = insts, md_fam_insts = fam_insts, @@ -350,8 +360,8 @@ mkIface_ hsc_env then Nothing else Just semantic_mod) & set_mi_hsc_src hsc_src + & set_mi_self_recomp self_recomp & set_mi_deps deps - & set_mi_usages usages & set_mi_exports (mkIfaceExports exports) & set_mi_defaults (defaultsToIfaceDefaults defaults) @@ -376,7 +386,6 @@ mkIface_ hsc_env & set_mi_docs docs & set_mi_final_exts () & set_mi_ext_fields emptyExtensibleFields - & set_mi_src_hash (ms_hs_hash mod_summary) & set_mi_hi_bytes PartialIfaceBinHandle where ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -15,6 +15,7 @@ module GHC.Iface.Recomp , CompileReason(..) , recompileRequired , addFingerprints + , mkSelfRecomp ) where @@ -171,6 +172,7 @@ data RecompReason = UnitDepRemoved UnitId | ModulePackageChanged FastString | SourceFileChanged + | NoSelfRecompInfo | ThisUnitIdChanged | ImpurePlugin | PluginsChanged @@ -204,6 +206,7 @@ instance Outputable RecompReason where UnitDepRemoved uid -> ppr uid <+> text "removed" ModulePackageChanged s -> ftext s <+> text "package changed" SourceFileChanged -> text "Source file changed" + NoSelfRecompInfo -> text "Old interface lacks recompilation info" ThisUnitIdChanged -> text "-this-unit-id changed" ImpurePlugin -> text "Impure plugin forced recompilation" PluginsChanged -> text "Plugins changed" @@ -283,7 +286,7 @@ check_old_iface hsc_env mod_summary maybe_iface logger = hsc_logger hsc_env getIface = case maybe_iface of - Just _ -> do + Just {} -> do trace_if logger (text "We already have the old interface for" <+> ppr (ms_mod mod_summary)) return maybe_iface @@ -354,7 +357,9 @@ check_old_iface hsc_env mod_summary maybe_iface -- should check versions because some packages -- might have changed or gone away. Just iface -> - check_dyn_hi iface $ checkVersions hsc_env mod_summary iface + case mi_self_recomp_info iface of + Nothing -> return $ outOfDateItemBecause NoSelfRecompInfo Nothing + Just sr_info -> check_dyn_hi iface $ checkVersions hsc_env mod_summary iface sr_info -- | Check if a module is still the same 'version'. -- @@ -370,8 +375,9 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface + -> ModIfaceSelfRecomp -> IfG (MaybeValidated ModIface) -checkVersions hsc_env mod_summary iface +checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger (text "Considering whether compilation is required for" <+> ppr (mi_module iface) <> colon) @@ -380,23 +386,22 @@ checkVersions hsc_env mod_summary iface -- but we ALSO must make sure the instantiation matches up. See -- test case bkpcabal04! ; hsc_env <- getTopEnv - ; if mi_src_hash iface /= ms_hs_hash mod_summary + ; if mi_sr_src_hash self_recomp /= ms_hs_hash mod_summary then return $ outOfDateItemBecause SourceFileChanged Nothing else do { ; if not (isHomeModule home_unit (mi_module iface)) then return $ outOfDateItemBecause ThisUnitIdChanged Nothing else do { - ; recomp <- liftIO $ checkFlagHash hsc_env iface - `recompThen` checkOptimHash hsc_env iface - `recompThen` checkHpcHash hsc_env iface - `recompThen` checkMergedSignatures hsc_env mod_summary iface + ; recomp <- liftIO $ checkFlagHash hsc_env (mi_module iface) self_recomp + `recompThen` checkOptimHash hsc_env self_recomp + `recompThen` checkHpcHash hsc_env self_recomp + `recompThen` checkMergedSignatures hsc_env mod_summary self_recomp `recompThen` checkHsig logger home_unit mod_summary iface `recompThen` pure (checkHie dflags mod_summary) ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { ; recomp <- checkDependencies hsc_env mod_summary iface ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { - ; recomp <- checkPlugins (hsc_plugins hsc_env) iface + ; recomp <- checkPlugins (hsc_plugins hsc_env) self_recomp ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { - -- Source code unchanged and no errors yet... carry on -- -- First put the dependent-module info, read from the old @@ -411,7 +416,7 @@ checkVersions hsc_env mod_summary iface ; updateEps_ $ \eps -> eps { eps_is_boot = mkModDeps $ dep_boot_mods (mi_deps iface) } } ; recomp <- checkList [checkModUsage (hsc_FC hsc_env) u - | u <- mi_usages iface] + | u <- mi_sr_usages self_recomp] ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { ; return $ UpToDateItem iface }}}}}}} @@ -423,11 +428,11 @@ checkVersions hsc_env mod_summary iface -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIface -> IfG RecompileRequired -checkPlugins plugins iface = liftIO $ do +checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp - let old_fingerprint = mi_plugin_hash (mi_final_exts iface) + let old_fingerprint = mi_sr_plugin_hash self_recomp return $ pluginRecompileToRecompileRequired old_fingerprint new_fingerprint recomp recompPlugins :: Plugins -> IO PluginRecompile @@ -516,11 +521,11 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> ModIface -> IO RecompileRequired -checkFlagHash hsc_env iface = do +checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_flag_hash (mi_final_exts iface) - new_hash <- fingerprintDynFlags hsc_env (mi_module iface) putNameLiterally + let old_hash = mi_sr_flag_hash self_recomp + new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally case old_hash == new_hash of True -> up_to_date logger (text "Module flags unchanged") False -> out_of_date_hash logger FlagsChanged @@ -528,10 +533,10 @@ checkFlagHash hsc_env iface = do old_hash new_hash -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIface -> IO RecompileRequired +checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env - let old_hash = mi_opt_hash (mi_final_exts iface) + let old_hash = mi_sr_opt_hash iface new_hash <- fingerprintOptFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -544,10 +549,10 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIface -> IO RecompileRequired -checkHpcHash hsc_env iface = do +checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_hpc_hash (mi_final_exts iface) + let old_hash = mi_sr_hpc_hash self_recomp new_hash <- fingerprintHpcFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -561,11 +566,11 @@ checkHpcHash hsc_env iface = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIface -> IO RecompileRequired -checkMergedSignatures hsc_env mod_summary iface = do +checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env - let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_usages iface ] + let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_sr_usages self_recomp ] new_merged = case lookupUniqMap (requirementContext unit_state) (ms_mod_name mod_summary) of Nothing -> [] @@ -939,6 +944,28 @@ we use is: -} +-- | Compute the information needed for self-recompilation checking. This +-- information can be computed before the backend phase. +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp hsc_env this_mod src_hash usages = do + let dflags = hsc_dflags hsc_env + + flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + + opt_hash <- fingerprintOptFlags dflags putNameLiterally + + hpc_hash <- fingerprintHpcFlags dflags putNameLiterally + + plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + + return (ModIfaceSelfRecomp + { mi_sr_flag_hash = flag_hash + , mi_sr_hpc_hash = hpc_hash + , mi_sr_opt_hash = opt_hash + , mi_sr_plugin_hash = plugin_hash + , mi_sr_src_hash = src_hash + , mi_sr_usages = usages }) + -- | Add fingerprints for top-level declarations to a 'ModIface'. -- -- See Note [Fingerprinting IfaceDecls] @@ -1213,18 +1240,6 @@ addFingerprints hsc_env iface0 sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - -- the flag hash depends on: - -- - (some of) dflags - -- it returns two hashes, one that shouldn't change - -- the abi hash and one that should - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally - - opt_hash <- fingerprintOptFlags dflags putNameLiterally - - hpc_hash <- fingerprintHpcFlags dflags putNameLiterally - - plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) - -- the ABI hash depends on: -- - decls -- - export list @@ -1238,6 +1253,7 @@ addFingerprints hsc_env iface0 mi_warns iface0, mi_foreign iface0) + -- The interface hash depends on: -- - the ABI hash, plus -- - the source file hash, @@ -1246,21 +1262,17 @@ addFingerprints hsc_env iface0 -- - deps (home and external packages, dependent files) -- - hpc iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - mi_src_hash iface0, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_usages iface0, - sorted_deps, - mi_hpc iface0) + (mod_hash, + mi_src_hash iface0, + ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache + mi_usages iface0, + sorted_deps, + mi_hpc iface0) let final_iface_exts = ModIfaceBackend - { mi_iface_hash = iface_hash - , mi_mod_hash = mod_hash - , mi_flag_hash = flag_hash - , mi_opt_hash = opt_hash - , mi_hpc_hash = hpc_hash - , mi_plugin_hash = plugin_hash + { mi_mod_hash = mod_hash + , mi_iface_hash = iface_hash , mi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts @@ -1281,12 +1293,12 @@ addFingerprints hsc_env iface0 where this_mod = mi_module iface0 semantic_mod = mi_semantic_module iface0 - dflags = hsc_dflags hsc_env (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) ann_fn = mkIfaceAnnCache (mi_anns iface0) + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the -- current module). ===================================== compiler/GHC/Unit/Module/ModGuts.hs ===================================== @@ -53,7 +53,7 @@ data ModGuts mg_exports :: ![AvailInfo], -- ^ What it exports mg_deps :: !Dependencies, -- ^ What it depends on, directly or -- otherwise - mg_usages :: ![Usage], -- ^ What was used? Used for interfaces. + mg_usages :: !(Maybe [Usage]), -- ^ What was used? Used for interfaces. mg_used_th :: !Bool, -- ^ Did we run a TH splice? mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -15,7 +15,6 @@ module GHC.Unit.Module.ModIface , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -36,19 +35,16 @@ module GHC.Unit.Module.ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info ) , pattern ModIface - , restoreFromOldModIface - , addSourceFingerprint , set_mi_module , set_mi_sig_of , set_mi_hsc_src - , set_mi_src_hash + , set_mi_self_recomp , set_mi_hi_bytes , set_mi_deps - , set_mi_usages , set_mi_exports , set_mi_used_th , set_mi_fixities @@ -73,6 +69,8 @@ module GHC.Unit.Module.ModIface , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) + , ModIfaceSelfRecomp (..) + , withSelfRecomp , IfaceDeclExts , IfaceBackendExts , IfaceExport @@ -85,6 +83,12 @@ module GHC.Unit.Module.ModIface , mi_semantic_module , mi_free_holes , mi_mnwib + , mi_flag_hash + , mi_opt_hash + , mi_hpc_hash + , mi_plugin_hash + , mi_src_hash + , mi_usages , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,6 +110,8 @@ import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.ModIface.SelfRecomp + import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env @@ -150,19 +156,10 @@ type ModIface = ModIface_ 'ModIfaceFinal -- * Or computed just before writing the iface to disk. (Hashes) -- In order to fully instantiate it. data ModIfaceBackend = ModIfaceBackend - { mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_mod_hash :: !Fingerprint + { mi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_flag_hash :: !Fingerprint - -- ^ Hash of the important flags used when compiling the module, excluding - -- optimisation flags - , mi_opt_hash :: !Fingerprint - -- ^ Hash of optimisation flags - , mi_hpc_hash :: !Fingerprint - -- ^ Hash of hpc flags - , mi_plugin_hash :: !Fingerprint - -- ^ Hash of plugins + , mi_iface_hash :: !Fingerprint + -- ^ Hash of the whole interface , mi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans , mi_finsts :: !WhetherHasFamInst @@ -218,6 +215,15 @@ data IfaceBinHandle (phase :: ModIfacePhase) where -- (e.g., set to 'Nothing'). FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal + +withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp iface nk jk = + case mi_self_recomp_info iface of + Nothing -> nk + Just x -> jk x + + + -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, -- and can be written out to an interface file. The 'ModDetails is after @@ -245,16 +251,6 @@ data ModIface_ (phase :: ModIfacePhase) -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages_ :: [Usage], - -- ^ Usages; kept sorted so that it's easy to decide - -- whether to write a new iface file (changing usages - -- doesn't affect the hash of this module) - -- NOT STRICT! we read this field lazily from the interface file - -- It is *only* consulted by the recompilation checker - -- - -- The elements must be *deterministically* sorted to guarantee - -- deterministic interface files - mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier @@ -345,13 +341,15 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash_ :: !Fingerprint, - -- ^ Hash of the .hs source, used for recompilation checking. - mi_hi_bytes_ :: !(IfaceBinHandle phase) + mi_hi_bytes_ :: !(IfaceBinHandle phase), -- ^ A serialised in-memory buffer of this 'ModIface'. -- If this handle is given, we can avoid serialising the 'ModIface' -- when writing this 'ModIface' to disk, and write this buffer to disk instead. -- See Note [Sharing of ModIface]. + + mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] } -- Enough information to reconstruct the top level environment for a module @@ -397,6 +395,24 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} +mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ + +mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ + +mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ + +mi_src_hash :: ModIface_ phase -> Maybe Fingerprint +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ + +mi_usages :: ModIface_ phase -> Maybe [Usage] +mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ + +mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ + -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. mi_boot :: ModIface -> IsBootInterface @@ -454,9 +470,6 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance - -- because we are going to write it - -- out separately in the actual file mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then @@ -464,7 +477,6 @@ instance Binary ModIface where -- the byte array. -- See Note [Private fields in ModIface] mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_fixities_ = fixities, @@ -486,13 +498,10 @@ instance Binary ModIface where mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file + mi_self_recomp_info_ = self_recomp, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -501,16 +510,12 @@ instance Binary ModIface where put_ bh mod put_ bh sig_of put_ bh hsc_src - put_ bh iface_hash + put_ bh self_recomp put_ bh mod_hash - put_ bh flag_hash - put_ bh opt_hash - put_ bh hpc_hash - put_ bh plugin_hash + put_ bh iface_hash put_ bh orphan put_ bh hasFamInsts lazyPut bh deps - lazyPut bh usages put_ bh exports put_ bh exp_hash put_ bh used_th @@ -536,16 +541,12 @@ instance Binary ModIface where mod <- get bh sig_of <- get bh hsc_src <- get bh - iface_hash <- get bh + self_recomp_info <- get bh mod_hash <- get bh - flag_hash <- get bh - opt_hash <- get bh - hpc_hash <- get bh - plugin_hash <- get bh + iface_hash <- get bh orphan <- get bh hasFamInsts <- get bh deps <- lazyGet bh - usages <- {-# SCC "bin_usages" #-} lazyGet bh exports <- {-# SCC "bin_exports" #-} get bh exp_hash <- get bh used_th <- get bh @@ -570,15 +571,12 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = fingerprint0, -- placeholder because this is dealt - -- with specially when the file is read mi_hi_bytes_ = -- We can't populate this field here, as we are -- missing the 'mi_ext_fields_' field, which is -- handled in 'getIfaceWithExtFields'. FullIfaceBinHandle Strict.Nothing, mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_anns_ = anns, @@ -600,13 +598,10 @@ instance Binary ModIface where mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read + mi_self_recomp_info_ = self_recomp_info, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -625,10 +620,8 @@ emptyPartialModIface mod { mi_module_ = mod, mi_sig_of_ = Nothing, mi_hsc_src_ = HsSrcFile, - mi_src_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_usages_ = [], mi_exports_ = [], mi_used_th_ = False, mi_fixities_ = [], @@ -648,21 +641,19 @@ emptyPartialModIface mod mi_complete_matches_ = [], mi_docs_ = Nothing, mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields + mi_ext_fields_ = emptyExtensibleFields, + mi_self_recomp_info_ = Nothing } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) { mi_decls_ = [] + , mi_self_recomp_info_ = Nothing , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing , mi_final_exts_ = ModIfaceBackend - { mi_iface_hash = fingerprint0, - mi_mod_hash = fingerprint0, - mi_flag_hash = fingerprint0, - mi_opt_hash = fingerprint0, - mi_hpc_hash = fingerprint0, - mi_plugin_hash = fingerprint0, + { mi_mod_hash = fingerprint0, + mi_iface_hash = fingerprint0, mi_orphan = False, mi_finsts = False, mi_exp_hash = fingerprint0, @@ -692,18 +683,17 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_, mi_src_hash_ }) + , mi_ext_fields_ }) = rnf mi_module_ `seq` rnf mi_sig_of_ `seq` mi_hsc_src_ `seq` mi_hi_bytes_ `seq` mi_deps_ - `seq` mi_usages_ `seq` mi_exports_ `seq` rnf mi_used_th_ `seq` mi_fixities_ @@ -724,20 +714,14 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_docs_ `seq` mi_final_exts_ `seq` mi_ext_fields_ - `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_iface_hash, mi_mod_hash, mi_flag_hash, mi_opt_hash - , mi_hpc_hash, mi_plugin_hash, mi_orphan, mi_finsts, mi_exp_hash + rnf (ModIfaceBackend{ mi_mod_hash + , mi_orphan, mi_finsts, mi_exp_hash , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn , mi_hash_fn}) - = rnf mi_iface_hash - `seq` rnf mi_mod_hash - `seq` rnf mi_flag_hash - `seq` rnf mi_opt_hash - `seq` rnf mi_hpc_hash - `seq` rnf mi_plugin_hash + = rnf mi_mod_hash `seq` rnf mi_orphan `seq` rnf mi_finsts `seq` rnf mi_exp_hash @@ -803,27 +787,6 @@ completePartialModIface partial decls extra_decls final_exts = partial , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing } --- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array --- buffer 'mi_hi_bytes'. --- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. --- --- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. -addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase -addSourceFingerprint val iface = iface { mi_src_hash_ = val } - --- | Copy fields that aren't serialised to disk to the new 'ModIface_'. --- This includes especially hashes that are usually stored in the interface --- file header. --- --- We need this function after calling 'shareIface', to make sure the --- 'ModIface_' doesn't lose any information. This function does not discard --- the in-memory byte array buffer 'mi_hi_bytes'. -restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase -restoreFromOldModIface old new = new - { mi_hsc_src_ = mi_hsc_src_ old - , mi_src_hash_ = mi_src_hash_ old - } - set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } @@ -833,8 +796,8 @@ set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } -set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase -set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } +set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -842,9 +805,6 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } -set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase -set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } - set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } @@ -969,7 +929,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} -{-# INLINE mi_usages #-} {-# INLINE mi_exports #-} {-# INLINE mi_used_th #-} {-# INLINE mi_fixities #-} @@ -989,25 +948,23 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_docs #-} {-# INLINE mi_final_exts #-} {-# INLINE mi_ext_fields #-} -{-# INLINE mi_src_hash #-} {-# INLINE mi_hi_bytes #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + Module -> Maybe Module -> HscSource -> Dependencies -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface { mi_module , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -1028,14 +985,13 @@ pattern ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info } <- PrivateModIface { mi_module_ = mi_module , mi_sig_of_ = mi_sig_of , mi_hsc_src_ = mi_hsc_src , mi_deps_ = mi_deps - , mi_usages_ = mi_usages , mi_exports_ = mi_exports , mi_used_th_ = mi_used_th , mi_fixities_ = mi_fixities @@ -1056,6 +1012,6 @@ pattern ModIface , mi_docs_ = mi_docs , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields - , mi_src_hash_ = mi_src_hash , mi_hi_bytes_ = mi_hi_bytes + , mi_self_recomp_info_ = mi_self_recomp_info } ===================================== compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs ===================================== @@ -0,0 +1,111 @@ +module GHC.Unit.Module.ModIface.SelfRecomp where + +import GHC.Prelude +import GHC.Fingerprint +import GHC.Utils.Outputable +import GHC.Unit.Module.Deps + +import GHC.Utils.Binary + +import Control.DeepSeq + +{- +Note [Self recompilation information in interface files] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The flag -fwrite-if-self-recomp controls whether +interface files contain the information necessary to answer the +question: + + Is the interface file up-to-date, relative to: + * the source file it corresponds to, + * the flags passed to the GHC invocation to compile it, + * its dependencies (e.g. imported items, watched files added by addDependentFile, ...) + +If there is no self-recompilation information stored, then we always re-generate +the interface file from scratch. + +Why? Most packages are only built once either by a distribution or cabal +and then placed into an immutable store, after which we will never ask +this question. Therefore we can derive two benefits from omitting this +information. + +* Primary motivation: It vastly reduces the surface area for creating + non-deterministic interface files. See issue #10424 which motivated a + proper fix to that issue. Distributions have long contained versions + of GHC which just have broken self-recompilation checking (in order to + get deterministic interface files). + +* Secondary motivation: This reduces the size of interface files + slightly.. the `mi_usages` field can be quite big but probably this + isn't such a great benefit. + +* Third motivation: Conceptually clarity about which parts of an + interface file are used in order to **communicate** with subsequent + packages about the **interface** for a module. And which parts are + used to self-communicate during recompilation checking. + +The main tracking issue is #22188 but fixes issues such as #10424 in a +proper way. + +-} + +-- | The information for a module which is only used when deciding whether to recompile +-- itself. +-- +-- See Note [Self recompilation information in interface files] +data ModIfaceSelfRecomp = + ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint + -- ^ Hash of the .hs source, used for recompilation checking. + , mi_sr_usages :: [Usage] + -- ^ Usages; kept sorted so that it's easy to decide + -- whether to write a new iface file (changing usages + -- doesn't affect the hash of this module) + -- NOT STRICT! we read this field lazily from the interface file + -- It is *only* consulted by the recompilation checker + + , mi_sr_flag_hash :: !Fingerprint + -- ^ Hash of the important flags used when compiling the module, excluding + -- optimisation flags + , mi_sr_opt_hash :: !Fingerprint + -- ^ Hash of optimisation flags + , mi_sr_hpc_hash :: !Fingerprint + -- ^ Hash of hpc flags + , mi_sr_plugin_hash :: !Fingerprint + -- ^ Hash of plugins + } + + +instance Binary ModIfaceSelfRecomp where + put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do + put_ bh mi_sr_src_hash + lazyPut bh mi_sr_usages + put_ bh mi_sr_flag_hash + put_ bh mi_sr_opt_hash + put_ bh mi_sr_hpc_hash + put_ bh mi_sr_plugin_hash + + get bh = do + src_hash <- get bh + usages <- lazyGet bh + flag_hash <- get bh + opt_hash <- get bh + hpc_hash <- get bh + plugin_hash <- get bh + return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + +instance Outputable ModIfaceSelfRecomp where + ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) + = vcat [text "Self-Recomp" + , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash + , text "usages:" <+> ppr (length mi_sr_usages) + , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "opt hash:" <+> ppr mi_sr_opt_hash + , text "hpc hash:" <+> ppr mi_sr_hpc_hash + , text "plugin hash:" <+> ppr mi_sr_plugin_hash + ])] + +instance NFData ModIfaceSelfRecomp where + -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so + -- I left it as a shallow force. + rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file ===================================== compiler/ghc.cabal.in ===================================== @@ -955,6 +955,7 @@ Library GHC.Unit.Module.ModDetails GHC.Unit.Module.ModGuts GHC.Unit.Module.ModIface + GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.WholeCoreBindings GHC.Unit.Module.ModSummary GHC.Unit.Module.Status ===================================== docs/users_guide/phases.rst ===================================== @@ -702,6 +702,24 @@ Options affecting code generation depend on the optimisation level. Any definitions which are already included in an interface file (via an unfolding for an exported identifier) are reused. +.. ghc-flag:: -fwrite-if-self-recomp + :shortdesc: Write information for self-recompilation checking in an interface file + :type: dynamic + :category: codegen + + :default: on + + Include information in an interface file which can be used in future to determine + whether we need to recompile a module or can reuse the existing interface. + + This is intended to be turned off in situations where you know you will never try + to recompile a module, such as when compiling a package for distribution. + The advantage is that by omitting unecessary information to do with dependencies + there is less chance of build paths leaking into the interface file and affecting + determinism. + + + .. ghc-flag:: -fobject-code :shortdesc: Generate object code ===================================== hadrian/doc/flavours.md ===================================== @@ -107,7 +107,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH <td>-O2</td> </tr> <tr> - <th>release (same as perf with -haddock)</td> + <th>release (same as perf with -haddock and +no_self_recomp)</td> <td></td> <td>-O<br>-H64m</td> <td>-O<br>-H64m</td> @@ -329,6 +329,10 @@ The supported transformers are listed below: <td><code>dump_stg</code></td> <td>Dump STG of all modules compiled by a stage1 compiler to a file</td> </tr> + <tr> + <td><code>no_self_recomp</code></td> + <td>Disable including self-recompilation information in interface files via <code>-fno-write-if-self-recomp</code>. If you are building a distribution you can enable this flag to produce more deterministic interface files.</td> + </tr> </table> ### Static ===================================== hadrian/src/Flavour.hs ===================================== @@ -16,6 +16,7 @@ module Flavour , disableProfiledLibs , enableLinting , enableHaddock + , disableSelfRecompInfo , enableHiCore , useNativeBignum , enableTextWithSIMDUTF @@ -67,6 +68,7 @@ flavourTransformers = M.fromList , "debug_stage1_ghc" =: debugGhc Stage1 , "lint" =: enableLinting , "haddock" =: enableHaddock + , "no_self_recomp" =: disableSelfRecompInfo , "hi_core" =: enableHiCore , "late_ccs" =: enableLateCCS , "boot_nonmoving_gc" =: enableBootNonmovingGc @@ -208,6 +210,17 @@ enableHaddock = [ arg "-haddock" ] +-- | Disable self recompilation information in interface files +disableSelfRecompInfo :: Flavour -> Flavour +disableSelfRecompInfo = + addArgs $ stage1 ? mconcat + [ builder (Ghc CompileHs) ? selfRecomp + ] + where + selfRecomp = mconcat + [ arg "-fno-write-if-self-recomp" + ] + -- | Build stage2 dependencies with options to emit Core into -- interface files which is sufficient to restart code generation. enableHiCore :: Flavour -> Flavour ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,8 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableHaddock performanceFlavour { name = "release" } +releaseFlavour = + -- 1. These interface files will be distributed and the source files never recompiled. + disableSelfRecompInfo + -- 2. Include documentation in the interface for tools such as haddock and HLS to use + $ enableHaddock performanceFlavour { name = "release" } ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -201,6 +201,7 @@ GHC.Unit.Module.Env GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.Warnings GHC.Unit.Module.WholeCoreBindings GHC.Unit.Parser ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -227,6 +227,7 @@ GHC.Unit.Module.Graph GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.ModNodeKey GHC.Unit.Module.ModSummary GHC.Unit.Module.Warnings ===================================== testsuite/tests/driver/self-recomp/Makefile ===================================== @@ -0,0 +1,38 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +TEST_HC_OPTS_NO_RTSOPTS = $(filter-out -rtsopts,$(TEST_HC_OPTS)) + +# ----------------------------------------------------------------------------- +# One-shot compilations, non-hierarchical modules + +# Check that modifying flags doesn't affect interface +SelfRecomp01: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface1 + rm SelfRecomp01.hi + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-if-self-recomp -Iidir -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface2 + diff iface1 iface2 + +# Check that the result of addDependentFile doesn't end up in interface +SelfRecomp02: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp02.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp02.hi > iface + [ -z $(grep iface SelfRecomp02.hs) ] + +# Check that modifying source doesn't affect interface +SelfRecomp03: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface1 + rm SelfRecomp03.hi + echo "" >> SelfRecomp03.hs + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface2 + diff iface1 iface2 + +# Check that if you don't have recompilation info then you always recompile. +SelfRecomp04: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-if-self-recomp -fhide-source-paths + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-if-self-recomp -fhide-source-paths ===================================== testsuite/tests/driver/self-recomp/SelfRecomp01.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp01 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp02.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +module SelfRecomp02 where + +import Language.Haskell.TH.Syntax + +main = $(addDependentFile "SelfRecomp02.hs" >> [| print () |]) ===================================== testsuite/tests/driver/self-recomp/SelfRecomp03.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp03 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.hs ===================================== @@ -0,0 +1 @@ +module SelfRecomp04 where ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.stdout ===================================== @@ -0,0 +1,2 @@ +[1 of 1] Compiling SelfRecomp04 +[1 of 1] Compiling SelfRecomp04 [Old interface lacks recompilation info] ===================================== testsuite/tests/driver/self-recomp/all.T ===================================== @@ -0,0 +1,4 @@ +test('SelfRecomp01', normal, makefile_test, ['SelfRecomp01']) +test('SelfRecomp02', normal, makefile_test, ['SelfRecomp02']) +test('SelfRecomp03', [copy_files], makefile_test, ['SelfRecomp03']) +test('SelfRecomp04', normal, makefile_test, ['SelfRecomp04']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ffafd83d12a220a8a0a7a1ea52abe6d4d0aaeee3...782f46032853d42952d1c041bd66048efa8d6f65 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ffafd83d12a220a8a0a7a1ea52abe6d4d0aaeee3...782f46032853d42952d1c041bd66048efa8d6f65 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/1492d304/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 09:26:56 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 05 Mar 2025 04:26:56 -0500 Subject: [Git][ghc/ghc][wip/22188] 2 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67c818e068f3f_343add36ad80150d3@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: aa1ded09 by Matthew Pickering at 2025-03-05T09:26:00+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - cf497243 by Matthew Pickering at 2025-03-05T09:26:20+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 28 changed files: - compiler/GHC.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -104,10 +104,8 @@ module GHC ( mi_module, mi_sig_of, mi_hsc_src, - mi_src_hash, mi_hi_bytes, mi_deps, - mi_usages, mi_exports, mi_used_th, mi_fixities, ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1178,7 +1178,8 @@ defaultFlags settings Opt_ShowErrorContext, Opt_SuppressStgReps, Opt_UnoptimizedCoreForInterpreter, - Opt_SpecialiseIncoherents + Opt_SpecialiseIncoherents, + Opt_WriteSelfRecompInfo ] ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns] ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -692,6 +692,7 @@ data GeneralFlag | Opt_ExposeOverloadedUnfoldings | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code + | Opt_WriteSelfRecompInfo | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1243,11 +1243,11 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h (cg_guts, details) <- liftIO $ hscTidy hsc_env simplified_guts - let !partial_iface = + !partial_iface <- liftIO $ {-# SCC "GHC.Driver.Main.mkPartialIface" #-} -- This `force` saves 2M residency in test T10370 -- See Note [Avoiding space leaks in toIface*] for details. - force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) + fmap force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) return HscRecomp { hscs_guts = cg_guts, hscs_mod_location = ms_location summary, ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -875,10 +875,10 @@ pruneCache hpt summ modl = miKey iface linkable' | Just ms <- M.lookup modl ms_map - , mi_src_hash iface /= ms_hs_hash ms - = emptyHomeModInfoLinkable - | otherwise + , mi_src_hash iface == Just (ms_hs_hash ms) = linkable + | otherwise + = emptyHomeModInfoLinkable -- Using UFM Module is safe for determinism because the map is just used for a transient lookup. The cache should be unique and a key clash is an error. ms_map = M.fromListWith ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,6 +2528,7 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, + flagSpec "write-if-self-recomp" Opt_WriteSelfRecompInfo, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -22,14 +22,12 @@ import GHC.Driver.DynFlags import GHC.Driver.Config import GHC.Driver.Config.Core.Lint ( endPassHscEnvIO ) import GHC.Driver.Config.HsToCore.Ticks -import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env import GHC.Driver.Backend import GHC.Driver.Plugins import GHC.Hs -import GHC.HsToCore.Usage import GHC.HsToCore.Monad import GHC.HsToCore.Errors.Types import GHC.HsToCore.Expr @@ -42,7 +40,7 @@ import GHC.HsToCore.Docs import GHC.Tc.Types import GHC.Tc.Types.Origin ( Position(..) ) -import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceLoad ) +import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances ) import GHC.Tc.Module ( runTcInteractive ) import GHC.Core.Type @@ -100,6 +98,7 @@ import GHC.Unit.Module.Deps import Data.List (partition) import Data.IORef import Data.Traversable (for) +import GHC.Iface.Make (mkRecompUsageInfo) {- ************************************************************************ @@ -127,12 +126,10 @@ deSugar hsc_env tcg_fix_env = fix_env, tcg_inst_env = inst_env, tcg_fam_inst_env = fam_inst_env, - tcg_merged = merged, tcg_warns = warns, tcg_anns = anns, tcg_binds = binds, tcg_imp_specs = imp_specs, - tcg_dependent_files = dependent_files, tcg_ev_binds = ev_binds, tcg_th_foreign_files = th_foreign_files_var, tcg_fords = fords, @@ -228,8 +225,7 @@ deSugar hsc_env ; endPassHscEnvIO hsc_env name_ppr_ctx CoreDesugarOpt ds_binds ds_rules_for_imps - ; let used_names = mkUsedNames tcg_env - pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) + ; let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) home_unit = hsc_home_unit hsc_env ; let deps = mkDependencies home_unit (tcg_mod tcg_env) @@ -237,17 +233,10 @@ deSugar hsc_env (map mi_module pluginModules) ; used_th <- readIORef tc_splice_used - ; dep_files <- readIORef dependent_files ; safe_mode <- finalSafeMode dflags tcg_env - ; (needed_mods, needed_pkgs) <- readIORef (tcg_th_needed_deps tcg_env) - - ; let uc = initUsageConfig hsc_env - ; let plugins = hsc_plugins hsc_env - ; let fc = hsc_FC hsc_env - ; let unit_env = hsc_unit_env hsc_env - ; usages <- initIfaceLoad hsc_env $ - mkUsageInfo uc plugins fc unit_env mod (imp_mods imports) used_names - dep_files merged needed_mods needed_pkgs + + ; usages <- mkRecompUsageInfo hsc_env tcg_env + -- id_mod /= mod when we are processing an hsig, but hsigs -- never desugared and compiled (there's no code!) -- Consequently, this should hold for any ModGuts that make ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -49,7 +49,6 @@ import GHC.Types.Name.Cache import GHC.Types.SrcLoc import GHC.Platform import GHC.Settings.Constants -import GHC.Utils.Fingerprint import GHC.Iface.Type (IfaceType(..), getIfaceType, putIfaceType, ifaceTypeSharedByte) import Control.Monad @@ -114,7 +113,7 @@ readBinIfaceHeader -> CheckHiWay -> TraceBinIFace -> FilePath - -> IO (Fingerprint, ReadBinHandle) + -> IO ReadBinHandle readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do let platform = profilePlatform profile @@ -156,8 +155,7 @@ readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do when (checkHiWay == CheckHiWay) $ errorOnMismatch "mismatched interface file profile tag" tag check_tag - src_hash <- get bh - pure (src_hash, bh) + pure bh -- | Read an interface file. -- @@ -170,12 +168,11 @@ readBinIface -> FilePath -> IO ModIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do - (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path + bh <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path mod_iface <- getIfaceWithExtFields name_cache bh return $ mod_iface - & addSourceFingerprint src_hash getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface @@ -259,7 +256,6 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh (show hiVersion) let tag = profileBuildTag profile put_ bh tag - put_ bh (mi_src_hash mod_iface) putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1259,21 +1259,25 @@ pprModIfaceSimple unit_state iface = -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc pprModIface unit_state iface - = vcat [ text "interface" + = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) + <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash exts)) , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) + , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat + [ nest 2 (text "src_hash:" <+> ppr src) + , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "opt_hash:" <+> ppr opt_hash) + , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) + , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) + , vcat (map pprUsage usages) + ] , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) - , nest 2 (text "flag hash:" <+> ppr (mi_flag_hash exts)) - , nest 2 (text "opt_hash:" <+> ppr (mi_opt_hash exts)) - , nest 2 (text "hpc_hash:" <+> ppr (mi_hpc_hash exts)) - , nest 2 (text "plugin_hash:" <+> ppr (mi_plugin_hash exts)) - , nest 2 (text "src_hash:" <+> ppr (mi_src_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "used TH splices:" <+> ppr (mi_used_th iface)) , nest 2 (text "where") @@ -1282,7 +1286,6 @@ pprModIface unit_state iface , text "defaults:" , nest 2 (vcat (map ppr (mi_defaults iface))) , pprDeps unit_state (mi_deps iface) - , vcat (map pprUsage (mi_usages iface)) , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] @@ -1302,6 +1305,7 @@ pprModIface unit_state iface ] where exts = mi_final_exts iface + pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -13,6 +13,7 @@ module GHC.Iface.Make ( mkPartialIface , mkFullIface , mkIfaceTc + , mkRecompUsageInfo , mkIfaceExports ) where @@ -110,7 +111,7 @@ mkPartialIface :: HscEnv -> ModSummary -> [ImportUserSpec] -> ModGuts - -> PartialModIface + -> IO PartialModIface mkPartialIface hsc_env core_prog mod_details mod_summary import_decls ModGuts{ mg_module = this_mod , mg_hsc_src = hsc_src @@ -125,8 +126,10 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_trust_pkg = self_trust , mg_docs = docs } - = mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust - safe_mode usages docs mod_summary mod_details + = do + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages + return $ mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust + safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code -- generator produced information. @@ -181,9 +184,8 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = restoreFromOldModIface mi res - forceModIface resiface - return resiface + forceModIface res + return res -- | Initial ram buffer to allocate for writing interface files. initBinMemSize :: Int @@ -236,14 +238,11 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_merged = merged, tcg_warns = warns, tcg_hpc = other_hpc_info, - tcg_th_splice_used = tc_splice_used, - tcg_dependent_files = dependent_files + tcg_th_splice_used = tc_splice_used } = do - let used_names = mkUsedNames tc_result let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) let home_unit = hsc_home_unit hsc_env let deps = mkDependencies home_unit @@ -252,48 +251,59 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (map mi_module pluginModules) let hpc_info = emptyHpcInfo other_hpc_info used_th <- readIORef tc_splice_used - dep_files <- (readIORef dependent_files) - (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) - let uc = initUsageConfig hsc_env - plugins = hsc_plugins hsc_env - fc = hsc_FC hsc_env - unit_env = hsc_unit_env hsc_env - -- Do NOT use semantic module here; this_mod in mkUsageInfo - -- is used solely to decide if we should record a dependency - -- or not. When we instantiate a signature, the semantic - -- module is something we want to record dependencies for, - -- but if you pass that in here, we'll decide it's the local - -- module and does not need to be recorded as a dependency. - -- See Note [Identity versus semantic module] - usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env this_mod (imp_mods imports) used_names - dep_files merged needed_links needed_pkgs + usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usage let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info - (imp_trust_own_pkg imports) safe_mode usages - docs mod_summary + (imp_trust_own_pkg imports) safe_mode self_recomp + docs mod_details mkFullIface hsc_env partial_iface Nothing Nothing NoStubs [] +mkRecompUsageInfo :: HscEnv -> TcGblEnv -> IO (Maybe [Usage]) +mkRecompUsageInfo hsc_env tc_result = do + let dflags = hsc_dflags hsc_env + if not (gopt Opt_WriteSelfRecompInfo dflags) + then return Nothing + else do + let used_names = mkUsedNames tc_result + dep_files <- (readIORef (tcg_dependent_files tc_result)) + (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) + let uc = initUsageConfig hsc_env + plugins = hsc_plugins hsc_env + fc = hsc_FC hsc_env + unit_env = hsc_unit_env hsc_env + + -- Do NOT use semantic module here; this_mod in mkUsageInfo + -- is used solely to decide if we should record a dependency + -- or not. When we instantiate a signature, the semantic + -- module is something we want to record dependencies for, + -- but if you pass that in here, we'll decide it's the local + -- module and does not need to be recorded as a dependency. + -- See Note [Identity versus semantic module] + usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env (tcg_mod tc_result) (imp_mods (tcg_imports tc_result)) used_names + dep_files (tcg_merged tc_result) needed_links needed_pkgs + return (Just usages) + mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Bool -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo -> Bool -> SafeHaskellMode - -> [Usage] + -> Maybe ModIfaceSelfRecomp -> Maybe Docs - -> ModSummary -> ModDetails -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode usages - docs mod_summary + hpc_info pkg_trust_req safe_mode self_recomp + docs ModDetails{ md_defaults = defaults, md_insts = insts, md_fam_insts = fam_insts, @@ -350,8 +360,8 @@ mkIface_ hsc_env then Nothing else Just semantic_mod) & set_mi_hsc_src hsc_src + & set_mi_self_recomp self_recomp & set_mi_deps deps - & set_mi_usages usages & set_mi_exports (mkIfaceExports exports) & set_mi_defaults (defaultsToIfaceDefaults defaults) @@ -376,7 +386,6 @@ mkIface_ hsc_env & set_mi_docs docs & set_mi_final_exts () & set_mi_ext_fields emptyExtensibleFields - & set_mi_src_hash (ms_hs_hash mod_summary) & set_mi_hi_bytes PartialIfaceBinHandle where ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -15,6 +15,7 @@ module GHC.Iface.Recomp , CompileReason(..) , recompileRequired , addFingerprints + , mkSelfRecomp ) where @@ -171,6 +172,7 @@ data RecompReason = UnitDepRemoved UnitId | ModulePackageChanged FastString | SourceFileChanged + | NoSelfRecompInfo | ThisUnitIdChanged | ImpurePlugin | PluginsChanged @@ -204,6 +206,7 @@ instance Outputable RecompReason where UnitDepRemoved uid -> ppr uid <+> text "removed" ModulePackageChanged s -> ftext s <+> text "package changed" SourceFileChanged -> text "Source file changed" + NoSelfRecompInfo -> text "Old interface lacks recompilation info" ThisUnitIdChanged -> text "-this-unit-id changed" ImpurePlugin -> text "Impure plugin forced recompilation" PluginsChanged -> text "Plugins changed" @@ -283,7 +286,7 @@ check_old_iface hsc_env mod_summary maybe_iface logger = hsc_logger hsc_env getIface = case maybe_iface of - Just _ -> do + Just {} -> do trace_if logger (text "We already have the old interface for" <+> ppr (ms_mod mod_summary)) return maybe_iface @@ -354,7 +357,9 @@ check_old_iface hsc_env mod_summary maybe_iface -- should check versions because some packages -- might have changed or gone away. Just iface -> - check_dyn_hi iface $ checkVersions hsc_env mod_summary iface + case mi_self_recomp_info iface of + Nothing -> return $ outOfDateItemBecause NoSelfRecompInfo Nothing + Just sr_info -> check_dyn_hi iface $ checkVersions hsc_env mod_summary iface sr_info -- | Check if a module is still the same 'version'. -- @@ -370,8 +375,9 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface + -> ModIfaceSelfRecomp -> IfG (MaybeValidated ModIface) -checkVersions hsc_env mod_summary iface +checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger (text "Considering whether compilation is required for" <+> ppr (mi_module iface) <> colon) @@ -380,23 +386,22 @@ checkVersions hsc_env mod_summary iface -- but we ALSO must make sure the instantiation matches up. See -- test case bkpcabal04! ; hsc_env <- getTopEnv - ; if mi_src_hash iface /= ms_hs_hash mod_summary + ; if mi_sr_src_hash self_recomp /= ms_hs_hash mod_summary then return $ outOfDateItemBecause SourceFileChanged Nothing else do { ; if not (isHomeModule home_unit (mi_module iface)) then return $ outOfDateItemBecause ThisUnitIdChanged Nothing else do { - ; recomp <- liftIO $ checkFlagHash hsc_env iface - `recompThen` checkOptimHash hsc_env iface - `recompThen` checkHpcHash hsc_env iface - `recompThen` checkMergedSignatures hsc_env mod_summary iface + ; recomp <- liftIO $ checkFlagHash hsc_env (mi_module iface) self_recomp + `recompThen` checkOptimHash hsc_env self_recomp + `recompThen` checkHpcHash hsc_env self_recomp + `recompThen` checkMergedSignatures hsc_env mod_summary self_recomp `recompThen` checkHsig logger home_unit mod_summary iface `recompThen` pure (checkHie dflags mod_summary) ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { ; recomp <- checkDependencies hsc_env mod_summary iface ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { - ; recomp <- checkPlugins (hsc_plugins hsc_env) iface + ; recomp <- checkPlugins (hsc_plugins hsc_env) self_recomp ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { - -- Source code unchanged and no errors yet... carry on -- -- First put the dependent-module info, read from the old @@ -411,7 +416,7 @@ checkVersions hsc_env mod_summary iface ; updateEps_ $ \eps -> eps { eps_is_boot = mkModDeps $ dep_boot_mods (mi_deps iface) } } ; recomp <- checkList [checkModUsage (hsc_FC hsc_env) u - | u <- mi_usages iface] + | u <- mi_sr_usages self_recomp] ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { ; return $ UpToDateItem iface }}}}}}} @@ -423,11 +428,11 @@ checkVersions hsc_env mod_summary iface -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIface -> IfG RecompileRequired -checkPlugins plugins iface = liftIO $ do +checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp - let old_fingerprint = mi_plugin_hash (mi_final_exts iface) + let old_fingerprint = mi_sr_plugin_hash self_recomp return $ pluginRecompileToRecompileRequired old_fingerprint new_fingerprint recomp recompPlugins :: Plugins -> IO PluginRecompile @@ -516,11 +521,11 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> ModIface -> IO RecompileRequired -checkFlagHash hsc_env iface = do +checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_flag_hash (mi_final_exts iface) - new_hash <- fingerprintDynFlags hsc_env (mi_module iface) putNameLiterally + let old_hash = mi_sr_flag_hash self_recomp + new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally case old_hash == new_hash of True -> up_to_date logger (text "Module flags unchanged") False -> out_of_date_hash logger FlagsChanged @@ -528,10 +533,10 @@ checkFlagHash hsc_env iface = do old_hash new_hash -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIface -> IO RecompileRequired +checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env - let old_hash = mi_opt_hash (mi_final_exts iface) + let old_hash = mi_sr_opt_hash iface new_hash <- fingerprintOptFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -544,10 +549,10 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIface -> IO RecompileRequired -checkHpcHash hsc_env iface = do +checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_hpc_hash (mi_final_exts iface) + let old_hash = mi_sr_hpc_hash self_recomp new_hash <- fingerprintHpcFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -561,11 +566,11 @@ checkHpcHash hsc_env iface = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIface -> IO RecompileRequired -checkMergedSignatures hsc_env mod_summary iface = do +checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env - let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_usages iface ] + let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_sr_usages self_recomp ] new_merged = case lookupUniqMap (requirementContext unit_state) (ms_mod_name mod_summary) of Nothing -> [] @@ -939,6 +944,28 @@ we use is: -} +-- | Compute the information needed for self-recompilation checking. This +-- information can be computed before the backend phase. +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp hsc_env this_mod src_hash usages = do + let dflags = hsc_dflags hsc_env + + flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + + opt_hash <- fingerprintOptFlags dflags putNameLiterally + + hpc_hash <- fingerprintHpcFlags dflags putNameLiterally + + plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + + return (ModIfaceSelfRecomp + { mi_sr_flag_hash = flag_hash + , mi_sr_hpc_hash = hpc_hash + , mi_sr_opt_hash = opt_hash + , mi_sr_plugin_hash = plugin_hash + , mi_sr_src_hash = src_hash + , mi_sr_usages = usages }) + -- | Add fingerprints for top-level declarations to a 'ModIface'. -- -- See Note [Fingerprinting IfaceDecls] @@ -1213,18 +1240,6 @@ addFingerprints hsc_env iface0 sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - -- the flag hash depends on: - -- - (some of) dflags - -- it returns two hashes, one that shouldn't change - -- the abi hash and one that should - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally - - opt_hash <- fingerprintOptFlags dflags putNameLiterally - - hpc_hash <- fingerprintHpcFlags dflags putNameLiterally - - plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) - -- the ABI hash depends on: -- - decls -- - export list @@ -1238,6 +1253,7 @@ addFingerprints hsc_env iface0 mi_warns iface0, mi_foreign iface0) + -- The interface hash depends on: -- - the ABI hash, plus -- - the source file hash, @@ -1246,21 +1262,17 @@ addFingerprints hsc_env iface0 -- - deps (home and external packages, dependent files) -- - hpc iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - mi_src_hash iface0, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_usages iface0, - sorted_deps, - mi_hpc iface0) + (mod_hash, + mi_src_hash iface0, + ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache + mi_usages iface0, + sorted_deps, + mi_hpc iface0) let final_iface_exts = ModIfaceBackend - { mi_iface_hash = iface_hash - , mi_mod_hash = mod_hash - , mi_flag_hash = flag_hash - , mi_opt_hash = opt_hash - , mi_hpc_hash = hpc_hash - , mi_plugin_hash = plugin_hash + { mi_mod_hash = mod_hash + , mi_iface_hash = iface_hash , mi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts @@ -1281,12 +1293,12 @@ addFingerprints hsc_env iface0 where this_mod = mi_module iface0 semantic_mod = mi_semantic_module iface0 - dflags = hsc_dflags hsc_env (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) ann_fn = mkIfaceAnnCache (mi_anns iface0) + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the -- current module). ===================================== compiler/GHC/Unit/Module/ModGuts.hs ===================================== @@ -53,7 +53,7 @@ data ModGuts mg_exports :: ![AvailInfo], -- ^ What it exports mg_deps :: !Dependencies, -- ^ What it depends on, directly or -- otherwise - mg_usages :: ![Usage], -- ^ What was used? Used for interfaces. + mg_usages :: !(Maybe [Usage]), -- ^ What was used? Used for interfaces. mg_used_th :: !Bool, -- ^ Did we run a TH splice? mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -15,7 +15,6 @@ module GHC.Unit.Module.ModIface , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -36,19 +35,16 @@ module GHC.Unit.Module.ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info ) , pattern ModIface - , restoreFromOldModIface - , addSourceFingerprint , set_mi_module , set_mi_sig_of , set_mi_hsc_src - , set_mi_src_hash + , set_mi_self_recomp , set_mi_hi_bytes , set_mi_deps - , set_mi_usages , set_mi_exports , set_mi_used_th , set_mi_fixities @@ -73,6 +69,8 @@ module GHC.Unit.Module.ModIface , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) + , ModIfaceSelfRecomp (..) + , withSelfRecomp , IfaceDeclExts , IfaceBackendExts , IfaceExport @@ -85,6 +83,12 @@ module GHC.Unit.Module.ModIface , mi_semantic_module , mi_free_holes , mi_mnwib + , mi_flag_hash + , mi_opt_hash + , mi_hpc_hash + , mi_plugin_hash + , mi_src_hash + , mi_usages , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,6 +110,8 @@ import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.ModIface.SelfRecomp + import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env @@ -150,19 +156,10 @@ type ModIface = ModIface_ 'ModIfaceFinal -- * Or computed just before writing the iface to disk. (Hashes) -- In order to fully instantiate it. data ModIfaceBackend = ModIfaceBackend - { mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_mod_hash :: !Fingerprint + { mi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_flag_hash :: !Fingerprint - -- ^ Hash of the important flags used when compiling the module, excluding - -- optimisation flags - , mi_opt_hash :: !Fingerprint - -- ^ Hash of optimisation flags - , mi_hpc_hash :: !Fingerprint - -- ^ Hash of hpc flags - , mi_plugin_hash :: !Fingerprint - -- ^ Hash of plugins + , mi_iface_hash :: !Fingerprint + -- ^ Hash of the whole interface , mi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans , mi_finsts :: !WhetherHasFamInst @@ -218,6 +215,15 @@ data IfaceBinHandle (phase :: ModIfacePhase) where -- (e.g., set to 'Nothing'). FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal + +withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp iface nk jk = + case mi_self_recomp_info iface of + Nothing -> nk + Just x -> jk x + + + -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, -- and can be written out to an interface file. The 'ModDetails is after @@ -245,16 +251,6 @@ data ModIface_ (phase :: ModIfacePhase) -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages_ :: [Usage], - -- ^ Usages; kept sorted so that it's easy to decide - -- whether to write a new iface file (changing usages - -- doesn't affect the hash of this module) - -- NOT STRICT! we read this field lazily from the interface file - -- It is *only* consulted by the recompilation checker - -- - -- The elements must be *deterministically* sorted to guarantee - -- deterministic interface files - mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier @@ -345,13 +341,15 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash_ :: !Fingerprint, - -- ^ Hash of the .hs source, used for recompilation checking. - mi_hi_bytes_ :: !(IfaceBinHandle phase) + mi_hi_bytes_ :: !(IfaceBinHandle phase), -- ^ A serialised in-memory buffer of this 'ModIface'. -- If this handle is given, we can avoid serialising the 'ModIface' -- when writing this 'ModIface' to disk, and write this buffer to disk instead. -- See Note [Sharing of ModIface]. + + mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] } -- Enough information to reconstruct the top level environment for a module @@ -397,6 +395,24 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} +mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ + +mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ + +mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ + +mi_src_hash :: ModIface_ phase -> Maybe Fingerprint +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ + +mi_usages :: ModIface_ phase -> Maybe [Usage] +mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ + +mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ + -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. mi_boot :: ModIface -> IsBootInterface @@ -454,9 +470,6 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance - -- because we are going to write it - -- out separately in the actual file mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then @@ -464,7 +477,6 @@ instance Binary ModIface where -- the byte array. -- See Note [Private fields in ModIface] mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_fixities_ = fixities, @@ -486,13 +498,10 @@ instance Binary ModIface where mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file + mi_self_recomp_info_ = self_recomp, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -501,16 +510,12 @@ instance Binary ModIface where put_ bh mod put_ bh sig_of put_ bh hsc_src - put_ bh iface_hash + put_ bh self_recomp put_ bh mod_hash - put_ bh flag_hash - put_ bh opt_hash - put_ bh hpc_hash - put_ bh plugin_hash + put_ bh iface_hash put_ bh orphan put_ bh hasFamInsts lazyPut bh deps - lazyPut bh usages put_ bh exports put_ bh exp_hash put_ bh used_th @@ -536,16 +541,12 @@ instance Binary ModIface where mod <- get bh sig_of <- get bh hsc_src <- get bh - iface_hash <- get bh + self_recomp_info <- get bh mod_hash <- get bh - flag_hash <- get bh - opt_hash <- get bh - hpc_hash <- get bh - plugin_hash <- get bh + iface_hash <- get bh orphan <- get bh hasFamInsts <- get bh deps <- lazyGet bh - usages <- {-# SCC "bin_usages" #-} lazyGet bh exports <- {-# SCC "bin_exports" #-} get bh exp_hash <- get bh used_th <- get bh @@ -570,15 +571,12 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = fingerprint0, -- placeholder because this is dealt - -- with specially when the file is read mi_hi_bytes_ = -- We can't populate this field here, as we are -- missing the 'mi_ext_fields_' field, which is -- handled in 'getIfaceWithExtFields'. FullIfaceBinHandle Strict.Nothing, mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_anns_ = anns, @@ -600,13 +598,10 @@ instance Binary ModIface where mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read + mi_self_recomp_info_ = self_recomp_info, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -625,10 +620,8 @@ emptyPartialModIface mod { mi_module_ = mod, mi_sig_of_ = Nothing, mi_hsc_src_ = HsSrcFile, - mi_src_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_usages_ = [], mi_exports_ = [], mi_used_th_ = False, mi_fixities_ = [], @@ -648,21 +641,19 @@ emptyPartialModIface mod mi_complete_matches_ = [], mi_docs_ = Nothing, mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields + mi_ext_fields_ = emptyExtensibleFields, + mi_self_recomp_info_ = Nothing } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) { mi_decls_ = [] + , mi_self_recomp_info_ = Nothing , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing , mi_final_exts_ = ModIfaceBackend - { mi_iface_hash = fingerprint0, - mi_mod_hash = fingerprint0, - mi_flag_hash = fingerprint0, - mi_opt_hash = fingerprint0, - mi_hpc_hash = fingerprint0, - mi_plugin_hash = fingerprint0, + { mi_mod_hash = fingerprint0, + mi_iface_hash = fingerprint0, mi_orphan = False, mi_finsts = False, mi_exp_hash = fingerprint0, @@ -692,18 +683,17 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_, mi_src_hash_ }) + , mi_ext_fields_ }) = rnf mi_module_ `seq` rnf mi_sig_of_ `seq` mi_hsc_src_ `seq` mi_hi_bytes_ `seq` mi_deps_ - `seq` mi_usages_ `seq` mi_exports_ `seq` rnf mi_used_th_ `seq` mi_fixities_ @@ -724,20 +714,14 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_docs_ `seq` mi_final_exts_ `seq` mi_ext_fields_ - `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_iface_hash, mi_mod_hash, mi_flag_hash, mi_opt_hash - , mi_hpc_hash, mi_plugin_hash, mi_orphan, mi_finsts, mi_exp_hash + rnf (ModIfaceBackend{ mi_mod_hash + , mi_orphan, mi_finsts, mi_exp_hash , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn , mi_hash_fn}) - = rnf mi_iface_hash - `seq` rnf mi_mod_hash - `seq` rnf mi_flag_hash - `seq` rnf mi_opt_hash - `seq` rnf mi_hpc_hash - `seq` rnf mi_plugin_hash + = rnf mi_mod_hash `seq` rnf mi_orphan `seq` rnf mi_finsts `seq` rnf mi_exp_hash @@ -803,27 +787,6 @@ completePartialModIface partial decls extra_decls final_exts = partial , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing } --- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array --- buffer 'mi_hi_bytes'. --- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. --- --- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. -addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase -addSourceFingerprint val iface = iface { mi_src_hash_ = val } - --- | Copy fields that aren't serialised to disk to the new 'ModIface_'. --- This includes especially hashes that are usually stored in the interface --- file header. --- --- We need this function after calling 'shareIface', to make sure the --- 'ModIface_' doesn't lose any information. This function does not discard --- the in-memory byte array buffer 'mi_hi_bytes'. -restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase -restoreFromOldModIface old new = new - { mi_hsc_src_ = mi_hsc_src_ old - , mi_src_hash_ = mi_src_hash_ old - } - set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } @@ -833,8 +796,8 @@ set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } -set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase -set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } +set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -842,9 +805,6 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } -set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase -set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } - set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } @@ -969,7 +929,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} -{-# INLINE mi_usages #-} {-# INLINE mi_exports #-} {-# INLINE mi_used_th #-} {-# INLINE mi_fixities #-} @@ -989,25 +948,23 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_docs #-} {-# INLINE mi_final_exts #-} {-# INLINE mi_ext_fields #-} -{-# INLINE mi_src_hash #-} {-# INLINE mi_hi_bytes #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + Module -> Maybe Module -> HscSource -> Dependencies -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface { mi_module , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -1028,14 +985,13 @@ pattern ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info } <- PrivateModIface { mi_module_ = mi_module , mi_sig_of_ = mi_sig_of , mi_hsc_src_ = mi_hsc_src , mi_deps_ = mi_deps - , mi_usages_ = mi_usages , mi_exports_ = mi_exports , mi_used_th_ = mi_used_th , mi_fixities_ = mi_fixities @@ -1056,6 +1012,6 @@ pattern ModIface , mi_docs_ = mi_docs , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields - , mi_src_hash_ = mi_src_hash , mi_hi_bytes_ = mi_hi_bytes + , mi_self_recomp_info_ = mi_self_recomp_info } ===================================== compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs ===================================== @@ -0,0 +1,111 @@ +module GHC.Unit.Module.ModIface.SelfRecomp where + +import GHC.Prelude +import GHC.Fingerprint +import GHC.Utils.Outputable +import GHC.Unit.Module.Deps + +import GHC.Utils.Binary + +import Control.DeepSeq + +{- +Note [Self recompilation information in interface files] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The flag -fwrite-if-self-recomp controls whether +interface files contain the information necessary to answer the +question: + + Is the interface file up-to-date, relative to: + * the source file it corresponds to, + * the flags passed to the GHC invocation to compile it, + * its dependencies (e.g. imported items, watched files added by addDependentFile, ...) + +If there is no self-recompilation information stored, then we always re-generate +the interface file from scratch. + +Why? Most packages are only built once either by a distribution or cabal +and then placed into an immutable store, after which we will never ask +this question. Therefore we can derive two benefits from omitting this +information. + +* Primary motivation: It vastly reduces the surface area for creating + non-deterministic interface files. See issue #10424 which motivated a + proper fix to that issue. Distributions have long contained versions + of GHC which just have broken self-recompilation checking (in order to + get deterministic interface files). + +* Secondary motivation: This reduces the size of interface files + slightly.. the `mi_usages` field can be quite big but probably this + isn't such a great benefit. + +* Third motivation: Conceptually clarity about which parts of an + interface file are used in order to **communicate** with subsequent + packages about the **interface** for a module. And which parts are + used to self-communicate during recompilation checking. + +The main tracking issue is #22188 but fixes issues such as #10424 in a +proper way. + +-} + +-- | The information for a module which is only used when deciding whether to recompile +-- itself. +-- +-- See Note [Self recompilation information in interface files] +data ModIfaceSelfRecomp = + ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint + -- ^ Hash of the .hs source, used for recompilation checking. + , mi_sr_usages :: [Usage] + -- ^ Usages; kept sorted so that it's easy to decide + -- whether to write a new iface file (changing usages + -- doesn't affect the hash of this module) + -- NOT STRICT! we read this field lazily from the interface file + -- It is *only* consulted by the recompilation checker + + , mi_sr_flag_hash :: !Fingerprint + -- ^ Hash of the important flags used when compiling the module, excluding + -- optimisation flags + , mi_sr_opt_hash :: !Fingerprint + -- ^ Hash of optimisation flags + , mi_sr_hpc_hash :: !Fingerprint + -- ^ Hash of hpc flags + , mi_sr_plugin_hash :: !Fingerprint + -- ^ Hash of plugins + } + + +instance Binary ModIfaceSelfRecomp where + put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do + put_ bh mi_sr_src_hash + lazyPut bh mi_sr_usages + put_ bh mi_sr_flag_hash + put_ bh mi_sr_opt_hash + put_ bh mi_sr_hpc_hash + put_ bh mi_sr_plugin_hash + + get bh = do + src_hash <- get bh + usages <- lazyGet bh + flag_hash <- get bh + opt_hash <- get bh + hpc_hash <- get bh + plugin_hash <- get bh + return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + +instance Outputable ModIfaceSelfRecomp where + ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) + = vcat [text "Self-Recomp" + , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash + , text "usages:" <+> ppr (length mi_sr_usages) + , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "opt hash:" <+> ppr mi_sr_opt_hash + , text "hpc hash:" <+> ppr mi_sr_hpc_hash + , text "plugin hash:" <+> ppr mi_sr_plugin_hash + ])] + +instance NFData ModIfaceSelfRecomp where + -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so + -- I left it as a shallow force. + rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file ===================================== compiler/ghc.cabal.in ===================================== @@ -955,6 +955,7 @@ Library GHC.Unit.Module.ModDetails GHC.Unit.Module.ModGuts GHC.Unit.Module.ModIface + GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.WholeCoreBindings GHC.Unit.Module.ModSummary GHC.Unit.Module.Status ===================================== docs/users_guide/phases.rst ===================================== @@ -702,6 +702,24 @@ Options affecting code generation depend on the optimisation level. Any definitions which are already included in an interface file (via an unfolding for an exported identifier) are reused. +.. ghc-flag:: -fwrite-if-self-recomp + :shortdesc: Write information for self-recompilation checking in an interface file + :type: dynamic + :category: codegen + + :default: on + + Include information in an interface file which can be used in future to determine + whether we need to recompile a module or can reuse the existing interface. + + This is intended to be turned off in situations where you know you will never try + to recompile a module, such as when compiling a package for distribution. + The advantage is that by omitting unecessary information to do with dependencies + there is less chance of build paths leaking into the interface file and affecting + determinism. + + + .. ghc-flag:: -fobject-code :shortdesc: Generate object code ===================================== hadrian/doc/flavours.md ===================================== @@ -107,7 +107,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH <td>-O2</td> </tr> <tr> - <th>release (same as perf with -haddock)</td> + <th>release (same as perf with -haddock and +no_self_recomp)</td> <td></td> <td>-O<br>-H64m</td> <td>-O<br>-H64m</td> @@ -329,6 +329,10 @@ The supported transformers are listed below: <td><code>dump_stg</code></td> <td>Dump STG of all modules compiled by a stage1 compiler to a file</td> </tr> + <tr> + <td><code>no_self_recomp</code></td> + <td>Disable including self-recompilation information in interface files via <code>-fno-write-if-self-recomp</code>. If you are building a distribution you can enable this flag to produce more deterministic interface files.</td> + </tr> </table> ### Static ===================================== hadrian/src/Flavour.hs ===================================== @@ -16,6 +16,7 @@ module Flavour , disableProfiledLibs , enableLinting , enableHaddock + , disableSelfRecompInfo , enableHiCore , useNativeBignum , enableTextWithSIMDUTF @@ -67,6 +68,7 @@ flavourTransformers = M.fromList , "debug_stage1_ghc" =: debugGhc Stage1 , "lint" =: enableLinting , "haddock" =: enableHaddock + , "no_self_recomp" =: disableSelfRecompInfo , "hi_core" =: enableHiCore , "late_ccs" =: enableLateCCS , "boot_nonmoving_gc" =: enableBootNonmovingGc @@ -208,6 +210,17 @@ enableHaddock = [ arg "-haddock" ] +-- | Disable self recompilation information in interface files +disableSelfRecompInfo :: Flavour -> Flavour +disableSelfRecompInfo = + addArgs $ stage1 ? mconcat + [ builder (Ghc CompileHs) ? selfRecomp + ] + where + selfRecomp = mconcat + [ arg "-fno-write-if-self-recomp" + ] + -- | Build stage2 dependencies with options to emit Core into -- interface files which is sufficient to restart code generation. enableHiCore :: Flavour -> Flavour ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,8 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableHaddock performanceFlavour { name = "release" } +releaseFlavour = + -- 1. These interface files will be distributed and the source files never recompiled. + disableSelfRecompInfo + -- 2. Include documentation in the interface for tools such as haddock and HLS to use + $ enableHaddock performanceFlavour { name = "release" } ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -201,6 +201,7 @@ GHC.Unit.Module.Env GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.Warnings GHC.Unit.Module.WholeCoreBindings GHC.Unit.Parser ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -227,6 +227,7 @@ GHC.Unit.Module.Graph GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModIface.SelfRecomp GHC.Unit.Module.ModNodeKey GHC.Unit.Module.ModSummary GHC.Unit.Module.Warnings ===================================== testsuite/tests/driver/self-recomp/Makefile ===================================== @@ -0,0 +1,38 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +TEST_HC_OPTS_NO_RTSOPTS = $(filter-out -rtsopts,$(TEST_HC_OPTS)) + +# ----------------------------------------------------------------------------- +# One-shot compilations, non-hierarchical modules + +# Check that modifying flags doesn't affect interface +SelfRecomp01: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface1 + rm SelfRecomp01.hi + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-if-self-recomp -Iidir -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface2 + diff iface1 iface2 + +# Check that the result of addDependentFile doesn't end up in interface +SelfRecomp02: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp02.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp02.hi > iface + [ -z $(grep iface SelfRecomp02.hs) ] + +# Check that modifying source doesn't affect interface +SelfRecomp03: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface1 + rm SelfRecomp03.hi + echo "" >> SelfRecomp03.hs + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface2 + diff iface1 iface2 + +# Check that if you don't have recompilation info then you always recompile. +SelfRecomp04: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-if-self-recomp -fhide-source-paths + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-if-self-recomp -fhide-source-paths ===================================== testsuite/tests/driver/self-recomp/SelfRecomp01.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp01 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp02.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +module SelfRecomp02 where + +import Language.Haskell.TH.Syntax + +main = $(addDependentFile "SelfRecomp02.hs" >> [| print () |]) ===================================== testsuite/tests/driver/self-recomp/SelfRecomp03.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp03 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.hs ===================================== @@ -0,0 +1 @@ +module SelfRecomp04 where ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.stdout ===================================== @@ -0,0 +1,2 @@ +[1 of 1] Compiling SelfRecomp04 +[1 of 1] Compiling SelfRecomp04 [Old interface lacks recompilation info] ===================================== testsuite/tests/driver/self-recomp/all.T ===================================== @@ -0,0 +1,4 @@ +test('SelfRecomp01', normal, makefile_test, ['SelfRecomp01']) +test('SelfRecomp02', normal, makefile_test, ['SelfRecomp02']) +test('SelfRecomp03', [copy_files], makefile_test, ['SelfRecomp03']) +test('SelfRecomp04', normal, makefile_test, ['SelfRecomp04']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/782f46032853d42952d1c041bd66048efa8d6f65...cf4972430f38429b07ca978faef21d3d4a17d12c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/782f46032853d42952d1c041bd66048efa8d6f65...cf4972430f38429b07ca978faef21d3d4a17d12c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/e6dc47ae/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 09:48:40 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Mar 2025 04:48:40 -0500 Subject: [Git][ghc/ghc][master] perf: Speed up the bytecode assembler Message-ID: <67c81df87731c_343add788b602198a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - 7 changed files: - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T Changes: ===================================== compiler/GHC/ByteCode/Asm.hs ===================================== @@ -1,8 +1,12 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE PatternSynonyms #-} {-# OPTIONS_GHC -optc-DNON_POSIX_SOURCE #-} -- +-- -- (c) The University of Glasgow 2002-2006 -- @@ -12,10 +16,14 @@ module GHC.ByteCode.Asm ( bcoFreeNames, SizedSeq, sizeSS, ssElts, iNTERP_STACK_CHECK_THRESH, - mkNativeCallInfoLit + mkNativeCallInfoLit, + + -- * For testing + assembleBCO ) where -import GHC.Prelude +import GHC.Prelude hiding ( any ) + import GHC.ByteCode.Instr import GHC.ByteCode.InfoTable @@ -29,12 +37,14 @@ import GHC.Types.Name.Set import GHC.Types.Literal import GHC.Types.Unique.DSet import GHC.Types.SptEntry +import GHC.Types.Unique.FM import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Core.TyCon import GHC.Data.SizedSeq +import GHC.Data.SmallArray import GHC.StgToCmm.Layout ( ArgRep(..) ) import GHC.Cmm.Expr @@ -44,19 +54,25 @@ import GHC.Platform import GHC.Platform.Profile import Control.Monad -import Control.Monad.Trans.Class -import Control.Monad.Trans.State.Strict +import qualified Control.Monad.Trans.State.Strict as MTL import qualified Data.Array.Unboxed as Array -import Data.Array.Base ( UArray(..) ) +import qualified Data.Array.IO as Array +import Data.Array.Base ( UArray(..), numElements, unsafeFreeze ) + +#if ! defined(DEBUG) +import Data.Array.Base ( unsafeWrite ) +#endif import Foreign hiding (shiftL, shiftR) -import Data.Char ( ord ) -import Data.Map.Strict (Map) +import Data.Char (ord) import Data.Maybe (fromMaybe) -import qualified Data.Map.Strict as Map import GHC.Float (castFloatToWord32, castDoubleToWord64) +import qualified Data.List as List ( any ) +import GHC.Exts + + -- ----------------------------------------------------------------------------- -- Unlinked BCOs @@ -133,9 +149,9 @@ assembleBCOs interp profile proto_bcos tycons top_strs modbreaks spt_entries = d -- mallocStrings :: Interp -> FlatBag UnlinkedBCO -> IO (FlatBag UnlinkedBCO) mallocStrings interp ulbcos = do - let bytestrings = reverse (execState (mapM_ collect ulbcos) []) + let bytestrings = reverse (MTL.execState (mapM_ collect ulbcos) []) ptrs <- interpCmd interp (MallocStrings bytestrings) - return (evalState (mapM splice ulbcos) ptrs) + return (MTL.evalState (mapM splice ulbcos) ptrs) where splice bco at UnlinkedBCO{..} = do lits <- mapM spliceLit unlinkedBCOLits @@ -143,10 +159,10 @@ mallocStrings interp ulbcos = do return bco { unlinkedBCOLits = lits, unlinkedBCOPtrs = ptrs } spliceLit (BCONPtrStr _) = do - rptrs <- get + rptrs <- MTL.get case rptrs of (RemotePtr p : rest) -> do - put rest + MTL.put rest return (BCONPtrWord (fromIntegral p)) _ -> panic "mallocStrings:spliceLit" spliceLit other = return other @@ -159,13 +175,61 @@ mallocStrings interp ulbcos = do mapM_ collectPtr unlinkedBCOPtrs collectLit (BCONPtrStr bs) = do - strs <- get - put (bs:strs) + strs <- MTL.get + MTL.put (bs:strs) collectLit _ = return () collectPtr (BCOPtrBCO bco) = collect bco collectPtr _ = return () +data RunAsmReader = RunAsmReader { isn_array :: {-# UNPACK #-} !(Array.IOUArray Int Word16) + , ptr_array :: {-# UNPACK #-} !(SmallMutableArrayIO BCOPtr) + , lit_array :: {-# UNPACK #-} !(SmallMutableArrayIO BCONPtr ) + } + +data RunAsmResult = RunAsmResult { final_isn_array :: !(Array.UArray Int Word16) + , final_ptr_array :: !(SmallArray BCOPtr) + , final_lit_array :: !(SmallArray BCONPtr) } + +-- How many words we have written so far. +data AsmState = AsmState { nisn :: !Int, nptr :: !Int, nlit :: !Int } + + +{-# NOINLINE inspectInstrs #-} +-- | Perform analysis of the bytecode to determine +-- 1. How many instructions we will produce +-- 2. If we are going to need long jumps. +-- 3. The offsets that labels refer to +inspectInstrs :: Platform -> Bool -> Word -> [BCInstr] -> InspectState +inspectInstrs platform long_jump e instrs = + inspectAsm long_jump e (mapM_ (assembleInspectAsm platform) instrs) + +{-# NOINLINE runInstrs #-} +-- | Assemble the bytecode from the instructions. +runInstrs :: Platform -> Bool -> InspectState -> [BCInstr] -> IO RunAsmResult +runInstrs platform long_jumps is_state instrs = do + -- Produce arrays of exactly the right size, corresponding to the result of inspectInstrs. + isn_array <- Array.newArray_ (0, (fromIntegral $ instrCount is_state) - 1) + ptr_array <- newSmallArrayIO (fromIntegral $ ptrCount is_state) undefined + lit_array <- newSmallArrayIO (fromIntegral $ litCount is_state) undefined + let env :: LocalLabel -> Word + env lbl = fromMaybe + (pprPanic "assembleBCO.findLabel" (ppr lbl)) + (lookupUFM (lblEnv is_state) lbl) + let initial_state = AsmState 0 0 0 + let initial_reader = RunAsmReader{..} + runAsm long_jumps env initial_reader initial_state (mapM_ (\i -> assembleRunAsm platform i) instrs) + final_isn_array <- unsafeFreeze isn_array + final_ptr_array <- unsafeFreezeSmallArrayIO ptr_array + final_lit_array <- unsafeFreezeSmallArrayIO lit_array + return $ RunAsmResult {..} + +assembleRunAsm :: Platform -> BCInstr -> RunAsm () +assembleRunAsm p i = assembleI @RunAsm p i + +assembleInspectAsm :: Platform -> BCInstr -> InspectAsm () +assembleInspectAsm p i = assembleI @InspectAsm p i + assembleBCO :: Platform -> ProtoBCO Name -> IO UnlinkedBCO assembleBCO platform (ProtoBCO { protoBCOName = nm @@ -174,9 +238,7 @@ assembleBCO platform , protoBCOBitmapSize = bsize , protoBCOArity = arity }) = do -- pass 1: collect up the offsets of the local labels. - let asm = mapM_ (assembleI platform) instrs - - initial_offset = 0 + let initial_offset = 0 -- Jump instructions are variable-sized, there are long and short variants -- depending on the magnitude of the offset. However, we can't tell what @@ -186,30 +248,25 @@ assembleBCO platform -- and if the final size is indeed small enough for short jumps, we are -- done. Otherwise, we repeat the calculation, and we force all jumps in -- this BCO to be long. - (n_insns0, lbl_map0) = inspectAsm platform False initial_offset asm - ((n_insns, lbl_map), long_jumps) - | isLargeW (fromIntegral $ Map.size lbl_map0) - || isLargeW n_insns0 - = (inspectAsm platform True initial_offset asm, True) - | otherwise = ((n_insns0, lbl_map0), False) - - env :: LocalLabel -> Word - env lbl = fromMaybe - (pprPanic "assembleBCO.findLabel" (ppr lbl)) - (Map.lookup lbl lbl_map) + is0 = inspectInstrs platform False initial_offset instrs + (is1, long_jumps) + | isLargeInspectState is0 + = (inspectInstrs platform True initial_offset instrs, True) + | otherwise = (is0, False) + -- pass 2: run assembler and generate instructions, literals and pointers - let initial_state = (emptySS, emptySS, emptySS) - (final_insns, final_lits, final_ptrs) <- flip execStateT initial_state $ runAsm platform long_jumps env asm + RunAsmResult{..} <- runInstrs platform long_jumps is1 instrs -- precomputed size should be equal to final size - massertPpr (n_insns == sizeSS final_insns) + massertPpr (fromIntegral (instrCount is1) == numElements final_isn_array + && fromIntegral (ptrCount is1) == sizeofSmallArray final_ptr_array + && fromIntegral (litCount is1) == sizeofSmallArray final_lit_array) (text "bytecode instruction count mismatch") - let asm_insns = ssElts final_insns - !insns_arr = mkBCOByteArray $ Array.listArray (0 :: Int, fromIntegral n_insns - 1) asm_insns + let !insns_arr = mkBCOByteArray $ final_isn_array !bitmap_arr = mkBCOByteArray $ mkBitmapArray bsize bitmap - ul_bco = UnlinkedBCO nm arity insns_arr bitmap_arr (fromSizedSeq final_lits) (fromSizedSeq final_ptrs) + ul_bco = UnlinkedBCO nm arity insns_arr bitmap_arr (fromSmallArray final_lit_array) (fromSmallArray final_ptr_array) -- 8 Aug 01: Finalisers aren't safe when attached to non-primitive -- objects, since they might get run too early. Disable this until @@ -226,10 +283,6 @@ mkBitmapArray bsize bitmap = Array.listArray (0, length bitmap) $ fromIntegral bsize : map (fromInteger . fromStgWord) bitmap --- instrs nonptrs ptrs -type AsmState = (SizedSeq Word16, - SizedSeq BCONPtr, - SizedSeq BCOPtr) data Operand = Op Word @@ -249,39 +302,9 @@ truncHalfWord platform w = case platformWordSize platform of PW8 | w <= 4294967295 -> Op (fromIntegral w) _ -> pprPanic "GHC.ByteCode.Asm.truncHalfWord" (ppr w) -data Assembler a - = AllocPtr (IO BCOPtr) (Word -> Assembler a) - | AllocLit [BCONPtr] (Word -> Assembler a) - | AllocLabel LocalLabel (Assembler a) - | Emit Word16 [Operand] (Assembler a) - | NullAsm a - deriving (Functor) - -instance Applicative Assembler where - pure = NullAsm - (<*>) = ap - -instance Monad Assembler where - NullAsm x >>= f = f x - AllocPtr p k >>= f = AllocPtr p (k >=> f) - AllocLit l k >>= f = AllocLit l (k >=> f) - AllocLabel lbl k >>= f = AllocLabel lbl (k >>= f) - Emit w ops k >>= f = Emit w ops (k >>= f) - -ioptr :: IO BCOPtr -> Assembler Word -ioptr p = AllocPtr p return - -ptr :: BCOPtr -> Assembler Word -ptr = ioptr . return - -lit :: [BCONPtr] -> Assembler Word -lit l = AllocLit l return -label :: LocalLabel -> Assembler () -label w = AllocLabel w (return ()) - -emit :: Word16 -> [Operand] -> Assembler () -emit w ops = Emit w ops (return ()) +ptr :: MonadAssembler m => BCOPtr -> m Word +ptr = ioptr . return type LabelEnv = LocalLabel -> Word @@ -292,38 +315,142 @@ largeOp long_jumps op = case op of IOp i -> isLargeI i LabelOp _ -> long_jumps -runAsm :: Platform -> Bool -> LabelEnv -> Assembler a -> StateT AsmState IO a -runAsm platform long_jumps e = go +newtype RunAsm a = RunAsm' { runRunAsm :: Bool + -> LabelEnv + -> RunAsmReader + -> AsmState + -> IO (AsmState, a) } + +pattern RunAsm :: (Bool -> LabelEnv -> RunAsmReader -> AsmState -> IO (AsmState, a)) + -> RunAsm a +pattern RunAsm m <- RunAsm' m where - go (NullAsm x) = return x - go (AllocPtr p_io k) = do - p <- lift p_io - w <- state $ \(st_i0,st_l0,st_p0) -> - let st_p1 = addToSS st_p0 p - in (sizeSS st_p0, (st_i0,st_l0,st_p1)) - go $ k w - go (AllocLit lits k) = do - w <- state $ \(st_i0,st_l0,st_p0) -> - let st_l1 = addListToSS st_l0 lits - in (sizeSS st_l0, (st_i0,st_l1,st_p0)) - go $ k w - go (AllocLabel _ k) = go k - go (Emit w ops k) = do - let largeArgs = any (largeOp long_jumps) ops - opcode - | largeArgs = largeArgInstr w - | otherwise = w - words = concatMap expand ops - expand (SmallOp w) = [w] - expand (LabelOp w) = expand (Op (e w)) - expand (Op w) = if largeArgs then largeArg platform (fromIntegral w) else [fromIntegral w] - expand (IOp i) = if largeArgs then largeArg platform (fromIntegral i) else [fromIntegral i] - state $ \(st_i0,st_l0,st_p0) -> - let st_i1 = addListToSS st_i0 (opcode : words) - in ((), (st_i1,st_l0,st_p0)) - go k - -type LabelEnvMap = Map LocalLabel Word + RunAsm m = RunAsm' (oneShot $ \a -> oneShot $ \b -> oneShot $ \c -> oneShot $ \d -> m a b c d) +{-# COMPLETE RunAsm #-} + +instance Functor RunAsm where + fmap f (RunAsm x) = RunAsm (\a b c !s -> fmap (fmap f) (x a b c s)) + +instance Applicative RunAsm where + pure x = RunAsm $ \_ _ _ !s -> pure (s, x) + (RunAsm f) <*> (RunAsm x) = RunAsm $ \a b c !s -> do + (!s', f') <- f a b c s + (!s'', x') <- x a b c s' + return (s'', f' x') + {-# INLINE (<*>) #-} + + +instance Monad RunAsm where + return = pure + (RunAsm m) >>= f = RunAsm $ \a b c !s -> m a b c s >>= \(s', r) -> runRunAsm (f r) a b c s' + {-# INLINE (>>=) #-} + +runAsm :: Bool -> LabelEnv -> RunAsmReader -> AsmState -> RunAsm a -> IO a +runAsm long_jumps e r s (RunAsm'{runRunAsm}) = fmap snd $ runRunAsm long_jumps e r s + +expand :: PlatformWordSize -> Bool -> Operand -> RunAsm () +expand word_size largeArgs o = do + e <- askEnv + case o of + (SmallOp w) -> writeIsn w + (LabelOp w) -> let !r = e w in handleLargeArg r + (Op w) -> handleLargeArg w + (IOp i) -> handleLargeArg i + + where + handleLargeArg :: Integral a => a -> RunAsm () + handleLargeArg w = + if largeArgs + then largeArg word_size (fromIntegral w) + else writeIsn (fromIntegral w) + +lift :: IO a -> RunAsm a +lift io = RunAsm $ \_ _ _ s -> io >>= \a -> pure (s, a) + +askLongJumps :: RunAsm Bool +askLongJumps = RunAsm $ \a _ _ s -> pure (s, a) + +askEnv :: RunAsm LabelEnv +askEnv = RunAsm $ \_ b _ s -> pure (s, b) + +writePtr :: BCOPtr -> RunAsm Word +writePtr w + = RunAsm $ \_ _ (RunAsmReader{..}) asm -> do + writeSmallArrayIO ptr_array (nptr asm) w + let !n' = nptr asm + 1 + let !asm' = asm { nptr = n' } + return (asm', fromIntegral (nptr asm)) + +writeLit :: BCONPtr -> RunAsm Word +writeLit w = RunAsm $ \_ _ (RunAsmReader{..}) asm -> do + writeSmallArrayIO lit_array (nlit asm) w + let !n' = nlit asm + 1 + let !asm' = asm { nlit = n' } + return (asm', fromIntegral (nlit asm)) + +writeLits :: OneOrTwo BCONPtr -> RunAsm Word +writeLits (OnlyOne l) = writeLit l +writeLits (OnlyTwo l1 l2) = writeLit l1 <* writeLit l2 + +writeIsn :: Word16 -> RunAsm () +writeIsn w = RunAsm $ \_ _ (RunAsmReader{..}) asm -> do +#if defined(DEBUG) + Array.writeArray isn_array (nisn asm) w +#else + unsafeWrite isn_array (nisn asm) w +#endif + let !n' = nisn asm + 1 + let !asm' = asm { nisn = n' } + return (asm', ()) + +{-# INLINE any #-} +-- Any is unrolled manually so that the call in `emit` can be eliminated without +-- relying on SpecConstr (which does not work across modules). +any :: (a -> Bool) -> [a] -> Bool +any _ [] = False +any f [x] = f x +any f [x,y] = f x || f y +any f [x,y,z] = f x || f y || f z +any f [x1,x2,x3,x4] = f x1 || f x2 || f x3 || f x4 +any f [x1,x2,x3,x4, x5] = f x1 || f x2 || f x3 || f x4 || f x5 +any f [x1,x2,x3,x4,x5,x6] = f x1 || f x2 || f x3 || f x4 || f x5 || f x6 +any f xs = List.any f xs + +{-# INLINE mapM6_ #-} +mapM6_ :: Monad m => (a -> m b) -> [a] -> m () +mapM6_ _ [] = return () +mapM6_ f [x] = () <$ f x +mapM6_ f [x,y] = () <$ f x <* f y +mapM6_ f [x,y,z] = () <$ f x <* f y <* f z +mapM6_ f [a1,a2,a3,a4] = () <$ f a1 <* f a2 <* f a3 <* f a4 +mapM6_ f [a1,a2,a3,a4,a5] = () <$ f a1 <* f a2 <* f a3 <* f a4 <* f a5 +mapM6_ f [a1,a2,a3,a4,a5,a6] = () <$ f a1 <* f a2 <* f a3 <* f a4 <* f a5 <* f a6 +mapM6_ f xs = mapM_ f xs + +instance MonadAssembler RunAsm where + ioptr p_io = do + p <- lift p_io + writePtr p + lit lits = writeLits lits + + label _ = return () + + emit pwordsize w ops = do + long_jumps <- askLongJumps + -- See the definition of `any` above + let largeArgs = any (largeOp long_jumps) ops + let opcode + | largeArgs = largeArgInstr w + | otherwise = w + writeIsn opcode + mapM6_ (expand pwordsize largeArgs) ops + + {-# INLINE emit #-} + {-# INLINE label #-} + {-# INLINE lit #-} + {-# INLINE ioptr #-} + +type LabelEnvMap = UniqFM LocalLabel Word data InspectState = InspectState { instrCount :: !Word @@ -332,27 +459,105 @@ data InspectState = InspectState , lblEnv :: LabelEnvMap } +instance Outputable InspectState where + ppr (InspectState i p l m) = text "InspectState" <+> ppr [ppr i, ppr p, ppr l, ppr (sizeUFM m)] + +isLargeInspectState :: InspectState -> Bool +isLargeInspectState InspectState{..} = + isLargeW (fromIntegral $ sizeUFM lblEnv) + || isLargeW instrCount -inspectAsm :: Platform -> Bool -> Word -> Assembler a -> (Word, LabelEnvMap) -inspectAsm platform long_jumps initial_offset - = go (InspectState initial_offset 0 0 Map.empty) +newtype InspectEnv = InspectEnv { _inspectLongJumps :: Bool + } + +newtype InspectAsm a = InspectAsm' { runInspectAsm :: InspectEnv -> InspectState -> (# InspectState, a #) } + +pattern InspectAsm :: (InspectEnv -> InspectState -> (# InspectState, a #)) + -> InspectAsm a +pattern InspectAsm m <- InspectAsm' m where - go s (NullAsm _) = (instrCount s, lblEnv s) - go s (AllocPtr _ k) = go (s { ptrCount = n + 1 }) (k n) - where n = ptrCount s - go s (AllocLit ls k) = go (s { litCount = n + strictGenericLength ls }) (k n) - where n = litCount s - go s (AllocLabel lbl k) = go s' k - where s' = s { lblEnv = Map.insert lbl (instrCount s) (lblEnv s) } - go s (Emit _ ops k) = go s' k - where - s' = s { instrCount = instrCount s + size } - size = sum (map count ops) + 1 + InspectAsm m = InspectAsm' (oneShot $ \a -> oneShot $ \b -> m a b) +{-# COMPLETE InspectAsm #-} + +instance Functor InspectAsm where + fmap f (InspectAsm k) = InspectAsm $ \a b -> case k a b of + (# b', c #) -> (# b', f c #) + +instance Applicative InspectAsm where + pure x = InspectAsm $ \_ s -> (# s, x #) + (InspectAsm f) <*> (InspectAsm x) = InspectAsm $ \a b -> case f a b of + (# s', f' #) -> + case x a s' of + (# s'', x' #) -> (# s'', f' x' #) + +instance Monad InspectAsm where + return = pure + (InspectAsm m) >>= f = InspectAsm $ \ a b -> case m a b of + (# s', a' #) -> runInspectAsm (f a') a s' + +get_ :: InspectAsm InspectState +get_ = InspectAsm $ \_ b -> (# b, b #) + +put_ :: InspectState -> InspectAsm () +put_ !s = InspectAsm $ \_ _ -> (# s, () #) + +modify_ :: (InspectState -> InspectState) -> InspectAsm () +modify_ f = InspectAsm $ \_ s -> let !s' = f s in (# s', () #) + +ask_ :: InspectAsm InspectEnv +ask_ = InspectAsm $ \a b -> (# b, a #) + +inspectAsm :: Bool -> Word -> InspectAsm () -> InspectState +inspectAsm long_jumps initial_offset (InspectAsm s) = + case s (InspectEnv long_jumps) (InspectState initial_offset 0 0 emptyUFM) of + (# res, () #) -> res +{-# INLINE inspectAsm #-} + + + +instance MonadAssembler InspectAsm where + ioptr _ = do + s <- get_ + let n = ptrCount s + put_ (s { ptrCount = n + 1 }) + return n + + lit ls = do + s <- get_ + let n = litCount s + put_ (s { litCount = n + oneTwoLength ls }) + return n + + label lbl = modify_ (\s -> let !count = instrCount s in let !env' = addToUFM (lblEnv s) lbl count in s { lblEnv = env' }) + + emit pwordsize _ ops = do + InspectEnv long_jumps <- ask_ + -- Size is written in this way as `mapM6_` is also used by RunAsm, and guaranteed + -- to unroll for arguments up to size 6. + let size = (MTL.execState (mapM6_ (\x -> MTL.modify (count' x +)) ops) 0) + 1 largeOps = any (largeOp long_jumps) ops - count (SmallOp _) = 1 - count (LabelOp _) = count (Op 0) - count (Op _) = if largeOps then largeArg16s platform else 1 - count (IOp _) = if largeOps then largeArg16s platform else 1 + bigSize = largeArg16s pwordsize + count' = if largeOps then countLarge bigSize else countSmall bigSize + + s <- get_ + put_ (s { instrCount = instrCount s + size }) + + {-# INLINE emit #-} + {-# INLINE label #-} + {-# INLINE lit #-} + {-# INLINE ioptr #-} + +count :: Word -> Bool -> Operand -> Word +count _ _ (SmallOp _) = 1 +count big largeOps (LabelOp _) = if largeOps then big else 1 +count big largeOps (Op _) = if largeOps then big else 1 +count big largeOps (IOp _) = if largeOps then big else 1 +{-# INLINE count #-} + +countSmall, countLarge :: Word -> Operand -> Word +countLarge big x = count big True x +countSmall big x = count big False x + -- Bring in all the bci_ bytecode constants. #include "Bytecodes.h" @@ -360,47 +565,67 @@ inspectAsm platform long_jumps initial_offset largeArgInstr :: Word16 -> Word16 largeArgInstr bci = bci_FLAG_LARGE_ARGS .|. bci -largeArg :: Platform -> Word64 -> [Word16] -largeArg platform w = case platformWordSize platform of - PW8 -> [fromIntegral (w `shiftR` 48), - fromIntegral (w `shiftR` 32), - fromIntegral (w `shiftR` 16), - fromIntegral w] +{-# INLINE largeArg #-} +largeArg :: PlatformWordSize -> Word64 -> RunAsm () +largeArg wsize w = case wsize of + PW8 -> do writeIsn (fromIntegral (w `shiftR` 48)) + writeIsn (fromIntegral (w `shiftR` 32)) + writeIsn (fromIntegral (w `shiftR` 16)) + writeIsn (fromIntegral w) PW4 -> assertPpr (w < fromIntegral (maxBound :: Word32)) - (text "largeArg too big:" <+> ppr w) $ - [fromIntegral (w `shiftR` 16), - fromIntegral w] + (text "largeArg too big:" <+> ppr w) $ do + writeIsn (fromIntegral (w `shiftR` 16)) + writeIsn (fromIntegral w) -largeArg16s :: Platform -> Word -largeArg16s platform = case platformWordSize platform of +largeArg16s :: PlatformWordSize -> Word +largeArg16s pwordsize = case pwordsize of PW8 -> 4 PW4 -> 2 -assembleI :: Platform +data OneOrTwo a = OnlyOne a | OnlyTwo a a deriving (Functor) + +oneTwoLength :: OneOrTwo a -> Word +oneTwoLength (OnlyOne {}) = 1 +oneTwoLength (OnlyTwo {}) = 2 + +class Monad m => MonadAssembler m where + ioptr :: IO BCOPtr -> m Word + lit :: OneOrTwo BCONPtr -> m Word + label :: LocalLabel -> m () + emit :: PlatformWordSize -> Word16 -> [Operand] -> m () + +lit1 :: MonadAssembler m => BCONPtr -> m Word +lit1 p = lit (OnlyOne p) + +{-# SPECIALISE assembleI :: Platform -> BCInstr -> InspectAsm () #-} +{-# SPECIALISE assembleI :: Platform -> BCInstr -> RunAsm () #-} + +assembleI :: forall m . MonadAssembler m + => Platform -> BCInstr - -> Assembler () + -> m () assembleI platform i = case i of - STKCHECK n -> emit bci_STKCHECK [Op n] - PUSH_L o1 -> emit bci_PUSH_L [wOp o1] - PUSH_LL o1 o2 -> emit bci_PUSH_LL [wOp o1, wOp o2] - PUSH_LLL o1 o2 o3 -> emit bci_PUSH_LLL [wOp o1, wOp o2, wOp o3] - PUSH8 o1 -> emit bci_PUSH8 [bOp o1] - PUSH16 o1 -> emit bci_PUSH16 [bOp o1] - PUSH32 o1 -> emit bci_PUSH32 [bOp o1] - PUSH8_W o1 -> emit bci_PUSH8_W [bOp o1] - PUSH16_W o1 -> emit bci_PUSH16_W [bOp o1] - PUSH32_W o1 -> emit bci_PUSH32_W [bOp o1] + STKCHECK n -> emit_ bci_STKCHECK [Op n] + PUSH_L o1 -> emit_ bci_PUSH_L [wOp o1] + PUSH_LL o1 o2 -> emit_ bci_PUSH_LL [wOp o1, wOp o2] + PUSH_LLL o1 o2 o3 -> emit_ bci_PUSH_LLL [wOp o1, wOp o2, wOp o3] + PUSH8 o1 -> emit_ bci_PUSH8 [bOp o1] + PUSH16 o1 -> emit_ bci_PUSH16 [bOp o1] + PUSH32 o1 -> emit_ bci_PUSH32 [bOp o1] + PUSH8_W o1 -> emit_ bci_PUSH8_W [bOp o1] + PUSH16_W o1 -> emit_ bci_PUSH16_W [bOp o1] + PUSH32_W o1 -> emit_ bci_PUSH32_W [bOp o1] PUSH_G nm -> do p <- ptr (BCOPtrName nm) - emit bci_PUSH_G [Op p] + emit_ bci_PUSH_G [Op p] PUSH_PRIMOP op -> do p <- ptr (BCOPtrPrimOp op) - emit bci_PUSH_G [Op p] + emit_ bci_PUSH_G [Op p] PUSH_BCO proto -> do let ul_bco = assembleBCO platform proto p <- ioptr (liftM BCOPtrBCO ul_bco) - emit bci_PUSH_G [Op p] + emit_ bci_PUSH_G [Op p] PUSH_ALTS proto pk -> do let ul_bco = assembleBCO platform proto p <- ioptr (liftM BCOPtrBCO ul_bco) - emit (push_alts pk) [Op p] + emit_ (push_alts pk) [Op p] PUSH_ALTS_TUPLE proto call_info tuple_proto -> do let ul_bco = assembleBCO platform proto ul_tuple_bco = assembleBCO platform @@ -409,127 +634,131 @@ assembleI platform i = case i of p_tup <- ioptr (liftM BCOPtrBCO ul_tuple_bco) info <- word (fromIntegral $ mkNativeCallInfoSig platform call_info) - emit bci_PUSH_ALTS_T + emit_ bci_PUSH_ALTS_T [Op p, Op info, Op p_tup] - PUSH_PAD8 -> emit bci_PUSH_PAD8 [] - PUSH_PAD16 -> emit bci_PUSH_PAD16 [] - PUSH_PAD32 -> emit bci_PUSH_PAD32 [] + PUSH_PAD8 -> emit_ bci_PUSH_PAD8 [] + PUSH_PAD16 -> emit_ bci_PUSH_PAD16 [] + PUSH_PAD32 -> emit_ bci_PUSH_PAD32 [] PUSH_UBX8 lit -> do np <- literal lit - emit bci_PUSH_UBX8 [Op np] + emit_ bci_PUSH_UBX8 [Op np] PUSH_UBX16 lit -> do np <- literal lit - emit bci_PUSH_UBX16 [Op np] + emit_ bci_PUSH_UBX16 [Op np] PUSH_UBX32 lit -> do np <- literal lit - emit bci_PUSH_UBX32 [Op np] + emit_ bci_PUSH_UBX32 [Op np] PUSH_UBX lit nws -> do np <- literal lit - emit bci_PUSH_UBX [Op np, wOp nws] - + emit_ bci_PUSH_UBX [Op np, wOp nws] -- see Note [Generating code for top-level string literal bindings] in GHC.StgToByteCode - PUSH_ADDR nm -> do np <- lit [BCONPtrAddr nm] - emit bci_PUSH_UBX [Op np, SmallOp 1] - - PUSH_APPLY_N -> emit bci_PUSH_APPLY_N [] - PUSH_APPLY_V -> emit bci_PUSH_APPLY_V [] - PUSH_APPLY_F -> emit bci_PUSH_APPLY_F [] - PUSH_APPLY_D -> emit bci_PUSH_APPLY_D [] - PUSH_APPLY_L -> emit bci_PUSH_APPLY_L [] - PUSH_APPLY_P -> emit bci_PUSH_APPLY_P [] - PUSH_APPLY_PP -> emit bci_PUSH_APPLY_PP [] - PUSH_APPLY_PPP -> emit bci_PUSH_APPLY_PPP [] - PUSH_APPLY_PPPP -> emit bci_PUSH_APPLY_PPPP [] - PUSH_APPLY_PPPPP -> emit bci_PUSH_APPLY_PPPPP [] - PUSH_APPLY_PPPPPP -> emit bci_PUSH_APPLY_PPPPPP [] - - SLIDE n by -> emit bci_SLIDE [wOp n, wOp by] - ALLOC_AP n -> emit bci_ALLOC_AP [truncHalfWord platform n] - ALLOC_AP_NOUPD n -> emit bci_ALLOC_AP_NOUPD [truncHalfWord platform n] - ALLOC_PAP arity n -> emit bci_ALLOC_PAP [truncHalfWord platform arity, truncHalfWord platform n] - MKAP off sz -> emit bci_MKAP [wOp off, truncHalfWord platform sz] - MKPAP off sz -> emit bci_MKPAP [wOp off, truncHalfWord platform sz] - UNPACK n -> emit bci_UNPACK [wOp n] - PACK dcon sz -> do itbl_no <- lit [BCONPtrItbl (getName dcon)] - emit bci_PACK [Op itbl_no, wOp sz] + PUSH_ADDR nm -> do np <- lit1 (BCONPtrAddr nm) + emit_ bci_PUSH_UBX [Op np, SmallOp 1] + + PUSH_APPLY_N -> emit_ bci_PUSH_APPLY_N [] + PUSH_APPLY_V -> emit_ bci_PUSH_APPLY_V [] + PUSH_APPLY_F -> emit_ bci_PUSH_APPLY_F [] + PUSH_APPLY_D -> emit_ bci_PUSH_APPLY_D [] + PUSH_APPLY_L -> emit_ bci_PUSH_APPLY_L [] + PUSH_APPLY_P -> emit_ bci_PUSH_APPLY_P [] + PUSH_APPLY_PP -> emit_ bci_PUSH_APPLY_PP [] + PUSH_APPLY_PPP -> emit_ bci_PUSH_APPLY_PPP [] + PUSH_APPLY_PPPP -> emit_ bci_PUSH_APPLY_PPPP [] + PUSH_APPLY_PPPPP -> emit_ bci_PUSH_APPLY_PPPPP [] + PUSH_APPLY_PPPPPP -> emit_ bci_PUSH_APPLY_PPPPPP [] + + SLIDE n by -> emit_ bci_SLIDE [wOp n, wOp by] + ALLOC_AP n -> emit_ bci_ALLOC_AP [truncHalfWord platform n] + ALLOC_AP_NOUPD n -> emit_ bci_ALLOC_AP_NOUPD [truncHalfWord platform n] + ALLOC_PAP arity n -> emit_ bci_ALLOC_PAP [truncHalfWord platform arity, truncHalfWord platform n] + MKAP off sz -> emit_ bci_MKAP [wOp off, truncHalfWord platform sz] + MKPAP off sz -> emit_ bci_MKPAP [wOp off, truncHalfWord platform sz] + UNPACK n -> emit_ bci_UNPACK [wOp n] + PACK dcon sz -> do itbl_no <- lit1 (BCONPtrItbl (getName dcon)) + emit_ bci_PACK [Op itbl_no, wOp sz] LABEL lbl -> label lbl TESTLT_I i l -> do np <- int i - emit bci_TESTLT_I [Op np, LabelOp l] + emit_ bci_TESTLT_I [Op np, LabelOp l] TESTEQ_I i l -> do np <- int i - emit bci_TESTEQ_I [Op np, LabelOp l] + emit_ bci_TESTEQ_I [Op np, LabelOp l] TESTLT_W w l -> do np <- word w - emit bci_TESTLT_W [Op np, LabelOp l] + emit_ bci_TESTLT_W [Op np, LabelOp l] TESTEQ_W w l -> do np <- word w - emit bci_TESTEQ_W [Op np, LabelOp l] + emit_ bci_TESTEQ_W [Op np, LabelOp l] TESTLT_I64 i l -> do np <- word64 (fromIntegral i) - emit bci_TESTLT_I64 [Op np, LabelOp l] + emit_ bci_TESTLT_I64 [Op np, LabelOp l] TESTEQ_I64 i l -> do np <- word64 (fromIntegral i) - emit bci_TESTEQ_I64 [Op np, LabelOp l] + emit_ bci_TESTEQ_I64 [Op np, LabelOp l] TESTLT_I32 i l -> do np <- word (fromIntegral i) - emit bci_TESTLT_I32 [Op np, LabelOp l] + emit_ bci_TESTLT_I32 [Op np, LabelOp l] TESTEQ_I32 i l -> do np <- word (fromIntegral i) - emit bci_TESTEQ_I32 [Op np, LabelOp l] + emit_ bci_TESTEQ_I32 [Op np, LabelOp l] TESTLT_I16 i l -> do np <- word (fromIntegral i) - emit bci_TESTLT_I16 [Op np, LabelOp l] + emit_ bci_TESTLT_I16 [Op np, LabelOp l] TESTEQ_I16 i l -> do np <- word (fromIntegral i) - emit bci_TESTEQ_I16 [Op np, LabelOp l] + emit_ bci_TESTEQ_I16 [Op np, LabelOp l] TESTLT_I8 i l -> do np <- word (fromIntegral i) - emit bci_TESTLT_I8 [Op np, LabelOp l] + emit_ bci_TESTLT_I8 [Op np, LabelOp l] TESTEQ_I8 i l -> do np <- word (fromIntegral i) - emit bci_TESTEQ_I8 [Op np, LabelOp l] + emit_ bci_TESTEQ_I8 [Op np, LabelOp l] TESTLT_W64 w l -> do np <- word64 w - emit bci_TESTLT_W64 [Op np, LabelOp l] + emit_ bci_TESTLT_W64 [Op np, LabelOp l] TESTEQ_W64 w l -> do np <- word64 w - emit bci_TESTEQ_W64 [Op np, LabelOp l] + emit_ bci_TESTEQ_W64 [Op np, LabelOp l] TESTLT_W32 w l -> do np <- word (fromIntegral w) - emit bci_TESTLT_W32 [Op np, LabelOp l] + emit_ bci_TESTLT_W32 [Op np, LabelOp l] TESTEQ_W32 w l -> do np <- word (fromIntegral w) - emit bci_TESTEQ_W32 [Op np, LabelOp l] + emit_ bci_TESTEQ_W32 [Op np, LabelOp l] TESTLT_W16 w l -> do np <- word (fromIntegral w) - emit bci_TESTLT_W16 [Op np, LabelOp l] + emit_ bci_TESTLT_W16 [Op np, LabelOp l] TESTEQ_W16 w l -> do np <- word (fromIntegral w) - emit bci_TESTEQ_W16 [Op np, LabelOp l] + emit_ bci_TESTEQ_W16 [Op np, LabelOp l] TESTLT_W8 w l -> do np <- word (fromIntegral w) - emit bci_TESTLT_W8 [Op np, LabelOp l] + emit_ bci_TESTLT_W8 [Op np, LabelOp l] TESTEQ_W8 w l -> do np <- word (fromIntegral w) - emit bci_TESTEQ_W8 [Op np, LabelOp l] + emit_ bci_TESTEQ_W8 [Op np, LabelOp l] TESTLT_F f l -> do np <- float f - emit bci_TESTLT_F [Op np, LabelOp l] + emit_ bci_TESTLT_F [Op np, LabelOp l] TESTEQ_F f l -> do np <- float f - emit bci_TESTEQ_F [Op np, LabelOp l] + emit_ bci_TESTEQ_F [Op np, LabelOp l] TESTLT_D d l -> do np <- double d - emit bci_TESTLT_D [Op np, LabelOp l] + emit_ bci_TESTLT_D [Op np, LabelOp l] TESTEQ_D d l -> do np <- double d - emit bci_TESTEQ_D [Op np, LabelOp l] - TESTLT_P i l -> emit bci_TESTLT_P [SmallOp i, LabelOp l] - TESTEQ_P i l -> emit bci_TESTEQ_P [SmallOp i, LabelOp l] - CASEFAIL -> emit bci_CASEFAIL [] - SWIZZLE stkoff n -> emit bci_SWIZZLE [wOp stkoff, IOp n] - JMP l -> emit bci_JMP [LabelOp l] - ENTER -> emit bci_ENTER [] - RETURN rep -> emit (return_non_tuple rep) [] - RETURN_TUPLE -> emit bci_RETURN_T [] + emit_ bci_TESTEQ_D [Op np, LabelOp l] + TESTLT_P i l -> emit_ bci_TESTLT_P [SmallOp i, LabelOp l] + TESTEQ_P i l -> emit_ bci_TESTEQ_P [SmallOp i, LabelOp l] + CASEFAIL -> emit_ bci_CASEFAIL [] + SWIZZLE stkoff n -> emit_ bci_SWIZZLE [wOp stkoff, IOp n] + JMP l -> emit_ bci_JMP [LabelOp l] + ENTER -> emit_ bci_ENTER [] + RETURN rep -> emit_ (return_non_tuple rep) [] + RETURN_TUPLE -> emit_ bci_RETURN_T [] CCALL off m_addr i -> do np <- addr m_addr - emit bci_CCALL [wOp off, Op np, SmallOp i] - PRIMCALL -> emit bci_PRIMCALL [] + emit_ bci_CCALL [wOp off, Op np, SmallOp i] + PRIMCALL -> emit_ bci_PRIMCALL [] BRK_FUN arr tick_mod tickx info_mod infox cc -> do p1 <- ptr (BCOPtrBreakArray arr) tick_addr <- addr tick_mod info_addr <- addr info_mod np <- addr cc - emit bci_BRK_FUN [ Op p1 + emit_ bci_BRK_FUN [ Op p1 , Op tick_addr, Op info_addr , SmallOp tickx, SmallOp infox , Op np ] #if MIN_VERSION_rts(1,0,3) - BCO_NAME name -> do np <- lit [BCONPtrStr name] - emit bci_BCO_NAME [Op np] + BCO_NAME name -> do np <- lit1 (BCONPtrStr name) + emit_ bci_BCO_NAME [Op np] #endif + + where + emit_ = emit word_size + + literal :: Literal -> m Word literal (LitLabel fs _) = litlabel fs literal LitNullAddr = word 0 literal (LitFloat r) = float (fromRational r) literal (LitDouble r) = double (fromRational r) literal (LitChar c) = int (ord c) - literal (LitString bs) = lit [BCONPtrStr bs] + literal (LitString bs) = lit1 (BCONPtrStr bs) -- LitString requires a zero-terminator when emitted literal (LitNumber nt i) = case nt of LitNumInt -> word (fromIntegral i) @@ -549,10 +778,11 @@ assembleI platform i = case i of -- analysis messed up. literal (LitRubbish {}) = word 0 - litlabel fs = lit [BCONPtrLbl fs] - addr (RemotePtr a) = words [fromIntegral a] - words ws = lit (map BCONPtrWord ws) - word w = words [w] + litlabel fs = lit1 (BCONPtrLbl fs) + addr (RemotePtr a) = word (fromIntegral a) + words ws = lit (fmap BCONPtrWord ws) + word w = words (OnlyOne w) + word2 w1 w2 = words (OnlyTwo w1 w2) word_size = platformWordSize platform word_size_bits = platformWordSizeInBits platform @@ -563,36 +793,36 @@ assembleI platform i = case i of -- Note that we only support host endianness == target endianness for now, -- even with the external interpreter. This would need to be fixed to -- support host endianness /= target endianness - int :: Int -> Assembler Word + int :: Int -> m Word int i = word (fromIntegral i) - float :: Float -> Assembler Word + float :: Float -> m Word float f = word32 (castFloatToWord32 f) - double :: Double -> Assembler Word + double :: Double -> m Word double d = word64 (castDoubleToWord64 d) - word64 :: Word64 -> Assembler Word + word64 :: Word64 -> m Word word64 ww = case word_size of PW4 -> let !wl = fromIntegral ww !wh = fromIntegral (ww `unsafeShiftR` 32) in case platformByteOrder platform of - LittleEndian -> words [wl,wh] - BigEndian -> words [wh,wl] + LittleEndian -> word2 wl wh + BigEndian -> word2 wh wl PW8 -> word (fromIntegral ww) - word8 :: Word8 -> Assembler Word + word8 :: Word8 -> m Word word8 x = case platformByteOrder platform of LittleEndian -> word (fromIntegral x) BigEndian -> word (fromIntegral x `unsafeShiftL` (word_size_bits - 8)) - word16 :: Word16 -> Assembler Word + word16 :: Word16 -> m Word word16 x = case platformByteOrder platform of LittleEndian -> word (fromIntegral x) BigEndian -> word (fromIntegral x `unsafeShiftL` (word_size_bits - 16)) - word32 :: Word32 -> Assembler Word + word32 :: Word32 -> m Word word32 x = case platformByteOrder platform of LittleEndian -> word (fromIntegral x) BigEndian -> case word_size of ===================================== compiler/GHC/ByteCode/Instr.hs ===================================== @@ -36,6 +36,7 @@ import GHC.Stack.CCS (CostCentre) import GHC.Stg.Syntax import GHCi.BreakArray (BreakArray) import Language.Haskell.Syntax.Module.Name (ModuleName) +import GHC.Types.Unique -- ---------------------------------------------------------------------------- -- Bytecode instructions @@ -58,6 +59,10 @@ data ProtoBCO a newtype LocalLabel = LocalLabel { getLocalLabel :: Word32 } deriving (Eq, Ord) +-- Just so we can easily juse UniqFM. +instance Uniquable LocalLabel where + getUnique (LocalLabel w) = mkUniqueGrimily $ fromIntegral w + instance Outputable LocalLabel where ppr (LocalLabel lbl) = text "lbl:" <> ppr lbl ===================================== compiler/GHC/ByteCode/Types.hs ===================================== @@ -21,7 +21,7 @@ module GHC.ByteCode.Types , CgBreakInfo(..) , ModBreaks (..), BreakIndex, emptyModBreaks , CCostCentre - , FlatBag, sizeFlatBag, fromSizedSeq, elemsFlatBag + , FlatBag, sizeFlatBag, fromSmallArray, elemsFlatBag ) where import GHC.Prelude ===================================== compiler/GHC/Data/FlatBag.hs ===================================== @@ -8,13 +8,11 @@ module GHC.Data.FlatBag , mappendFlatBag -- * Construction , fromList - , fromSizedSeq + , fromSmallArray ) where import GHC.Prelude -import GHC.Data.SizedSeq (SizedSeq, ssElts, sizeSS) - import Control.DeepSeq import GHC.Data.SmallArray @@ -125,5 +123,10 @@ fromList n elts = -- | Convert a 'SizedSeq' into its flattened representation. -- A 'FlatBag a' is more memory efficient than '[a]', if no further modification -- is necessary. -fromSizedSeq :: SizedSeq a -> FlatBag a -fromSizedSeq s = fromList (sizeSS s) (ssElts s) +fromSmallArray :: SmallArray a -> FlatBag a +fromSmallArray s = case sizeofSmallArray s of + 0 -> EmptyFlatBag + 1 -> UnitFlatBag (indexSmallArray s 0) + 2 -> TupleFlatBag (indexSmallArray s 0) (indexSmallArray s 1) + _ -> FlatBag s + ===================================== compiler/GHC/Data/SmallArray.hs ===================================== @@ -16,11 +16,18 @@ module GHC.Data.SmallArray , mapSmallArray , foldMapSmallArray , rnfSmallArray + + -- * IO Operations + , SmallMutableArrayIO + , newSmallArrayIO + , writeSmallArrayIO + , unsafeFreezeSmallArrayIO ) where import GHC.Exts import GHC.Prelude +import GHC.IO import GHC.ST import Control.DeepSeq @@ -28,6 +35,8 @@ data SmallArray a = SmallArray (SmallArray# a) data SmallMutableArray s a = SmallMutableArray (SmallMutableArray# s a) +type SmallMutableArrayIO a = SmallMutableArray RealWorld a + newSmallArray :: Int -- ^ size -> a -- ^ initial contents @@ -37,6 +46,9 @@ newSmallArray newSmallArray (I# sz) x s = case newSmallArray# sz x s of (# s', a #) -> (# s', SmallMutableArray a #) +newSmallArrayIO :: Int -> a -> IO (SmallMutableArrayIO a) +newSmallArrayIO sz x = IO $ \s -> newSmallArray sz x s + writeSmallArray :: SmallMutableArray s a -- ^ array -> Int -- ^ index @@ -46,6 +58,12 @@ writeSmallArray {-# INLINE writeSmallArray #-} writeSmallArray (SmallMutableArray a) (I# i) x = writeSmallArray# a i x +writeSmallArrayIO :: SmallMutableArrayIO a + -> Int + -> a + -> IO () +writeSmallArrayIO a ix v = IO $ \s -> (# writeSmallArray a ix v s, () #) + -- | Copy and freeze a slice of a mutable array. freezeSmallArray @@ -69,6 +87,9 @@ unsafeFreezeSmallArray (SmallMutableArray ma) s = case unsafeFreezeSmallArray# ma s of (# s', a #) -> (# s', SmallArray a #) +unsafeFreezeSmallArrayIO :: SmallMutableArrayIO a -> IO (SmallArray a) +unsafeFreezeSmallArrayIO arr = IO $ \s -> unsafeFreezeSmallArray arr s + -- | Get the size of a 'SmallArray' sizeofSmallArray :: SmallArray a ===================================== testsuite/tests/perf/should_run/ByteCodeAsm.hs ===================================== @@ -0,0 +1,66 @@ +module Main where + +import GHC.Driver.Session +import GHC +import qualified GHC.LanguageExtensions as LangExt + +import Control.Monad (forM_) +import Control.Monad.IO.Class (liftIO) +import System.Environment (getArgs) + +import GHC.ByteCode.Asm ( assembleBCO ) +import GHC.ByteCode.Instr +import Control.Monad +import GHC.Builtin.Names + +-- Testing the performance of the bytecode assembler + +-- A nonsensical byte-code program +instrs = [ STKCHECK 1234 + , PUSH_L 1 + , PUSH_LL 1 2 + , PUSH_LLL 2 3 4 + , PUSH_LLL 2 3 4 + , PUSH_LLL 2 3 4 + , PUSH_LLL 2 3 4 + , PUSH_LLL 2 3 4 + , PUSH8 0 + , PUSH16 15 + , PUSH32 29 + , PUSH_PAD8 + , PUSH_APPLY_N + , PUSH_APPLY_V + , PUSH_APPLY_F + , PUSH_APPLY_D + , PUSH_APPLY_L + , PUSH_APPLY_P + , PUSH_APPLY_PP + , PUSH_APPLY_PPP + , PUSH_APPLY_PPPP + , PUSH_APPLY_PPPPP + , PUSH_APPLY_PPPPPP + , TESTLT_I 100 (LocalLabel 0) + , TESTEQ_I 100 (LocalLabel 0) + ] + ++ [ LABEL (LocalLabel n) | n <- [0..50] ] + ++ [ TESTEQ_I64 n (LocalLabel 49) | n <- [1243 .. 1253 + 50 ]] + ++ [ ENTER ] + ++ [ SLIDE x n | x <- [0..5], n <- [0..10] ] + ++ [ PUSH_G appAName | _ <- [0..100] ] + ++ [ PUSH_BCO fake_proto2 ] + +fake_proto = ProtoBCO appAName instrs [] 0 0 (Left []) [] + +instrs2 = [ STKCHECK 77, UNPACK 4, SLIDE 0 4, ENTER ] + +fake_proto2 = ProtoBCO appAName instrs2 [] 0 0 (Left []) [] + +main :: IO () +main = do + [libdir] <- getArgs + runGhc (Just libdir) $ do + dflags <- getSessionDynFlags + let platform = targetPlatform dflags + + -- ~1s on my machine + liftIO $ replicateM_ 100000 (assembleBCO platform fake_proto) ===================================== testsuite/tests/perf/should_run/all.T ===================================== @@ -415,3 +415,11 @@ test('T18964', [collect_stats('bytes allocated', 1), only_ways(['normal'])], com test('T23021', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O2']) test('T25055', [collect_stats('bytes allocated', 2), only_ways(['normal'])], compile_and_run, ['-O2']) test('T17949', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O2']) + +test('ByteCodeAsm', + [ extra_run_opts('"' + config.libdir + '"') + , js_broken(22261) + , collect_stats('bytes allocated', 10), + ], + compile_and_run, + ['-package ghc']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8f6cc90c2de9937af465d0c88344eb8c998d5e41 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8f6cc90c2de9937af465d0c88344eb8c998d5e41 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/80a92a67/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 09:49:14 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Mar 2025 04:49:14 -0500 Subject: [Git][ghc/ghc][master] 2 commits: ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Message-ID: <67c81e1a48ec_343add4d0e682479@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - 34 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8f6cc90c2de9937af465d0c88344eb8c998d5e41...91ef82df3b15bd35c660d6ca0882d7a19c93b3a1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8f6cc90c2de9937af465d0c88344eb8c998d5e41...91ef82df3b15bd35c660d6ca0882d7a19c93b3a1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/4e5d4767/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 09:49:45 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Mar 2025 04:49:45 -0500 Subject: [Git][ghc/ghc][master] Collapse string gaps as \& (#25784) Message-ID: <67c81e39c4a8c_343add379e982777c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 4 changed files: - compiler/GHC/Parser/String.hs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Parser/String.hs ===================================== @@ -127,7 +127,8 @@ collapseGaps = go where go = \case c1@(Char '\\') : c2@(Char c) : cs - | is_space c -> go $ dropGap cs + -- #25784: string gaps are semantically equivalent to "\&" + | is_space c -> c1 : setChar '&' c1 : go (dropGap cs) | otherwise -> c1 : c2 : go cs c : cs -> c : go cs [] -> [] ===================================== testsuite/tests/parser/should_run/T25784.hs ===================================== @@ -0,0 +1,18 @@ +{-# LANGUAGE MultilineStrings #-} + +main :: IO () +main = do + checkEqual "\65\ \0" "A0" + checkEqual + """ + a + \ + \ b + """ + " a\n b" + +checkEqual :: String -> String -> IO () +checkEqual actual expected = do + putStrLn $ "Expected: " ++ show expected + putStrLn $ "Actual: " ++ show actual + putStrLn "========================================" ===================================== testsuite/tests/parser/should_run/T25784.stdout ===================================== @@ -0,0 +1,6 @@ +Expected: "A0" +Actual: "A0" +======================================== +Expected: " a\n b" +Actual: " a\n b" +======================================== ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -27,3 +27,4 @@ test('MultilineStrings', normal, compile_and_run, ['']) test('MultilineStringsOverloaded', normal, compile_and_run, ['']) test('T25375', normal, compile_and_run, ['']) test('T25609', normal, compile_and_run, ['']) +test('T25784', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb9fe1ec0a1b35e4a9ceeafd7943dc95b3180fc3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb9fe1ec0a1b35e4a9ceeafd7943dc95b3180fc3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/292ce81f/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 09:51:07 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Mar 2025 04:51:07 -0500 Subject: [Git][ghc/ghc][master] 3 commits: ghc-experimental: make JSVal abstract in GHC.Wasm.Prim Message-ID: <67c81e8bd1531_343add1070c00327bc@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 5 changed files: - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - testsuite/tests/jsffi/jsffigc.hs Changes: ===================================== libraries/ghc-experimental/src/GHC/Wasm/Prim.hs ===================================== @@ -2,8 +2,9 @@ module GHC.Wasm.Prim ( -- User-facing JSVal type and freeJSVal - JSVal (..), + JSVal, freeJSVal, + mkWeakJSVal, -- The JSString type and conversion from/to Haskell String JSString (..), @@ -20,4 +21,3 @@ module GHC.Wasm.Prim ( ) where import GHC.Internal.Wasm.Prim - ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs ===================================== @@ -4,6 +4,7 @@ module GHC.Internal.Wasm.Prim ( -- User-facing JSVal type and freeJSVal JSVal (..), freeJSVal, + mkWeakJSVal, -- The JSString type and conversion from/to Haskell String JSString (..), ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -8,6 +8,7 @@ module GHC.Internal.Wasm.Prim.Types ( JSVal# (..), JSVal (..), freeJSVal, + mkWeakJSVal, JSString (..), fromJSString, toJSString, @@ -26,6 +27,7 @@ import GHC.Internal.IO.Encoding import GHC.Internal.Num import GHC.Internal.Show import GHC.Internal.Stable +import GHC.Internal.Weak {- @@ -82,7 +84,7 @@ newtype JSVal# = JSVal# (Any :: UnliftedType) data JSVal - = forall a . JSVal JSVal# (Weak# JSVal#) (StablePtr# a) + = forall a . JSVal JSVal# (Weak# JSVal) (StablePtr# a) freeJSVal :: JSVal -> IO () freeJSVal v@(JSVal _ w sp) = do @@ -94,6 +96,12 @@ freeJSVal v@(JSVal _ w sp) = do IO $ \s0 -> case finalizeWeak# w s0 of (# s1, _, _ #) -> (# s1, () #) +mkWeakJSVal :: JSVal -> Maybe (IO ()) -> IO (Weak JSVal) +mkWeakJSVal v@(JSVal k _ _) (Just (IO fin)) = IO $ \s0 -> + case mkWeak# k v fin s0 of + (# s1, w #) -> (# s1, Weak w #) +mkWeakJSVal (JSVal _ w _) Nothing = pure $ Weak w + foreign import javascript unsafe "if (!__ghc_wasm_jsffi_finalization_registry.unregister($1)) { throw new WebAssembly.RuntimeError('js_callback_unregister'); }" js_callback_unregister :: JSVal -> IO () ===================================== rts/wasm/JSFFI.c ===================================== @@ -107,7 +107,6 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { SET_HDR(w, &stg_WEAK_info, CCS_SYSTEM); w->cfinalizers = (StgClosure *)cfin; w->key = p; - w->value = Unit_closure; w->finalizer = &stg_NO_FINALIZER_closure; w->link = cap->weak_ptr_list_hd; cap->weak_ptr_list_hd = w; @@ -120,7 +119,9 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { box->payload[0] = p; box->payload[1] = (HaskellObj)w; box->payload[2] = NULL; - return TAG_CLOSURE(1, box); + + w->value = TAG_CLOSURE(1, box); + return w->value; } __attribute__((import_module("ghc_wasm_jsffi"), import_name("getJSVal"))) ===================================== testsuite/tests/jsffi/jsffigc.hs ===================================== @@ -22,13 +22,6 @@ foreign import javascript "wrapper" foreign export javascript "testDynExportFree sync" testDynExportFree :: Int -> Int -> Int -> IO () --- JSVal uses Weak# under the hood for garbage collection support, --- this exposes the internal Weak# to observe the liveliness of --- JSVal#. Do not use this in your own codebase since this is purely --- an implementation detail of JSVal and subject to change! -jsvalWeak :: JSVal -> Weak JSVal -jsvalWeak (JSVal _ w _) = Weak $ unsafeCoerce# Weak w - probeWeak :: Weak v -> IO () probeWeak wk = print =<< isJust <$> deRefWeak wk @@ -42,7 +35,7 @@ testDynExportFree x y z = do -- wk_js observe the liveliness of the JavaScript callback on the -- Haskell heap. Make sure it's eagerly evaluated and isn't a thunk -- that retains cb. - let !wk_js = jsvalWeak cb + !wk_js <- mkWeakJSVal cb Nothing print $ js_to_hs cb x y -- Eagerly drop references to both the JavaScript callback and the -- Haskell function closure. @@ -60,7 +53,7 @@ testDynExportGC x y z = do let fn a b = a * b + z wk_fn <- mkWeak fn () Nothing cb <- js_from_hs fn - let !wk_js = jsvalWeak cb + !wk_js <- mkWeakJSVal cb Nothing print $ js_to_hs cb x y -- Why performGC twice? The first run gathers some C finalizers -- which will be invoked in the second run to free the JSVal View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eb9fe1ec0a1b35e4a9ceeafd7943dc95b3180fc3...55af20e6ed5c72a46a09b88e8590b6b2309eb41b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eb9fe1ec0a1b35e4a9ceeafd7943dc95b3180fc3...55af20e6ed5c72a46a09b88e8590b6b2309eb41b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/af3cbb93/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 09:51:46 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Mar 2025 04:51:46 -0500 Subject: [Git][ghc/ghc][master] simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Message-ID: <67c81eb2e1e8a_343add1070c00369c6@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 4 changed files: - compiler/GHC/Core/SimpleOpt.hs - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T Changes: ===================================== compiler/GHC/Core/SimpleOpt.hs ===================================== @@ -89,6 +89,24 @@ functions called precisely once, without repeatedly optimising the same expression. In fact, the simple optimiser is a good example of this little dance in action; the full Simplifier is a lot more complicated. +Note [The InScopeSet for simpleOptExpr] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars +before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. +Consider calling `simpleOptExpr` on an expression like + +``` + case x of (a,b) -> (x,a) +``` + +* One of those two occurrences of x has an unfolding (the one in (x,a), with +unfolding x = (a,b)) and the other does not. (Inside a case GHC adds +unfolding-info to the scrutinee's Id.) +* But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. +* Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. +* Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. + +See ticket #25790 -} -- | Simple optimiser options @@ -135,14 +153,9 @@ simpleOptExpr opts expr = -- pprTrace "simpleOptExpr" (ppr init_subst $$ ppr expr) simpleOptExprWith opts init_subst expr where - init_subst = mkEmptySubst (mkInScopeSet (exprFreeVars expr)) - -- It's potentially important to make a proper in-scope set - -- Consider let x = ..y.. in \y. ...x... - -- Then we should remember to clone y before substituting - -- for x. It's very unlikely to occur, because we probably - -- won't *be* substituting for x if it occurs inside a - -- lambda. - -- + init_subst = mkEmptySubst (mkInScopeSet (mapVarSet zapIdUnfolding (exprFreeVars expr))) + -- zapIdUnfolding: see Note [The InScopeSet for simpleOptExpr] + -- It's a bit painful to call exprFreeVars, because it makes -- three passes instead of two (occ-anal, and go) ===================================== testsuite/tests/ghci/should_run/T25790.hs ===================================== @@ -0,0 +1,10 @@ +module T25790 + ( nest + ) where + +import Control.Monad.Reader + +data RunS = RunS { depth :: Int } + +nest :: ReaderT RunS IO a -> ReaderT RunS IO a +nest = local (\s -> s { depth = depth s }) ===================================== testsuite/tests/ghci/should_run/T25790.script ===================================== @@ -0,0 +1 @@ +:l T25790.hs ===================================== testsuite/tests/ghci/should_run/all.T ===================================== @@ -97,3 +97,4 @@ test('T24115', just_ghci + [extra_run_opts("-e ':add T24115.hs'")], ghci_script, test('T10920', [only_ways(ghci_ways), extra_files(['LocalPrelude/Prelude.hs'])], ghci_script, ['T10920.script']) test('TopEnvIface', [only_ways(ghci_ways)], makefile_test, []) +test('T25790', [only_ways(ghci_ways), extra_ways(["ghci-opt"])], ghci_script, ['T25790.script']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8273d7d16ddc1b16096dbab6ad7208dded4ad1b2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8273d7d16ddc1b16096dbab6ad7208dded4ad1b2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/413fbdc8/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 09:52:16 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Mar 2025 04:52:16 -0500 Subject: [Git][ghc/ghc][master] docs: Fix ghci :doc documentation Message-ID: <67c81ed08a4b6_343add13698f838454@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - 1 changed file: - docs/users_guide/ghci.rst Changes: ===================================== docs/users_guide/ghci.rst ===================================== @@ -2444,8 +2444,6 @@ commonly used commands. .. ghci-cmd:: :doc; ⟨name⟩ - (Experimental: This command will likely change significantly in GHC 8.8.) - Displays the documentation for the given name. Currently the command is restricted to displaying the documentation directly on the declaration in question, ignoring documentation for arguments, constructors etc. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/07fe6d1daad01030cb7b9e6897492b7bdaec5a90 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/07fe6d1daad01030cb7b9e6897492b7bdaec5a90 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/3915892b/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 10:22:30 2025 From: gitlab at gitlab.haskell.org (Ryan Scott (@RyanGlScott)) Date: Wed, 05 Mar 2025 05:22:30 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/make-Wdata-kinds-tc-an-error Message-ID: <67c825e66ae6f_343add1747c40453c5@gitlab.mail> Ryan Scott pushed new branch wip/make-Wdata-kinds-tc-an-error at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/make-Wdata-kinds-tc-an-error You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/1b6b98c8/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 12:12:13 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 05 Mar 2025 07:12:13 -0500 Subject: [Git][ghc/ghc][wip/t25571] 17 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67c83f9dc3c34_38c2cd4c4410937e7@gitlab.mail> Matthew Pickering pushed to branch wip/t25571 at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - aa1ded09 by Matthew Pickering at 2025-03-05T09:26:00+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - cf497243 by Matthew Pickering at 2025-03-05T09:26:20+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 70b5f1da by Matthew Pickering at 2025-03-05T09:26:20+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 72 changed files: - compiler/GHC.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/include/RtsAPI.h - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/950c58dec3ee75afba2545b10ba954ce485ffc48...70b5f1da951de72f23f57c2da99e8fabc0fb2ded -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/950c58dec3ee75afba2545b10ba954ce485ffc48...70b5f1da951de72f23f57c2da99e8fabc0fb2ded You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/37c3cd6d/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 12:18:13 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 05 Mar 2025 07:18:13 -0500 Subject: [Git][ghc/ghc][wip/T25647] Clarify wildcard handling in type families documentation and improve explanations for FamArgFlavour Message-ID: <67c841057177a_38c2cd6c1934943cf@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: c64232e9 by Patrick at 2025-03-05T20:18:04+08:00 Clarify wildcard handling in type families documentation and improve explanations for FamArgFlavour - - - - - 2 changed files: - compiler/GHC/Core/TyCon.hs - compiler/GHC/Tc/Instance/Class.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -3001,12 +3001,15 @@ Some common agreements: By picking different type var for different flavours of wildcards in `tcAnonWildCardOcc`, we can explore different design spaces. For example, we can have the following design spaces: -1. Wildcards can represet arbitrary types, including type variables, picks TauTv. -2. Wildcards can only represent type variables, picks TyVarTv. -3. Wildcards stand alone, pick skolemTv variables. + +* 1. For Wildcards can represet arbitrary types, including type variables, picks TauTv. + But we need to taking care of not defaulting it unexpectively. +* 2. For Wildcards can only represent type variables, picks TyVarTv. + Unlike skolemTv, it should help us to equalize two _ if there is such a need. +* 3. For Wildcards stand alone, pick skolemTv variables. ... and so on. -Maintaining backward compatibility from 8.6.4 to 9.10.2, the picks would be: +If maintaining backward compatibility from 8.6.4 to 9.10.2, the picks would be: - TyVarTv for FreeArg - TauTv for ClassArg - TauTv for SigArg @@ -3020,7 +3023,7 @@ For more discussion, see #13908. {- Note [FamArgFlavour] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The FamArgFlavour is used to distinguish the different kinds of arguments that may -appear in an associated type family declaration/instance. In an associated type family, +appear in an type family declaration/instance. In an associated type family, some arguments come directly from the parent class (the “class argumentsâ€) while others are provided freely by the user (the “free argumentsâ€). For example, consider: @@ -3061,6 +3064,36 @@ now let's consider _ here as a FreeArg then TyVarTv, then it would not match Typ Say if we assign ClassArg to _ here, if we want to flip class arguments in associated type family to only match Type variables. Then this example would not work. +Another reason is that it is really hard for us to know if wildcard in signature in an +associated type family corresponding to a class argument or a free argument. +For example, in the following + code: + +class C a b c where + type F a (d :: TYPE a) (e :: TYPE k) f +instance C LiftedRep Int c where + type F _ (_ :: TYPE _) (_ :: TYPE _) (_ :: TYPE _) = Int + +we have: + +tyConBinders: [[spec] (@(k_a7h :: RuntimeRep)), + [req] (@(a_a7e :: RuntimeRep)), AnonTCB (@(d_a7i :: TYPE a_a7e)), + AnonTCB (@(e_a7j :: TYPE k_a7h)), AnonTCB (@f_a7k)] +tyConTyVars: [k_a7h, a_a7e, d_a7i, e_a7j, f_a7k] +tyConFamArgFlavours: [FreeArg, ClassArg, FreeArg, FreeArg, FreeArg] + +* The first `TYPE _` is bounded to classArg `a` while its' binder `d` occurs freely. +* The second `TYPE _` is not bounded to a class argument and its' binder `e` occurs freely. +* The third `TYPE _` is not bounded to a class argument, does not appear in `tyConBinders` + +It is rather hard to distinguish them during typechecking. +THe best way I can think of is to mark them as SigArg and treat them as TauTv. + +* For the first two, let the explicit type application or implicit instantiation of the + `tyConBinders` to decide the final type for them. +* For the third one, it default it LiftedRep. It is more of a trade off, because I think + it is the best if we do not default any wildCard. + Hence we maintain three different flavours of wildcards in type families. This provides a flexibility to interpret wildcards in type families. ===================================== compiler/GHC/Tc/Instance/Class.hs ===================================== @@ -37,7 +37,7 @@ import GHC.Types.FieldLabel import GHC.Types.Name.Reader import GHC.Types.SafeHaskell import GHC.Types.Name ( Name ) -import GHC.Types.Var.Env ( VarEnv, elemVarEnv ) +import GHC.Types.Var.Env ( VarEnv ) import GHC.Types.Id import GHC.Types.Var View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c64232e978ec9a8ab63bd5d706b5326c8dae6179 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c64232e978ec9a8ab63bd5d706b5326c8dae6179 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/714c4930/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 12:26:57 2025 From: gitlab at gitlab.haskell.org (Ryan Scott (@RyanGlScott)) Date: Wed, 05 Mar 2025 07:26:57 -0500 Subject: [Git][ghc/ghc][wip/make-Wdata-kinds-tc-an-error] Remove -Wdata-kinds-tc warning, make DataKinds issues in typechecker become errors Message-ID: <67c843114cd4f_38c2cd8e376c98218@gitlab.mail> Ryan Scott pushed to branch wip/make-Wdata-kinds-tc-an-error at Glasgow Haskell Compiler / GHC Commits: 1cb814c0 by Ryan Scott at 2025-03-05T07:26:15-05:00 Remove -Wdata-kinds-tc warning, make DataKinds issues in typechecker become errors !11314 introduced the `-Wdata-kinds-tc` warning as part of a fix for #22141. This was a temporary stopgap measure to allow users who were accidentally relying on code which needed the `DataKinds` extension in order to typecheck without having to explicitly enable the extension. Now that some amount of time has passed, this patch removes `-Wdata-kinds-tc` and upgrades any `DataKinds`-related issues in the typechecker (which were previously warnings) into errors. - - - - - 25 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Validity.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/using-warnings.rst - − testsuite/tests/typecheck/should_compile/T22141a.stderr - − testsuite/tests/typecheck/should_compile/T22141b.stderr - − testsuite/tests/typecheck/should_compile/T22141c.stderr - − testsuite/tests/typecheck/should_compile/T22141d.stderr - − testsuite/tests/typecheck/should_compile/T22141e.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs - testsuite/tests/typecheck/should_fail/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs - testsuite/tests/typecheck/should_fail/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs - testsuite/tests/typecheck/should_fail/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs - testsuite/tests/typecheck/should_fail/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs - testsuite/tests/typecheck/should_fail/T22141e.stderr - testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1073,7 +1073,6 @@ data WarningFlag = | Opt_WarnIncompleteRecordSelectors -- Since 9.10 | Opt_WarnBadlyStagedTypes -- Since 9.10 | Opt_WarnInconsistentFlags -- Since 9.8 - | Opt_WarnDataKindsTC -- Since 9.10 | Opt_WarnDefaultedExceptionContext -- Since 9.10 | Opt_WarnViewPatternSignatures -- Since 9.12 deriving (Eq, Ord, Show, Enum, Bounded) @@ -1189,7 +1188,6 @@ warnFlagNames wflag = case wflag of Opt_WarnIncompleteRecordSelectors -> "incomplete-record-selectors" :| [] Opt_WarnBadlyStagedTypes -> "badly-staged-types" :| [] Opt_WarnInconsistentFlags -> "inconsistent-flags" :| [] - Opt_WarnDataKindsTC -> "data-kinds-tc" :| [] Opt_WarnDefaultedExceptionContext -> "defaulted-exception-context" :| [] Opt_WarnViewPatternSignatures -> "view-pattern-signatures" :| [] @@ -1331,7 +1329,6 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnBadlyStagedTypes, Opt_WarnTypeEqualityRequiresOperators, Opt_WarnInconsistentFlags, - Opt_WarnDataKindsTC, Opt_WarnTypeEqualityOutOfScope, Opt_WarnViewPatternSignatures ] ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2355,7 +2355,6 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnImplicitRhsQuantification -> warnSpec x Opt_WarnIncompleteExportWarnings -> warnSpec x Opt_WarnIncompleteRecordSelectors -> warnSpec x - Opt_WarnDataKindsTC -> warnSpec x Opt_WarnDefaultedExceptionContext -> warnSpec x Opt_WarnViewPatternSignatures -> warnSpec x ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1715,21 +1715,15 @@ instance Diagnostic TcRnMessage where , inHsDocContext doc ] TcRnDataKindsError typeOrKind thing - -- See Note [Checking for DataKinds] (Wrinkle: Migration story for - -- DataKinds typechecker errors) in GHC.Tc.Validity for why we give - -- different diagnostic messages below. -> case thing of Left renamer_thing -> - mkSimpleDecorated $ - text "Illegal" <+> ppr_level <> colon <+> quotes (ppr renamer_thing) + mkSimpleDecorated $ msg renamer_thing Right typechecker_thing -> - mkSimpleDecorated $ vcat - [ text "An occurrence of" <+> quotes (ppr typechecker_thing) <+> - text "in a" <+> ppr_level <+> text "requires DataKinds." - , text "Future versions of GHC will turn this warning into an error." - ] + mkSimpleDecorated $ msg typechecker_thing where - ppr_level = text $ levelString typeOrKind + msg :: Outputable a => a -> SDoc + msg thing = text "Illegal" <+> text (levelString typeOrKind) <> + colon <+> quotes (ppr thing) TcRnTypeSynonymCycle decl_or_tcs -> mkSimpleDecorated $ @@ -2524,17 +2518,8 @@ instance Diagnostic TcRnMessage where -> ErrorWithoutFlag TcRnUnusedQuantifiedTypeVar{} -> WarningWithFlag Opt_WarnUnusedForalls - TcRnDataKindsError _ thing - -- DataKinds errors can arise from either the renamer (Left) or the - -- typechecker (Right). The latter category of DataKinds errors are a - -- fairly recent addition to GHC (introduced in GHC 9.10), and in order - -- to prevent these new errors from breaking users' code, we temporarily - -- downgrade these errors to warnings. See Note [Checking for DataKinds] - -- (Wrinkle: Migration story for DataKinds typechecker errors) - -- in GHC.Tc.Validity. - -> case thing of - Left _ -> ErrorWithoutFlag - Right _ -> WarningWithFlag Opt_WarnDataKindsTC + TcRnDataKindsError{} + -> ErrorWithoutFlag TcRnTypeSynonymCycle{} -> ErrorWithoutFlag TcRnZonkerMessage msg ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -2519,11 +2519,11 @@ data TcRnMessage where rename/should_fail/T22478e th/TH_Promoted1Tuple typecheck/should_compile/tcfail094 - typecheck/should_compile/T22141a - typecheck/should_compile/T22141b - typecheck/should_compile/T22141c - typecheck/should_compile/T22141d - typecheck/should_compile/T22141e + typecheck/should_fail/T22141a + typecheck/should_fail/T22141b + typecheck/should_fail/T22141c + typecheck/should_fail/T22141d + typecheck/should_fail/T22141e typecheck/should_compile/T22141f typecheck/should_compile/T22141g typecheck/should_fail/T20873c ===================================== compiler/GHC/Tc/Validity.hs ===================================== @@ -1000,18 +1000,11 @@ checkVdqOK ve tvbs ty = do -- | Check for a DataKinds violation in a kind context. -- See @Note [Checking for DataKinds]@. --- --- Note that emitting DataKinds errors from the typechecker is a fairly recent --- addition to GHC (introduced in GHC 9.10), and in order to prevent these new --- errors from breaking users' code, we temporarily downgrade these errors to --- warnings. (This is why we use 'diagnosticTcM' below.) See --- @Note [Checking for DataKinds] (Wrinkle: Migration story for DataKinds --- typechecker errors)@. checkDataKinds :: ValidityEnv -> Type -> TcM () checkDataKinds (ValidityEnv{ ve_ctxt = ctxt, ve_tidy_env = env }) ty = do data_kinds <- xoptM LangExt.DataKinds - diagnosticTcM - (not (data_kinds || typeLevelUserTypeCtxt ctxt)) $ + checkTcM + (data_kinds || typeLevelUserTypeCtxt ctxt) $ (env, TcRnDataKindsError KindLevel (Right (tidyType env ty))) {- Note [No constraints in kinds] @@ -1163,28 +1156,6 @@ different places in the code: synonym), so we also catch a subset of kind-level violations in the renamer to allow for earlier reporting of these errors. ------ --- Wrinkle: Migration story for DataKinds typechecker errors ------ - -As mentioned above, DataKinds is checked in two different places: the renamer -and the typechecker. The checks in the renamer have been around since DataKinds -was introduced. The checks in the typechecker, on the other hand, are a fairly -recent addition, having been introduced in GHC 9.10. As such, it is possible -that there are some programs in the wild that (1) do not enable DataKinds, and -(2) were accepted by a previous GHC version, but would now be rejected by the -new DataKinds checks in the typechecker. - -To prevent the new DataKinds checks in the typechecker from breaking users' -code, we temporarily allow programs to compile if they violate a DataKinds -check in the typechecker, but GHC will emit a warning if such a violation -occurs. Users can then silence the warning by enabling DataKinds in the module -where the affected code lives. It is fairly straightforward to distinguish -between DataKinds violations arising from the renamer versus the typechecker, -as TcRnDataKindsError (the error message type classifying all DataKinds errors) -stores an Either field that is Left when the error comes from the renamer and -Right when the error comes from the typechecker. - ************************************************************************ * * \subsection{Checking a theta or source type} ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -40,6 +40,21 @@ Language * Multiline strings are now accepted in foreign imports. (#25157) +* The ``-Wdata-kinds-tc`` warning has been removed, and the use of promoted + data types in kinds is now an error (rather than a warning) unless the + :extension:`DataKinds` extension is enabled. For example, the following code + will be rejected unless :extension:`DataKinds` is on: + + import Data.Kind (Type) + import GHC.TypeNats (Nat) + + -- Nat shouldn't be allowed here without DataKinds + data Vec :: Nat -> Type -> Type + + (The ``-Wdata-kinds-tc`` warning was introduced in GHC 9.10 as part of a fix + for an accidental oversight in which programs like the one above were + mistakenly accepted without the use of :extension:`DataKinds`.) + Compiler ~~~~~~~~ ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -82,7 +82,6 @@ as ``-Wno-...`` for every individual warning in the group. * :ghc-flag:`-Winconsistent-flags` * :ghc-flag:`-Wnoncanonical-monoid-instances` * :ghc-flag:`-Wnoncanonical-monad-instances` - * :ghc-flag:`-Wdata-kinds-tc` .. ghc-flag:: -W :shortdesc: enable normal warnings @@ -2535,26 +2534,6 @@ of ``-W(no-)*``. issued. Another example is :ghc-flag:`-dynamic` is ignored when :ghc-flag:`-dynamic-too` is passed. -.. ghc-flag:: -Wdata-kinds-tc - :shortdesc: warn when an illegal use of a type or kind without - :extension:`DataKinds` is caught by the typechecker - :type: dynamic - :reverse: -Wno-data-kinds-tc - - :since: 9.10.1 - - Introduced in GHC 9.10.1, this warns when an illegal use of a type or kind - (without having enabled the :extension:`DataKinds` extension) is caught in - the typechecker (hence the ``-tc`` suffix). These warnings complement the - existing :extension:`DataKinds` checks (that have existed since - :extension:`DataKinds` was first introduced), which result in errors - instead of warnings. - - This warning is scheduled to be changed to an error in a future GHC - version, at which point the :ghc-flag:`-Wdata-kinds-tc` flag will be - removed. Users can enable the :extension:`DataKinds` extension to avoid - issues (thus silencing the warning). - .. ghc-flag:: -Wdefaulted-exception-context :shortdesc: warn when an :base-ref:`Control.Exception.Context.ExceptionContext` implicit parameter is defaulted to ===================================== testsuite/tests/typecheck/should_compile/T22141a.stderr deleted ===================================== @@ -1,8 +0,0 @@ -T22141a.hs:8:1: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘Nat’ - In the data type declaration for ‘Vector’ - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/T22141b.stderr deleted ===================================== @@ -1,9 +0,0 @@ -T22141b.hs:10:1: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘Nat’ - In the expansion of type synonym ‘MyNat’ - In the data type declaration for ‘Vector’ - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/T22141c.stderr deleted ===================================== @@ -1,37 +0,0 @@ -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘(# *, * #)’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘T’ - In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘'[]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘'[GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘[GHC.Internal.Types.LiftedRep, - GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘Proxy T’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/T22141d.stderr deleted ===================================== @@ -1,37 +0,0 @@ -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘(# * | * #)’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘T’ - In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘'[]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘'[GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘[GHC.Internal.Types.LiftedRep, - GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘Proxy T’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/T22141e.stderr deleted ===================================== @@ -1,22 +0,0 @@ -T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘42’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘T’ - In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘Proxy T’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -862,11 +862,6 @@ test('T21951a', normal, compile, ['-Wredundant-strictness-flags']) test('T21951b', normal, compile, ['-Wredundant-strictness-flags']) test('DataToTagSolving', normal, compile, ['']) test('T21550', normal, compile, ['']) -test('T22141a', normal, compile, ['']) -test('T22141b', normal, compile, ['']) -test('T22141c', normal, compile, ['']) -test('T22141d', normal, compile, ['']) -test('T22141e', [extra_files(['T22141e_Aux.hs'])], multimod_compile, ['T22141e.hs', '-v0']) test('T22141f', normal, compile, ['']) test('T22141g', normal, compile, ['']) test('T22310', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141a.stderr ===================================== @@ -1,6 +1,7 @@ - T22141a.hs:8:1: error: [GHC-68567] - • Illegal kind: ‘GHC.Num.Natural.Natural’ + • Illegal kind: ‘GHC.Internal.Bignum.Natural.Natural’ • In the expansion of type synonym ‘Nat’ In the data type declaration for ‘Vector’ - Suggested fix: Perhaps you intended to use DataKinds + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) + ===================================== testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141b.stderr ===================================== @@ -1,7 +1,8 @@ - T22141b.hs:10:1: error: [GHC-68567] - • Illegal kind: ‘GHC.Num.Natural.Natural’ + • Illegal kind: ‘GHC.Internal.Bignum.Natural.Natural’ • In the expansion of type synonym ‘Nat’ In the expansion of type synonym ‘MyNat’ In the data type declaration for ‘Vector’ - Suggested fix: Perhaps you intended to use DataKinds + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) + ===================================== testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141c.stderr ===================================== @@ -1,4 +1,6 @@ +T22141c.hs:10:11: error: [GHC-68567] + • Illegal kind: ‘Proxy T’ + • In a standalone kind signature for ‘D’: Proxy T -> Type + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) -T22141c.hs:8:17: error: [GHC-68567] - Illegal kind: ‘(# Type, Type #)’ - Suggested fix: Perhaps you intended to use DataKinds ===================================== testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141d.stderr ===================================== @@ -1,4 +1,6 @@ +T22141d.hs:10:11: error: [GHC-68567] + • Illegal kind: ‘Proxy T’ + • In a standalone kind signature for ‘D’: Proxy T -> Type + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) -T22141d.hs:8:17: error: [GHC-68567] - Illegal kind: ‘(# Type | Type #)’ - Suggested fix: Perhaps you intended to use DataKinds ===================================== testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141e.stderr ===================================== @@ -1,4 +1,6 @@ +T22141e.hs:8:11: error: [GHC-68567] + • Illegal kind: ‘Proxy T’ + • In a standalone kind signature for ‘D’: Proxy T -> Type + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) -T22141e.hs:7:17: error: [GHC-68567] - Illegal kind: ‘42’ - Suggested fix: Perhaps you intended to use DataKinds ===================================== testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -666,6 +666,11 @@ test('T21447', normal, compile_fail, ['']) test('T21530a', normal, compile_fail, ['']) test('T21530b', normal, compile_fail, ['']) test('Or4', normal, compile_fail, ['']) +test('T22141a', normal, compile_fail, ['']) +test('T22141b', normal, compile_fail, ['']) +test('T22141c', normal, compile_fail, ['']) +test('T22141d', normal, compile_fail, ['']) +test('T22141e', [extra_files(['T22141e_Aux.hs'])], multimod_compile_fail, ['T22141e.hs', '-v0']) test('T22570', normal, compile_fail, ['']) test('T22645', normal, compile_fail, ['']) test('T20666', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1cb814c08f31b69c4a8e081893bf0f95bbfd46a4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1cb814c08f31b69c4a8e081893bf0f95bbfd46a4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/b6179ce4/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 12:40:31 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 05 Mar 2025 07:40:31 -0500 Subject: [Git][ghc/ghc][wip/T25647] Enhance documentation on FamArgFlavour handling in type families and clarify... Message-ID: <67c8463f1ddf1_38c2cda517981005b7@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 6ab0b7c9 by Patrick at 2025-03-05T20:40:21+08:00 Enhance documentation on FamArgFlavour handling in type families and clarify implementation details in TyCon and HsType modules - - - - - 2 changed files: - compiler/GHC/Core/TyCon.hs - compiler/GHC/Tc/Gen/HsType.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -3053,6 +3053,12 @@ For instance, for an instance declaration like the first two underscores (free arguments) would yield TyVarTv’s while the last two underscores (a class argument and a signature argument) would produce TauTv's. +<Implemenation Detail> +The ClassArg and FreeArg are generated in `mkFamilyTyCon` and store at `famTcParent` field at `FamilyTyCon`. +When typechecking type families, the `FamArgFlavour's passed in `tcAnonWildCardOcc` when dancing around +inside `tcInferTyApps` and `SigArg` is passed down at `HsKindSig` branch of `tcHsType` in the dance. + + <More on SigArg> Example from T14366 ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -1286,6 +1286,7 @@ tcHsType mode rn_ty@(HsOpTy{}) exp_kind = tc_app_ty mode rn_ty exp_kind tcHsType mode rn_ty@(HsKindSig _ ty sig) exp_kind = do { let mode' = (updateFamArgFlavour SigArg $ mode { mode_tyki = KindLevel}) + -- see Note [FamArgFlavour] ; traceTc "tcHsType:sig0" (ppr ty <+> ppr (mode_holes mode')) ; sig' <- tc_lhs_kind_sig mode' KindSigCtxt sig -- We must typecheck the kind signature, and solve all @@ -1578,7 +1579,7 @@ tcInferTyApps, tcInferTyApps_nosat -> LHsType GhcRn -- ^ Function (for printing only) -> TcType -- ^ Function -> [LHsTypeArg GhcRn] -- ^ Args - -> [FamArgFlavour] -- ^ Args + -> [FamArgFlavour] -- ^ Args flavours see Note [FamArgFlavour] and -> TcM (TcType, TcKind) -- ^ (f args, result kind) tcInferTyApps mode hs_ty fun hs_args famArgFlvs = do { (f_args, res_k) <- tcInferTyApps_nosat mode hs_ty fun hs_args famArgFlvs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ab0b7c9a0edd1931a456166320b73b72a037b1b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ab0b7c9a0edd1931a456166320b73b72a037b1b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/7e6c1a1f/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 12:48:09 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 05 Mar 2025 07:48:09 -0500 Subject: [Git][ghc/ghc][wip/T25647] format Message-ID: <67c848098c44_3c1099c5da0109b@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: d6ea25d6 by Patrick at 2025-03-05T20:47:59+08:00 format - - - - - 1 changed file: - compiler/GHC/Core/TyCon.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -3050,14 +3050,14 @@ For instance, for an instance declaration like instance C Int [x] Bool where type F _ _ (_ :: _) = Int -the first two underscores (free arguments) would yield TyVarTv’s while the last two underscores (a class -argument and a signature argument) would produce TauTv's. +the first two underscores (free arguments) would yield TyVarTv’s while the last two +underscores (a class argument and a signature argument) would produce TauTv's. <Implemenation Detail> -The ClassArg and FreeArg are generated in `mkFamilyTyCon` and store at `famTcParent` field at `FamilyTyCon`. -When typechecking type families, the `FamArgFlavour's passed in `tcAnonWildCardOcc` when dancing around -inside `tcInferTyApps` and `SigArg` is passed down at `HsKindSig` branch of `tcHsType` in the dance. - +The ClassArg and FreeArg are generated in `mkFamilyTyCon` and store at `famTcParent` +field at `FamilyTyCon`. When typechecking type families, the `FamArgFlavour's passed +in `tcAnonWildCardOcc` when dancing around inside `tcInferTyApps` and `SigArg` is +passed down at `HsKindSig` branch of `tcHsType` in the dance. <More on SigArg> Example from T14366 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d6ea25d657ae308f8888254fb394694466f58158 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d6ea25d657ae308f8888254fb394694466f58158 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/1f81ff90/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 13:26:39 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 05 Mar 2025 08:26:39 -0500 Subject: [Git][ghc/ghc][wip/T25657] 63 commits: compiler: use fromAscList when applicable Message-ID: <67c8510fc319a_3c109928c724133b8@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25657 at Glasgow Haskell Compiler / GHC Commits: 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-â” |---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | â””-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - 89b74b2d by Simon Peyton Jones at 2025-03-05T13:26:28+00:00 Remove the Core flattener Needs a full commit message - - - - - a3ed0bbd by Simon Peyton Jones at 2025-03-05T13:26:28+00:00 Wibbles - - - - - 99f641db by Simon Peyton Jones at 2025-03-05T13:26:28+00:00 Wibble - - - - - da5ff5fe by Simon Peyton Jones at 2025-03-05T13:26:28+00:00 More wibbles - - - - - 85c48696 by Simon Peyton Jones at 2025-03-05T13:26:28+00:00 Wibbles - - - - - 0356c148 by Simon Peyton Jones at 2025-03-05T13:26:28+00:00 More wibbles - - - - - 5ce80d9c by Simon Peyton Jones at 2025-03-05T13:26:29+00:00 More updates - - - - - 6d6e1597 by Simon Peyton Jones at 2025-03-05T13:26:29+00:00 More wibbles - - - - - 33aad9b0 by Simon Peyton Jones at 2025-03-05T13:26:29+00:00 Wibbles - - - - - 413a30b5 by Simon Peyton Jones at 2025-03-05T13:26:29+00:00 Remove unnecessary import - - - - - 522a84e1 by Simon Peyton Jones at 2025-03-05T13:26:29+00:00 Comments - - - - - 063d0f8e by Simon Peyton Jones at 2025-03-05T13:26:29+00:00 Comments and a bit of renaming - - - - - 262 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Instance/FunDeps.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Panic.hs - distrib/configure.ac.in - docs/users_guide/ghci.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/wasm/JSFFI.c - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - + testsuite/tests/indexed-types/should_compile/T25657.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/typecheck/should_compile/InstanceGivenOverlap.hs - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/doc/conf.py - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6cca10b868d07d8b846b4a83480ca3f016e672c3...063d0f8ec04e2b0c945e4452562bf284cf892af2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6cca10b868d07d8b846b4a83480ca3f016e672c3...063d0f8ec04e2b0c945e4452562bf284cf892af2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/1b8c66d2/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 13:38:48 2025 From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher)) Date: Wed, 05 Mar 2025 08:38:48 -0500 Subject: [Git][ghc/ghc][wip/T18462] Multiplicity annotation on records Message-ID: <67c853e8275e2_3c10998632b015224@gitlab.mail> Sjoerd Visscher pushed to branch wip/T18462 at Glasgow Haskell Compiler / GHC Commits: 279c3e28 by Sjoerd Visscher at 2025-03-05T14:38:40+01:00 Multiplicity annotation on records New HsConDeclField Merge HsMultAnn and HsMultAnnOn - - - - - 79 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Id/Make.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/linear_types.rst - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - + testsuite/tests/linear/should_compile/NonLinearRecord.hs - testsuite/tests/linear/should_compile/all.T - + testsuite/tests/linear/should_fail/LinearRecFieldMany.hs - + testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr - testsuite/tests/linear/should_fail/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T15279.stderr - testsuite/tests/parser/should_fail/T3811c.stderr - testsuite/tests/parser/should_fail/unpack_inside_type.stderr - testsuite/tests/printer/T18791.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/LinearTypes.html - utils/haddock/html-test/src/LinearTypes.hs - utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex - utils/haddock/latex-test/src/LinearTypes/LinearTypes.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/279c3e2879ed0865e2d6c6278d6a8b8801106812 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/279c3e2879ed0865e2d6c6278d6a8b8801106812 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/d1dcca2e/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 13:39:13 2025 From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher)) Date: Wed, 05 Mar 2025 08:39:13 -0500 Subject: [Git][ghc/ghc][wip/T18462] 52 commits: compiler: use fromAscList when applicable Message-ID: <67c8540149c7b_3c1099698fac15859@gitlab.mail> Sjoerd Visscher pushed to branch wip/T18462 at Glasgow Haskell Compiler / GHC Commits: 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-â” |---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | â””-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - ccd5eb3a by Sjoerd Visscher at 2025-03-05T14:39:01+01:00 Multiplicity annotation on records New HsConDeclField Merge HsMultAnn and HsMultAnnOn - - - - - 307 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.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/Bind.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Type.hs - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/linear_types.rst - docs/users_guide/ghci.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/wasm/JSFFI.c - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/linear/should_compile/NonLinearRecord.hs - testsuite/tests/linear/should_compile/all.T - + testsuite/tests/linear/should_fail/LinearRecFieldMany.hs - + testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr - testsuite/tests/linear/should_fail/all.T - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T15279.stderr - testsuite/tests/parser/should_fail/T3811c.stderr - testsuite/tests/parser/should_fail/unpack_inside_type.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/printer/T18791.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/LinearTypes.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/haddock/html-test/src/LinearTypes.hs - utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex - utils/haddock/latex-test/src/LinearTypes/LinearTypes.hs - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/279c3e2879ed0865e2d6c6278d6a8b8801106812...ccd5eb3a6f5e53505d4fc5d8d9159d4716f5e9e7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/279c3e2879ed0865e2d6c6278d6a8b8801106812...ccd5eb3a6f5e53505d4fc5d8d9159d4716f5e9e7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/f4b2eeee/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 13:59:14 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 05 Mar 2025 08:59:14 -0500 Subject: [Git][ghc/ghc][wip/T25647] Refactor documentation on wildcards in type families and clarify... Message-ID: <67c858b1b0e64_3e7f0cc7ec097f@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 92486dbd by Patrick at 2025-03-05T21:59:01+08:00 Refactor documentation on wildcards in type families and clarify implementation details in TyCon, Rename, and HsType modules - - - - - 4 changed files: - compiler/GHC/Core/TyCon.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/Language/Haskell/Syntax/Type.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2979,14 +2979,17 @@ tyConSkolem = isHoleName . tyConName -- not whether it is abstract or not. -{- Note [WildCards in type families] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Implementation tweak for wildCards in family instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Wildcards in type families are used to represent type/kind information that -are not specified by the user. It is controversial how to interpret wildcards -in type families. Hence We classify kinds of wildcards in type families into -three categories represented by the FamArgFlavour data type: ClassArg, FreeArg, -and SigArg, see Note [FamArgFlavour] for more detail. This flexibility allows -us to flip the interpretation of wildcards in type families. +are not specified by the user. See Note [Wildcards in family instances] for +more intuition. + +It is controversial how to interpret wildcards in type families. Hence We +classify kinds of wildcards in type families into three categories represented +by the FamArgFlavour data type: ClassArg, FreeArg, and SigArg, see Note [FamArgFlavour] +for more detail. This flexibility allows us to flip the interpretation of wildcards in +type families. Some common agreements: @@ -3014,8 +3017,15 @@ If maintaining backward compatibility from 8.6.4 to 9.10.2, the picks would be: - TauTv for ClassArg - TauTv for SigArg +<Implemenation Detail> +The ClassArg and FreeArg are generated in `mkFamilyTyCon` and store at `famTcParent` +field at `FamilyTyCon`. When typechecking type families, the `FamArgFlavour's passed +in `tcAnonWildCardOcc` when dancing around inside `tcInferTyApps` and `SigArg` is +passed down at `HsKindSig` branch of `tcHsType` in the dance. + See <More on SigArg> session in Note [FamArgFlavour] for why not just merge SigArg and ClassArg. +See also Note [Wildcards in family instances] for more intuition. For more discussion, see #13908. -} @@ -3053,12 +3063,6 @@ For instance, for an instance declaration like the first two underscores (free arguments) would yield TyVarTv’s while the last two underscores (a class argument and a signature argument) would produce TauTv's. -<Implemenation Detail> -The ClassArg and FreeArg are generated in `mkFamilyTyCon` and store at `famTcParent` -field at `FamilyTyCon`. When typechecking type families, the `FamArgFlavour's passed -in `tcAnonWildCardOcc` when dancing around inside `tcInferTyApps` and `SigArg` is -passed down at `HsKindSig` branch of `tcHsType` in the dance. - <More on SigArg> Example from T14366 @@ -3070,10 +3074,9 @@ now let's consider _ here as a FreeArg then TyVarTv, then it would not match Typ Say if we assign ClassArg to _ here, if we want to flip class arguments in associated type family to only match Type variables. Then this example would not work. -Another reason is that it is really hard for us to know if wildcard in signature in an +More over, it is really hard for us to know if wildcard in signature in an associated type family corresponding to a class argument or a free argument. -For example, in the following - code: +For example, in the following code: class C a b c where type F a (d :: TYPE a) (e :: TYPE k) f @@ -3102,6 +3105,8 @@ THe best way I can think of is to mark them as SigArg and treat them as TauTv. Hence we maintain three different flavours of wildcards in type families. This provides a flexibility to interpret wildcards in type families. +See Note [Implementation tweak for wildCards in family instances] for how we can explore +different design spaces. For more discussion, see #13908. -} ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -910,10 +910,15 @@ This is implemented as follows: Unnamed wildcards remain unchanged after the renamer, and then given fresh meta-variables during typechecking, and it is handled pretty much the same way as the ones in partial type signatures. We however don't want to emit hole constraints on wildcards in family -instances, so we turn on PartialTypeSignatures and turn off warning flag to -let typechecker know this. +instances, We use special hole_mode `HM_FamPat` to indicate that. + See related Note [Wildcards in visible kind application] in GHC.Tc.Gen.HsType +But over the develoment wildcards have became unintentionally more powerful +in associated type family instances since it's relation to the parent class +variables. It become confusing, See Note [Implementation tweak for wildCards in family instances] +for how we can explore the design space to make it more consistent. + Note [Unused type variables in family instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When the flag -fwarn-unused-type-patterns is on, the compiler reports ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -1295,7 +1295,7 @@ tcHsType mode rn_ty@(HsKindSig _ ty sig) exp_kind -- to be fully determined (#14904) ; traceTc "tcHsType:sig" (ppr ty $$ ppr sig') ; ty' <- tcAddKindSigPlaceholders sig $ - tc_check_lhs_type mode' ty sig' + tc_check_lhs_type mode ty sig' ; checkExpKind rn_ty ty' sig' exp_kind } -- See Note [Typechecking HsCoreTys] @@ -2266,7 +2266,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) } HM_FamPat ClassArg -> newTauTvDetailsAtLevel HM_FamPat SigArg -> newTauTvDetailsAtLevel _ -> newTauTvDetailsAtLevel - -- see Note [WildCards in type families] + -- see Note [Implementation tweak for wildCards in family instances] emit_holes = case hole_mode of HM_Sig -> True HM_FamPat _ -> False ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -216,7 +216,8 @@ A wildcard in a type can be written '_' In HsType this is represented by HsWildCardTy. The renamer leaves it untouched, and it is later given a fresh - meta tyvar in the typechecker. + meta tyvar in the typechecker. The wildcard in type families can + be cumbersome to deal with, See Note [Implementation tweak for wildCards in family instances]. * A named wildcard, written '_a', '_foo', etc View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92486dbd8e5af2b7fc40f96b98118af5767e1ef0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92486dbd8e5af2b7fc40f96b98118af5767e1ef0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/39b1e97f/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 14:00:51 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 05 Mar 2025 09:00:51 -0500 Subject: [Git][ghc/ghc][wip/T25647] Rename variable `famArgFlvs` to `fam_arg_flvs` for consistency in type inference functions Message-ID: <67c859138d094_3e7f0cc7f601613@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 5824b5f5 by Patrick at 2025-03-05T22:00:41+08:00 Rename variable `famArgFlvs` to `fam_arg_flvs` for consistency in type inference functions - - - - - 1 changed file: - compiler/GHC/Tc/Gen/HsType.hs Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -1581,8 +1581,8 @@ tcInferTyApps, tcInferTyApps_nosat -> [LHsTypeArg GhcRn] -- ^ Args -> [FamArgFlavour] -- ^ Args flavours see Note [FamArgFlavour] and -> TcM (TcType, TcKind) -- ^ (f args, result kind) -tcInferTyApps mode hs_ty fun hs_args famArgFlvs - = do { (f_args, res_k) <- tcInferTyApps_nosat mode hs_ty fun hs_args famArgFlvs +tcInferTyApps mode hs_ty fun hs_args fam_arg_flvs + = do { (f_args, res_k) <- tcInferTyApps_nosat mode hs_ty fun hs_args fam_arg_flvs ; saturateFamApp f_args res_k } tcInferTyApps_nosat mode orig_hs_ty fun orig_hs_args fam_arg_flvs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5824b5f5830ea7b73113fafb59aa98cb632b55eb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5824b5f5830ea7b73113fafb59aa98cb632b55eb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/833f659f/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 14:04:58 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 05 Mar 2025 09:04:58 -0500 Subject: [Git][ghc/ghc][wip/T25657] Remove the Core flattener Message-ID: <67c85a0ae96fc_3e7f0c38088854e5@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25657 at Glasgow Haskell Compiler / GHC Commits: da2b4e47 by Simon Peyton Jones at 2025-03-05T14:04:18+00:00 Remove the Core flattener This big MR entirely removes the "flattener" that took a type and replaced each type-family application with a fresh type variable. The flattener had its origin in the paper Injective type families for Haskell But (a) #25657 showed that flattening doesn't really work. (b) since we wrote the paper we have introduced the so-called "fine-grained" unifier GHC.Core.Unify, which can return * SurelyApart * Unifiable subst * MaybeApart subst where the MaybeApart says that the two types are not unifiable by a substitution, but could (perhaps) be unified "later" after some type family reductions. This turns out to subsume flattening. This MR does a major refactor of GHC.Core.Unify to make it capable of subsuming flattening. The main payload is described in Note [Apartness and type families] and its many wrinkles. The key (non-refactoring) implementation change is to add `um_fam_env` to the `UMState` in the unification monad. Careful review with Richard revealed various bugs in the treament of `kco`, the kind coercion carried around by the unifier, so that is substantially fixed too: see Note [Kind coercions in Unify]. Compile-time performance is improved by 0.1% with a few improvements over 1% and one worsening by 1.3% namely T9872a. (I have not investigated the latter.) Metric Decrease: T9872b T9872c TcPlugin_RewritePerf Metric Increase: T9872a - - - - - 21 changed files: - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/FunDeps.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Utils/Panic.hs - + testsuite/tests/indexed-types/should_compile/T25657.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/typecheck/should_compile/InstanceGivenOverlap.hs Changes: ===================================== compiler/GHC/Core/FamInstEnv.hs ===================================== @@ -487,8 +487,8 @@ Here is how we do it: apart(target, pattern) = not (unify(flatten(target), pattern)) where flatten (implemented in flattenTys, below) converts all type-family -applications into fresh variables. (See -Note [Flattening type-family applications when matching instances] in GHC.Core.Unify.) +applications into fresh variables. (See Note [Apartness and type families] +in GHC.Core.Unify.) Note [Compatibility] ~~~~~~~~~~~~~~~~~~~~ @@ -512,11 +512,11 @@ might be Int and therefore 'F a' should be Bool. We can simplify 'F a' to Int only when we can be sure that 'a' is not Int. To achieve this, after finding a possible match within the equations, we have to -go back to all previous equations and check that, under the -substitution induced by the match, other branches are surely apart. (See -Note [Apartness].) This is similar to what happens with class -instance selection, when we need to guarantee that there is only a match and -no unifiers. The exact algorithm is different here because the +go back to all previous equations and check that, under the substitution induced +by the match, other branches are surely apart, using `tcUnifyTysFG`. (See +Note [Apartness and type families] in GHC.Core.Unify.) This is similar to what +happens with class instance selection, when we need to guarantee that there is +only a match and no unifiers. The exact algorithm is different here because the potentially-overlapping group is closed. As another example, consider this: @@ -579,7 +579,7 @@ fails anyway. compatibleBranches :: CoAxBranch -> CoAxBranch -> Bool compatibleBranches (CoAxBranch { cab_lhs = lhs1, cab_rhs = rhs1 }) (CoAxBranch { cab_lhs = lhs2, cab_rhs = rhs2 }) - = case tcUnifyTysFG alwaysBindFun commonlhs1 commonlhs2 of + = case tcUnifyTysFG alwaysBindFam alwaysBindTv commonlhs1 commonlhs2 of -- Here we need the cab_tvs of the two branches to be disinct. -- See Note [CoAxBranch type variables] in GHC.Core.Coercion.Axiom. SurelyApart -> True @@ -610,7 +610,8 @@ injectiveBranches injectivity -- See Note [Verifying injectivity annotation], case 1. = let getInjArgs = filterByList injectivity in_scope = mkInScopeSetList (tvs1 ++ tvs2) - in case tcUnifyTyWithTFs True in_scope rhs1 rhs2 of -- True = two-way pre-unification + in case tcUnifyTyForInjectivity True in_scope rhs1 rhs2 of + -- True = two-way pre-unification Nothing -> InjectivityAccepted -- RHS are different, so equations are injective. -- This is case 1A from Note [Verifying injectivity annotation] @@ -1228,22 +1229,16 @@ findBranch branches target_tys -> Maybe (BranchIndex, [Type], [Coercion]) go (index, branch) other = let (CoAxBranch { cab_tvs = tpl_tvs, cab_cvs = tpl_cvs - , cab_lhs = tpl_lhs - , cab_incomps = incomps }) = branch - in_scope = mkInScopeSet (unionVarSets $ - map (tyCoVarsOfTypes . coAxBranchLHS) incomps) - -- See Note [Flattening type-family applications when matching instances] - -- in GHC.Core.Unify - flattened_target = flattenTys in_scope target_tys + , cab_lhs = tpl_lhs }) = branch in case tcMatchTys tpl_lhs target_tys of - Just subst -- matching worked. now, check for apartness. - | apartnessCheck flattened_target branch - -> -- matching worked & we're apart from all incompatible branches. + Just subst -- Matching worked. now, check for apartness. + | apartnessCheck target_tys branch + -> -- Matching worked & we're apart from all incompatible branches. -- success assert (all (isJust . lookupCoVar subst) tpl_cvs) $ Just (index, substTyVars subst tpl_tvs, substCoVars subst tpl_cvs) - -- failure. keep looking + -- Failure. keep looking _ -> other -- | Do an apartness check, as described in the "Closed Type Families" paper @@ -1251,15 +1246,12 @@ findBranch branches target_tys -- ('CoAxBranch') of a closed type family can be used to reduce a certain target -- type family application. apartnessCheck :: [Type] - -- ^ /flattened/ target arguments. Make sure they're flattened! See - -- Note [Flattening type-family applications when matching instances] - -- in GHC.Core.Unify. - -> CoAxBranch -- ^ the candidate equation we wish to use + -> CoAxBranch -- ^ The candidate equation we wish to use -- Precondition: this matches the target -> Bool -- ^ True <=> equation can fire -apartnessCheck flattened_target (CoAxBranch { cab_incomps = incomps }) +apartnessCheck target (CoAxBranch { cab_incomps = incomps }) = all (isSurelyApart - . tcUnifyTysFG alwaysBindFun flattened_target + . tcUnifyTysFG alwaysBindFam alwaysBindTv target . coAxBranchLHS) incomps where isSurelyApart SurelyApart = True ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -174,7 +174,7 @@ That is, they are Reason for freshness: we use unification when checking for overlap etc, and that requires the tyvars to be distinct. -The invariant is checked by the ASSERT in lookupInstEnv'. +The invariant is checked by the ASSERT in instEnvMatchesAndUnifiers. Note [Proper-match fields] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1108,11 +1108,12 @@ nullUnifiers :: PotentialUnifiers -> Bool nullUnifiers NoUnifiers{} = True nullUnifiers _ = False -lookupInstEnv' :: InstEnv -- InstEnv to look in - -> VisibleOrphanModules -- But filter against this - -> Class -> [Type] -- What we are looking for - -> ([InstMatch], -- Successful matches - PotentialUnifiers) -- These don't match but do unify +instEnvMatchesAndUnifiers + :: InstEnv -- InstEnv to look in + -> VisibleOrphanModules -- But filter against this + -> Class -> [Type] -- What we are looking for + -> ([InstMatch], -- Successful matches + PotentialUnifiers) -- These don't match but do unify -- (no incoherent ones in here) -- The second component of the result pair happens when we look up -- Foo [a] @@ -1124,7 +1125,7 @@ lookupInstEnv' :: InstEnv -- InstEnv to look in -- but Foo [Int] is a unifier. This gives the caller a better chance of -- giving a suitable error message -lookupInstEnv' (InstEnv rm) vis_mods cls tys +instEnvMatchesAndUnifiers (InstEnv rm) vis_mods cls tys = (foldr check_match [] rough_matches, check_unifiers rough_unifiers) where (rough_matches, rough_unifiers) = lookupRM' rough_tcs rm @@ -1162,10 +1163,14 @@ lookupInstEnv' (InstEnv rm) vis_mods cls tys -- Unification will break badly if the variables overlap -- They shouldn't because we allocate separate uniques for them -- See Note [Template tyvars are fresh] - case tcUnifyTysFG instanceBindFun tpl_tys tys of + case tcUnifyTysFG alwaysBindFam instanceBindFun tpl_tys tys of + -- alwaysBindFam: the family-application can't be in the instance head, + -- but it certainly can be in the Wanted constraint we are matching! + -- -- We consider MaybeApart to be a case where the instance might -- apply in the future. This covers an instance like C Int and -- a target like [W] C (F a), where F is a type family. + -- See (ATF1) in Note [Apartness and type families] in GHC.Core.Unify SurelyApart -> check_unifiers items -- See Note [Infinitary substitution in lookup] MaybeApart MARInfinite _ -> check_unifiers items @@ -1207,8 +1212,8 @@ lookupInstEnv check_overlap_safe tys = (final_matches, final_unifs, unsafe_overlapped) where - (home_matches, home_unifs) = lookupInstEnv' home_ie vis_mods cls tys - (pkg_matches, pkg_unifs) = lookupInstEnv' pkg_ie vis_mods cls tys + (home_matches, home_unifs) = instEnvMatchesAndUnifiers home_ie vis_mods cls tys + (pkg_matches, pkg_unifs) = instEnvMatchesAndUnifiers pkg_ie vis_mods cls tys all_matches = home_matches <> pkg_matches all_unifs = home_unifs <> pkg_unifs final_matches = pruneOverlappedMatches all_matches @@ -1579,14 +1584,14 @@ specialisation: overview] details how we achieve that. ************************************************************************ -} -instanceBindFun :: BindFun +instanceBindFun :: BindTvFun instanceBindFun tv _rhs_ty | isOverlappableTyVar tv = Apart | otherwise = BindMe - -- Note [Binding when looking up instances] + -- Note [Super skolems: binding when looking up instances] {- -Note [Binding when looking up instances] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Note [Super skolems: binding when looking up instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When looking up in the instance environment, or family-instance environment, we are careful about multiple matches, as described above in Note [Overlapping instances] @@ -1602,7 +1607,7 @@ them in the unification test. These are called "super skolems". Example: f :: T -> Int f (MkT x) = op [x,x] The op [x,x] means we need (Foo [a]). This `a` will never be instantiated, and -so it is a super skolem. (See the use of tcInstSuperSkolTyVarsX in +so it is a "super skolem". (See the use of tcInstSuperSkolTyVarsX in GHC.Tc.Gen.Pat.tcDataConPat.) Super skolems respond True to isOverlappableTyVar, and the use of Apart in instanceBindFun, above, means that these will be treated as fresh constants in the unification algorithm ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -2756,7 +2756,7 @@ lintBranch this_co fam_tc branch arg_kinds ; _ <- foldlM check_ki (empty_subst, empty_subst) (zip (ktvs ++ cvs) arg_kinds) - ; case check_no_conflict flattened_target incomps of + ; case check_no_conflict target incomps of Nothing -> return () Just bad_branch -> failWithL $ bad_ax this_co $ text "inconsistent with" <+> @@ -2782,15 +2782,12 @@ lintBranch this_co fam_tc branch arg_kinds subst = zipTvSubst tvs tys `composeTCvSubst` zipCvSubst cvs co_args target = Type.substTys subst (coAxBranchLHS branch) - in_scope = mkInScopeSet $ - unionVarSets (map (tyCoVarsOfTypes . coAxBranchLHS) incomps) - flattened_target = flattenTys in_scope target check_no_conflict :: [Type] -> [CoAxBranch] -> Maybe CoAxBranch check_no_conflict _ [] = Nothing check_no_conflict flat (b at CoAxBranch { cab_lhs = lhs_incomp } : rest) -- See Note [Apartness] in GHC.Core.FamInstEnv - | SurelyApart <- tcUnifyTysFG alwaysBindFun flat lhs_incomp + | SurelyApart <- tcUnifyTysFG alwaysBindFam alwaysBindTv flat lhs_incomp = check_no_conflict flat rest | otherwise = Just b ===================================== compiler/GHC/Core/Predicate.hs ===================================== @@ -30,7 +30,11 @@ module GHC.Core.Predicate ( isIPPred_maybe, -- Evidence variables - DictId, isEvVar, isDictId + DictId, isEvVar, isDictId, + + -- Equality left-hand sides + CanEqLHS(..), canEqLHS_maybe, canTyFamEqLHS_maybe, + canEqLHSKind, canEqLHSType, eqCanEqLHS, ) where @@ -38,7 +42,7 @@ import GHC.Prelude import GHC.Core.Type import GHC.Core.Class -import GHC.Core.TyCo.Compare( eqType ) +import GHC.Core.TyCo.Compare( eqType, tcEqTyConApps ) import GHC.Core.TyCon import GHC.Core.TyCon.RecWalk import GHC.Types.Var @@ -52,6 +56,13 @@ import GHC.Utils.Misc import GHC.Utils.Panic import GHC.Data.FastString + +{- ********************************************************************* +* * +* Pred and PredType * +* * +********************************************************************* -} + -- | A predicate in the solver. The solver tries to prove Wanted predicates -- from Given ones. data Pred @@ -229,9 +240,12 @@ predTypeEqRel ty | isReprEqPred ty = ReprEq | otherwise = NomEq -{------------------------------------------- -Predicates on PredType ---------------------------------------------} + +{- ********************************************************************* +* * +* Predicates on PredType * +* * +********************************************************************* -} {- Note [Evidence for quantified constraints] @@ -492,3 +506,61 @@ isEvVar var = isEvVarType (varType var) isDictId :: Id -> Bool isDictId id = isDictTy (varType id) + + +{- ********************************************************************* +* * +* Equality left-hand sides +* * +********************************************************************* -} + +-- | A 'CanEqLHS' is a type that can appear on the left of a canonical +-- equality: a type variable or /exactly-saturated/ type family application. +data CanEqLHS + = TyVarLHS TyVar + | TyFamLHS TyCon -- ^ TyCon of the family + [Type] -- ^ Arguments, /exactly saturating/ the family + +instance Outputable CanEqLHS where + ppr (TyVarLHS tv) = ppr tv + ppr (TyFamLHS fam_tc fam_args) = ppr (mkTyConApp fam_tc fam_args) + +----------------------------------- +-- | Is a type a canonical LHS? That is, is it a tyvar or an exactly-saturated +-- type family application? +-- Does not look through type synonyms. +canEqLHS_maybe :: Type -> Maybe CanEqLHS +canEqLHS_maybe xi + | Just tv <- getTyVar_maybe xi + = Just $ TyVarLHS tv + + | otherwise + = canTyFamEqLHS_maybe xi + +canTyFamEqLHS_maybe :: Type -> Maybe CanEqLHS +canTyFamEqLHS_maybe xi + | Just (tc, args) <- tcSplitTyConApp_maybe xi + , isTypeFamilyTyCon tc + , args `lengthIs` tyConArity tc + = Just $ TyFamLHS tc args + + | otherwise + = Nothing + +-- | Convert a 'CanEqLHS' back into a 'Type' +canEqLHSType :: CanEqLHS -> Type +canEqLHSType (TyVarLHS tv) = mkTyVarTy tv +canEqLHSType (TyFamLHS fam_tc fam_args) = mkTyConApp fam_tc fam_args + +-- | Retrieve the kind of a 'CanEqLHS' +canEqLHSKind :: CanEqLHS -> Kind +canEqLHSKind (TyVarLHS tv) = tyVarKind tv +canEqLHSKind (TyFamLHS fam_tc fam_args) = piResultTys (tyConKind fam_tc) fam_args + +-- | Are two 'CanEqLHS's equal? +eqCanEqLHS :: CanEqLHS -> CanEqLHS -> Bool +eqCanEqLHS (TyVarLHS tv1) (TyVarLHS tv2) = tv1 == tv2 +eqCanEqLHS (TyFamLHS fam_tc1 fam_args1) (TyFamLHS fam_tc2 fam_args2) + = tcEqTyConApps fam_tc1 fam_args1 fam_tc2 fam_args2 +eqCanEqLHS _ _ = False + ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -11,17 +11,18 @@ module GHC.Core.Unify ( tcMatchTyX_BM, ruleMatchTyKiX, -- Side-effect free unification - tcUnifyTy, tcUnifyTyKi, tcUnifyTys, tcUnifyTyKis, - tcUnifyTysFG, tcUnifyTyWithTFs, - BindFun, BindFlag(..), matchBindFun, alwaysBindFun, + tcUnifyTy, tcUnifyTys, tcUnifyFunDeps, tcUnifyDebugger, + tcUnifyTysFG, tcUnifyTyForInjectivity, + BindTvFun, BindFamFun, BindFlag(..), + matchBindTv, alwaysBindTv, alwaysBindFam, dontCareBindFam, UnifyResult, UnifyResultM(..), MaybeApartReason(..), typesCantMatch, typesAreApart, -- Matching a type against a lifted type (coercion) - liftCoMatch, + liftCoMatch -- The core flattening algorithm - flattenTys, flattenTysX, +-- flattenTys, flattenTysX, ) where @@ -30,32 +31,34 @@ import GHC.Prelude import GHC.Types.Var import GHC.Types.Var.Env import GHC.Types.Var.Set -import GHC.Types.Name( Name, mkSysTvName, mkSystemVarName ) import GHC.Builtin.Names( tYPETyConKey, cONSTRAINTTyConKey ) import GHC.Core.Type hiding ( getTvSubstEnv ) import GHC.Core.Coercion hiding ( getCvSubstEnv ) import GHC.Core.TyCon +import GHC.Core.Predicate( CanEqLHS(..), canEqLHS_maybe ) +import GHC.Core.TyCon.Env import GHC.Core.TyCo.Rep -import GHC.Core.TyCo.Compare ( eqType, tcEqType ) +import GHC.Core.TyCo.Compare ( eqType, tcEqType, tcEqTyConApps ) import GHC.Core.TyCo.FVs ( tyCoVarsOfCoList, tyCoFVsOfTypes ) -import GHC.Core.TyCo.Subst ( mkTvSubst, emptyIdSubstEnv ) +import GHC.Core.TyCo.Subst ( mkTvSubst ) import GHC.Core.Map.Type +import GHC.Core.Multiplicity + import GHC.Utils.FV( FV, fvVarList ) import GHC.Utils.Misc -import GHC.Data.Pair import GHC.Utils.Outputable -import GHC.Types.Unique +import GHC.Types.Basic( SwapFlag(..) ) import GHC.Types.Unique.FM -import GHC.Types.Unique.Set import GHC.Exts( oneShot ) import GHC.Utils.Panic -import GHC.Data.FastString -import Data.List ( mapAccumL ) +import GHC.Data.Pair +import GHC.Data.TrieMap +import GHC.Data.Maybe( orElse ) + import Control.Monad import qualified Data.Semigroup as S import GHC.Builtin.Types.Prim (fUNTyCon) -import GHC.Core.Multiplicity {- @@ -109,15 +112,56 @@ How do you choose between them? equals the kind of the target, then use the TyKi version. -} --- | Some unification functions are parameterised by a 'BindFun', which +-- | Some unification functions are parameterised by a 'BindTvFun', which -- says whether or not to allow a certain unification to take place. --- A 'BindFun' takes the 'TyVar' involved along with the 'Type' it will +-- A 'BindTvFun' takes the 'TyVar' involved along with the 'Type' it will -- potentially be bound to. -- -- It is possible for the variable to actually be a coercion variable -- (Note [Matching coercion variables]), but only when one-way matching. -- In this case, the 'Type' will be a 'CoercionTy'. -type BindFun = TyCoVar -> Type -> BindFlag +type BindTvFun = TyCoVar -> Type -> BindFlag + +-- | BindFamFun is similiar to BindTvFun, but deals with a saturated +-- type-family application. See Note [Apartness and type families]. +type BindFamFun = TyCon -> [Type] -> Type -> BindFlag + +-- | Allow binding only for any variable in the set. Variables may +-- be bound to any type. +-- Used when doing simple matching; e.g. can we find a substitution +-- +-- @ +-- S = [a :-> t1, b :-> t2] such that +-- S( Maybe (a, b->Int ) = Maybe (Bool, Char -> Int) +-- @ +matchBindTv :: TyCoVarSet -> BindTvFun +matchBindTv tvs tv _ty + | tv `elemVarSet` tvs = BindMe + | otherwise = Apart + +-- | Allow the binding of any variable to any type +alwaysBindTv :: BindTvFun +alwaysBindTv _tv _ty = BindMe + +-- | Allow the binding of a type-family application to any type +alwaysBindFam :: BindFamFun +alwaysBindFam _tc _args _rhs = BindMe + +dontCareBindFam :: HasCallStack => BindFamFun +dontCareBindFam tc args rhs + = pprPanic "dontCareBindFam" $ + vcat [ ppr tc <+> ppr args, text "rhs" <+> ppr rhs ] + +-- | Don't allow the binding of a type-family application at all +neverBindFam :: BindFamFun +neverBindFam _tc _args _rhs = Apart + + +{- ********************************************************************* +* * + Various wrappers for matching +* * +********************************************************************* -} -- | @tcMatchTy t1 t2@ produces a substitution (over fvs(t1)) -- @s@ such that @s(t1)@ equals @t2 at . @@ -131,67 +175,67 @@ type BindFun = TyCoVar -> Type -> BindFlag -- always used on top-level types, so we can bind any of the -- free variables of the LHS. -- See also Note [tcMatchTy vs tcMatchTyKi] -tcMatchTy :: Type -> Type -> Maybe Subst +tcMatchTy :: HasDebugCallStack => Type -> Type -> Maybe Subst tcMatchTy ty1 ty2 = tcMatchTys [ty1] [ty2] -tcMatchTyX_BM :: BindFun -> Subst +tcMatchTyX_BM :: HasDebugCallStack => BindTvFun -> Subst -> Type -> Type -> Maybe Subst -tcMatchTyX_BM bind_me subst ty1 ty2 - = tc_match_tys_x bind_me False subst [ty1] [ty2] +tcMatchTyX_BM bind_tv subst ty1 ty2 + = tc_match_tys_x bind_tv False subst [ty1] [ty2] -- | Like 'tcMatchTy', but allows the kinds of the types to differ, -- and thus matches them as well. -- See also Note [tcMatchTy vs tcMatchTyKi] -tcMatchTyKi :: Type -> Type -> Maybe Subst +tcMatchTyKi :: HasDebugCallStack => Type -> Type -> Maybe Subst tcMatchTyKi ty1 ty2 - = tc_match_tys alwaysBindFun True [ty1] [ty2] + = tc_match_tys alwaysBindTv True [ty1] [ty2] -- | This is similar to 'tcMatchTy', but extends a substitution -- See also Note [tcMatchTy vs tcMatchTyKi] -tcMatchTyX :: Subst -- ^ Substitution to extend +tcMatchTyX :: HasDebugCallStack => Subst -- ^ Substitution to extend -> Type -- ^ Template -> Type -- ^ Target -> Maybe Subst tcMatchTyX subst ty1 ty2 - = tc_match_tys_x alwaysBindFun False subst [ty1] [ty2] + = tc_match_tys_x alwaysBindTv False subst [ty1] [ty2] -- | Like 'tcMatchTy' but over a list of types. -- See also Note [tcMatchTy vs tcMatchTyKi] -tcMatchTys :: [Type] -- ^ Template +tcMatchTys :: HasDebugCallStack => [Type] -- ^ Template -> [Type] -- ^ Target -> Maybe Subst -- ^ One-shot; in principle the template -- variables could be free in the target tcMatchTys tys1 tys2 - = tc_match_tys alwaysBindFun False tys1 tys2 + = tc_match_tys alwaysBindTv False tys1 tys2 -- | Like 'tcMatchTyKi' but over a list of types. -- See also Note [tcMatchTy vs tcMatchTyKi] -tcMatchTyKis :: [Type] -- ^ Template +tcMatchTyKis :: HasDebugCallStack => [Type] -- ^ Template -> [Type] -- ^ Target -> Maybe Subst -- ^ One-shot substitution tcMatchTyKis tys1 tys2 - = tc_match_tys alwaysBindFun True tys1 tys2 + = tc_match_tys alwaysBindTv True tys1 tys2 -- | Like 'tcMatchTys', but extending a substitution -- See also Note [tcMatchTy vs tcMatchTyKi] -tcMatchTysX :: Subst -- ^ Substitution to extend +tcMatchTysX :: HasDebugCallStack => Subst -- ^ Substitution to extend -> [Type] -- ^ Template -> [Type] -- ^ Target -> Maybe Subst -- ^ One-shot substitution tcMatchTysX subst tys1 tys2 - = tc_match_tys_x alwaysBindFun False subst tys1 tys2 + = tc_match_tys_x alwaysBindTv False subst tys1 tys2 -- | Like 'tcMatchTyKis', but extending a substitution -- See also Note [tcMatchTy vs tcMatchTyKi] -tcMatchTyKisX :: Subst -- ^ Substitution to extend +tcMatchTyKisX :: HasDebugCallStack => Subst -- ^ Substitution to extend -> [Type] -- ^ Template -> [Type] -- ^ Target -> Maybe Subst -- ^ One-shot substitution tcMatchTyKisX subst tys1 tys2 - = tc_match_tys_x alwaysBindFun True subst tys1 tys2 + = tc_match_tys_x alwaysBindTv True subst tys1 tys2 -- | Same as tc_match_tys_x, but starts with an empty substitution -tc_match_tys :: BindFun +tc_match_tys :: HasDebugCallStack => BindTvFun -> Bool -- ^ match kinds? -> [Type] -> [Type] @@ -202,14 +246,15 @@ tc_match_tys bind_me match_kis tys1 tys2 in_scope = mkInScopeSet (tyCoVarsOfTypes tys1 `unionVarSet` tyCoVarsOfTypes tys2) -- | Worker for 'tcMatchTysX' and 'tcMatchTyKisX' -tc_match_tys_x :: BindFun +tc_match_tys_x :: HasDebugCallStack => BindTvFun -> Bool -- ^ match kinds? -> Subst -> [Type] -> [Type] -> Maybe Subst -tc_match_tys_x bind_me match_kis (Subst in_scope id_env tv_env cv_env) tys1 tys2 - = case tc_unify_tys bind_me +tc_match_tys_x bind_tv match_kis (Subst in_scope id_env tv_env cv_env) tys1 tys2 + = case tc_unify_tys alwaysBindFam -- (ATF7) in Note [Apartness and type families] + bind_tv False -- Matching, not unifying False -- Not an injectivity check match_kis @@ -230,31 +275,21 @@ ruleMatchTyKiX -> Maybe TvSubstEnv ruleMatchTyKiX tmpl_tvs rn_env tenv tmpl target -- See Note [Kind coercions in Unify] - = case tc_unify_tys (matchBindFun tmpl_tvs) False False - True -- <-- this means to match the kinds + = case tc_unify_tys neverBindFam (matchBindTv tmpl_tvs) + -- neverBindFam: a type family probably shouldn't appear + -- on the LHS of a RULE, although we don't currently prevent it. + -- But even if it did and we allowed it to bind, we would + -- never get Unifiable, which is all this function cares about. + -- So neverBindFam is fine here. + False -- Matching, not unifying + False -- No doing an injectivity check + True -- Match the kinds IgnoreMultiplicities -- See Note [Rewrite rules ignore multiplicities in FunTy] rn_env tenv emptyCvSubstEnv [tmpl] [target] of Unifiable (tenv', _) -> Just tenv' _ -> Nothing --- | Allow binding only for any variable in the set. Variables may --- be bound to any type. --- Used when doing simple matching; e.g. can we find a substitution --- --- @ --- S = [a :-> t1, b :-> t2] such that --- S( Maybe (a, b->Int ) = Maybe (Bool, Char -> Int) --- @ -matchBindFun :: TyCoVarSet -> BindFun -matchBindFun tvs tv _ty - | tv `elemVarSet` tvs = BindMe - | otherwise = Apart - --- | Allow the binding of any variable to any type -alwaysBindFun :: BindFun -alwaysBindFun _tv _ty = BindMe - {- ************************************************************************ * * @@ -299,18 +334,171 @@ typesCantMatch :: [(Type,Type)] -> Bool typesCantMatch prs = any (uncurry typesAreApart) prs typesAreApart :: Type -> Type -> Bool -typesAreApart t1 t2 = case tcUnifyTysFG alwaysBindFun [t1] [t2] of +typesAreApart t1 t2 = case tcUnifyTysFG alwaysBindFam alwaysBindTv [t1] [t2] of SurelyApart -> True _ -> False {- ************************************************************************ * * - Unification + Various wrappers for unification * * -************************************************************************ +********************************************************************* -} -Note [Fine-grained unification] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- | Simple unification of two types; all type variables are bindable +-- Precondition: the kinds are already equal +tcUnifyTy :: Type -> Type -- All tyvars are bindable + -> Maybe Subst + -- A regular one-shot (idempotent) substitution +tcUnifyTy t1 t2 = tcUnifyTys alwaysBindTv [t1] [t2] + +tcUnifyDebugger :: Type -> Type -> Maybe Subst +tcUnifyDebugger t1 t2 + = case tc_unify_tys_fg + True -- Unify kinds + alwaysBindFam -- Type families can show up + alwaysBindTv + [t1] [t2] of + Unifiable subst -> Just subst + _ -> Nothing + +-- | Like 'tcUnifyTys' but also unifies the kinds +tcUnifyFunDeps :: TyCoVarSet + -> [Type] -> [Type] + -> Maybe Subst +tcUnifyFunDeps qtvs tys1 tys2 + = case tc_unify_tys_fg + True -- Unify kinds + dontCareBindFam -- Class-instance heads never mention type families + (matchBindTv qtvs) + tys1 tys2 of + Unifiable subst -> Just subst + _ -> Nothing + +-- | Unify or match a type-family RHS with a type (possibly another type-family RHS) +-- Precondition: kinds are the same +tcUnifyTyForInjectivity + :: AmIUnifying -- ^ True <=> do two-way unification; + -- False <=> do one-way matching. + -- See end of sec 5.2 from the paper + -> InScopeSet -- Should include the free tyvars of both Type args + -> Type -> Type -- Types to unify + -> Maybe Subst +-- This algorithm is an implementation of the "Algorithm U" presented in +-- the paper "Injective type families for Haskell", Figures 2 and 3. +-- The code is incorporated with the standard unifier for convenience, but +-- its operation should match the specification in the paper. +tcUnifyTyForInjectivity unif in_scope t1 t2 + = case tc_unify_tys alwaysBindFam alwaysBindTv + unif -- Am I unifying? + True -- Do injectivity checks + False -- Don't check outermost kinds + RespectMultiplicities + rn_env emptyTvSubstEnv emptyCvSubstEnv + [t1] [t2] of + Unifiable (tv_subst, _cv_subst) -> Just $ maybe_fix tv_subst + MaybeApart _reason (tv_subst, _cv_subst) -> Just $ maybe_fix tv_subst + -- We want to *succeed* in questionable cases. + -- This is a pre-unification algorithm. + SurelyApart -> Nothing + where + rn_env = mkRnEnv2 in_scope + + maybe_fix | unif = niFixSubst in_scope + | otherwise = mkTvSubst in_scope -- when matching, don't confuse + -- domain with range + +----------------- +tcUnifyTys :: BindTvFun + -> [Type] -> [Type] + -> Maybe Subst + -- ^ A regular one-shot (idempotent) substitution + -- that unifies the erased types. See comments + -- for 'tcUnifyTysFG' + +-- The two types may have common type variables, and indeed do so in the +-- second call to tcUnifyTys in GHC.Tc.Instance.FunDeps.checkClsFD +tcUnifyTys bind_fn tys1 tys2 + = case tcUnifyTysFG neverBindFam bind_fn tys1 tys2 of + Unifiable result -> Just result + _ -> Nothing + +-- | @tcUnifyTysFG bind_tv tys1 tys2@ attempts to find a substitution @s@ (whose +-- domain elements all respond 'BindMe' to @bind_tv@) such that +-- @s(tys1)@ and that of @s(tys2)@ are equal, as witnessed by the returned +-- Coercions. This version requires that the kinds of the types are the same, +-- if you unify left-to-right. +tcUnifyTysFG :: BindFamFun -> BindTvFun + -> [Type] -> [Type] + -> UnifyResult +tcUnifyTysFG bind_fam bind_tv tys1 tys2 + = tc_unify_tys_fg False bind_fam bind_tv tys1 tys2 + +tc_unify_tys_fg :: Bool + -> BindFamFun -> BindTvFun + -> [Type] -> [Type] + -> UnifyResult +tc_unify_tys_fg match_kis bind_fam bind_tv tys1 tys2 + = do { (tv_env, _) <- tc_unify_tys bind_fam bind_tv + True -- Unifying + False -- Not doing an injectivity check + match_kis -- Match outer kinds + RespectMultiplicities rn_env + emptyTvSubstEnv emptyCvSubstEnv + tys1 tys2 + ; return $ niFixSubst in_scope tv_env } + where + in_scope = mkInScopeSet $ tyCoVarsOfTypes tys1 `unionVarSet` tyCoVarsOfTypes tys2 + rn_env = mkRnEnv2 in_scope + +-- | This function is actually the one to call the unifier -- a little +-- too general for outside clients, though. +tc_unify_tys :: BindFamFun -> BindTvFun + -> AmIUnifying -- ^ True <=> unify; False <=> match + -> Bool -- ^ True <=> doing an injectivity check + -> Bool -- ^ True <=> treat the kinds as well + -> MultiplicityFlag -- ^ see Note [Rewrite rules ignore multiplicities in FunTy] in GHC.Core.Unify + -> RnEnv2 + -> TvSubstEnv -- ^ substitution to extend + -> CvSubstEnv + -> [Type] -> [Type] + -> UnifyResultM (TvSubstEnv, CvSubstEnv) +-- NB: It's tempting to ASSERT here that, if we're not matching kinds, then +-- the kinds of the types should be the same. However, this doesn't work, +-- as the types may be a dependent telescope, where later types have kinds +-- that mention variables occurring earlier in the list of types. Here's an +-- example (from typecheck/should_fail/T12709): +-- template: [rep :: RuntimeRep, a :: TYPE rep] +-- target: [LiftedRep :: RuntimeRep, Int :: TYPE LiftedRep] +-- We can see that matching the first pair will make the kinds of the second +-- pair equal. Yet, we still don't need a separate pass to unify the kinds +-- of these types, so it's appropriate to use the Ty variant of unification. +-- See also Note [tcMatchTy vs tcMatchTyKi]. +tc_unify_tys bind_fam bind_tv unif inj_check match_kis match_mults rn_env tv_env cv_env tys1 tys2 + = initUM tv_env cv_env $ + do { when match_kis $ + unify_tys env kis1 kis2 + ; unify_tys env tys1 tys2 } + where + env = UMEnv { um_bind_tv_fun = bind_tv + , um_bind_fam_fun = bind_fam + , um_foralls = emptyVarSet + , um_unif = unif + , um_inj_tf = inj_check + , um_arr_mult = match_mults + , um_rn_env = rn_env } + + kis1 = map typeKind tys1 + kis2 = map typeKind tys2 + + +{- ********************************************************************* +* * + UnifyResult, MaybeApart etc +* * +********************************************************************* -} + +{- Note [Fine-grained unification] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Do the types (x, x) and ([y], y) unify? The answer is seemingly "no" -- no substitution to finite types makes these match. But, a substitution to *infinite* types can unify these two types: [x |-> [[[...]]], y |-> [[[...]]] ]. @@ -399,6 +587,165 @@ types are apart. This has practical consequences for the ability for closed type family applications to reduce. See test case indexed-types/should_compile/Overlap14. +Note [Apartness and type families] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this: + + type family F a b where + F Int Bool = Char + F a b = Double + type family G a -- open, no instances + +How do we reduce (F (G Float) (G Float))? The first equation clearly doesn't +match immediately while the second equation does. But, before reducing, we must +make sure that the target can never become (F Int Bool). Well, no matter what G +Float becomes, it certainly won't become *both* Int and Bool, so indeed we're +safe reducing (F (G Float) (G Float)) to Double. + +So we must say that the arguments + (G Float) (G Float) is SurelyApart from Int Bool + +This is necessary not only to get more reductions (which we might be willing to +give up on), but for /substitutivity/. If we have (F x x), we can see that (F x x) +can reduce to Double. So, it had better be the case that (F blah blah) can +reduce to Double, no matter what (blah) is! + +To achieve this, `go_fam` in `uVarOrFam` does this; + +* When we attempt to unify (G Float) ~ Int, we return MaybeApart.. + but we /also/ extend a "family substitution" [G Float :-> Int], + in `um_fam_env`, alongside the regular [tyvar :-> type] substitution in + `um_tv_env`. See the `BindMe` case of `go_fam` in `uVarOrFam`. + +* When we later encounter (G Float) ~ Bool, we apply the family substitution, + very much as we apply the conventional [tyvar :-> type] substitution + when we encounter a type variable. See the `lookupFamEnv` in `go_fam` in + `uVarOrFam`. + + So (G Float ~ Bool) becomes (Int ~ Bool) which is SurelyApart. Bingo. + + +Wrinkles + +(ATF0) Once we encounter a type-family application, we only ever return + MaybeApart or SurelyApart + but never `Unifiable`. Accordingly, we only return a TyCoVar substitution + from `tcUnifyTys` and friends; we dont' return a type-family substitution as + well. (We could imagine doing so, though.) + +(ATF1) Exactly the same mechanism is used in class-instance checking. + If we have + instance C (Maybe b) + instance {-# OVERLAPPING #-} C (Maybe Bool) + [W] C (Maybe (F a)) + we want to know that the second instance might match later, when we know more about `a`. + The function `GHC.Core.InstEnv. instEnvMatchesAndUnifiers` uses `tcUnifyTysFG` to + account for type familiies in the type being matched. + +(ATF2) A very similar check is made in `GHC.Tc.Utils.Unify.mightEqualLater`, which + again uses `tcUnifyTysFG` to account for the possibility of type families. See + Note [What might equal later?]in GHC.Tc.Utils.Unify, esp example (10). + +(ATF3) What about foralls? For example, supppose we are unifying + (forall a. F a) -> (forall a. F a) + Those two (F a) types are unrelated, bound by different foralls. + + So to keep things simple, the entire family-substitution machinery is used + only if there are no enclosing foralls (see the (um_foralls env)) check in + `uSatFamApp`). That's fine, because the apartness business is used only for + reducing type-family applications, and class instances, and their arguments + can't have foralls anyway. + + The bottom line is that we won't discover that + (forall a. (a, F Int, F Int)) + is surely apart from + (forall a. (a, Int, Bool)) + but that doesn't matter. Fixing this would be possible, but would require + quite a bit of head-scratching. + +(ATF4) The family substitution only has /saturated/ family applications in + its domain. Consider the following concrete example from #16995: + + type family Param :: Type -> Type -- arity 0 + + type family LookupParam (a :: Type) :: Type where + LookupParam (f Char) = Bool + LookupParam x = Int + + foo :: LookupParam (Param ()) + foo = 42 + + In order for `foo` to typecheck, `LookupParam (Param ())` must reduce to + `Int`. So (f Char) ~ (Param ()) must be SurelyApart. Remember, since + `Param` is a nullary type family, it is over-saturated in (Param ()). + This unification will only be SurelyApart if we decompose the outer AppTy + separately, to then give (() ~ Char). + + Not only does this allow more programs to be accepted, it's also important + for correctness. Not doing this was the root cause of the Core Lint error + in #16995. + +(ATF5) Consider + instance (Generic1 f, Ord (Rep1 f a)) + => Ord (Generically1 f a) where ... + -- The "..." gives rise to [W] Ord (Generically1 f a) + We must use the instance decl (recursively) to simplify the [W] constraint; + we do /not/ want to worry that the `[G] Ord (Rep1 f a)` might be an + alternative path. So `noMatchableGivenDicts` must return False; + so `mightMatchLater` must return False; so when um_bind_fam_fun returns + `Apart`, the unifier must return `SurelyApart`, not `MaybeApart`. See + `go_fam` in `uVarOrFam` + +(ATF6) You might think that when /matching/ the um_fam_env will always be empty, + because type-class-instance and type-family-instance heads can't include type + families. E.g. instance C (F a) where ... -- Illegal + + But you'd be wrong: when "improving" type family constraint we may have a + type family on the LHS of a match. Consider + type family G6 a = r j r ! a + type instance G6 [a] = [G a] + type instance G6 Bool = Int + and the Wanted constraint [W] G6 alpha ~ [Int]. We /match/ each type instance + RHS against [Int]! So we try + [G a] ~ [Int] + and we want to succeed with MaybeApart, so that we can generate the improvement + constraint [W] alpha ~ [beta] where beta is fresh. + See Section 5.2 of "Injective type families for Haskell". + +(ATF7) You might think that (ATF6) is a very special case, and in /other/ uses of + matching, where we enter via `tc_match_tys_x` we will never see a type-family + in the template. But actually we do see that case in the specialiser: see + the call to `tcMatchTy` in `GHC.Core.Opt.Specialise.beats_or_same` + + Also: a user-written RULE could conceivably have a type-family application + in the template. It might not be a good rule, but I don't think currently + check for this. + +SIDE NOTE. The paper "Closed type families with overlapping equations" +http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/axioms-extended.pdf +tries to achieve the same effect with a standard yes/no unifier, by "flattening" +the types (replacing each type-family application with a fresh type variable) +and then unifying. But that does not work well. Consider (#25657) + + type MyEq :: k -> k -> Bool + type family MyEq a b where + MyEq a a = 'True + MyEq _ _ = 'False + + type Var :: forall {k}. Tag -> k + type family Var tag = a | a -> tag + +Then, because Var is injective, we want + MyEq (Var A) (Var B) --> False + MyEq (Var A) (Var A) --> True + +But if we flattten the types (Var A) and (Var B) we'll just get fresh type variables, +and all is lost. But with the current algorithm we have that + a a ~ (Var A) (Var B) +is SurelyApart, so the first equation definitely doesn't match and we can try the +second, which does. END OF SIDE NOTE. + + Note [Rewrite rules ignore multiplicities in FunTy] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider the following (higher-order) rule: @@ -435,70 +782,6 @@ this case, and this case only, we can safely drop the first argument (using the tail function) and unify the rest. -} --- | Simple unification of two types; all type variables are bindable --- Precondition: the kinds are already equal -tcUnifyTy :: Type -> Type -- All tyvars are bindable - -> Maybe Subst - -- A regular one-shot (idempotent) substitution -tcUnifyTy t1 t2 = tcUnifyTys alwaysBindFun [t1] [t2] - --- | Like 'tcUnifyTy', but also unifies the kinds -tcUnifyTyKi :: Type -> Type -> Maybe Subst -tcUnifyTyKi t1 t2 = tcUnifyTyKis alwaysBindFun [t1] [t2] - --- | Unify two types, treating type family applications as possibly unifying --- with anything and looking through injective type family applications. --- Precondition: kinds are the same -tcUnifyTyWithTFs :: Bool -- ^ True <=> do two-way unification; - -- False <=> do one-way matching. - -- See end of sec 5.2 from the paper - -> InScopeSet -- Should include the free tyvars of both Type args - -> Type -> Type -- Types to unify - -> Maybe Subst --- This algorithm is an implementation of the "Algorithm U" presented in --- the paper "Injective type families for Haskell", Figures 2 and 3. --- The code is incorporated with the standard unifier for convenience, but --- its operation should match the specification in the paper. -tcUnifyTyWithTFs twoWay in_scope t1 t2 - = case tc_unify_tys alwaysBindFun twoWay True False RespectMultiplicities - rn_env emptyTvSubstEnv emptyCvSubstEnv - [t1] [t2] of - Unifiable (tv_subst, _cv_subst) -> Just $ maybe_fix tv_subst - MaybeApart _reason (tv_subst, _cv_subst) -> Just $ maybe_fix tv_subst - -- we want to *succeed* in questionable cases. This is a - -- pre-unification algorithm. - SurelyApart -> Nothing - where - rn_env = mkRnEnv2 in_scope - - maybe_fix | twoWay = niFixSubst in_scope - | otherwise = mkTvSubst in_scope -- when matching, don't confuse - -- domain with range - ------------------ -tcUnifyTys :: BindFun - -> [Type] -> [Type] - -> Maybe Subst - -- ^ A regular one-shot (idempotent) substitution - -- that unifies the erased types. See comments - -- for 'tcUnifyTysFG' - --- The two types may have common type variables, and indeed do so in the --- second call to tcUnifyTys in GHC.Tc.Instance.FunDeps.checkClsFD -tcUnifyTys bind_fn tys1 tys2 - = case tcUnifyTysFG bind_fn tys1 tys2 of - Unifiable result -> Just result - _ -> Nothing - --- | Like 'tcUnifyTys' but also unifies the kinds -tcUnifyTyKis :: BindFun - -> [Type] -> [Type] - -> Maybe Subst -tcUnifyTyKis bind_fn tys1 tys2 - = case tcUnifyTyKisFG bind_fn tys1 tys2 of - Unifiable result -> Just result - _ -> Nothing - -- This type does double-duty. It is used in the UM (unifier monad) and to -- return the final result. See Note [Fine-grained unification] type UnifyResult = UnifyResultM Subst @@ -524,16 +807,21 @@ data MaybeApartReason | MARTypeVsConstraint -- ^ matching Type ~? Constraint or the arrow types -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim + | MARCast -- ^ Very obscure. + -- See (KCU2) in Note [Kind coercions in Unify] + instance Outputable MaybeApartReason where ppr MARTypeFamily = text "MARTypeFamily" ppr MARInfinite = text "MARInfinite" ppr MARTypeVsConstraint = text "MARTypeVsConstraint" + ppr MARCast = text "MARCast" instance Semigroup MaybeApartReason where - -- see end of Note [Unification result] for why - MARTypeFamily <> r = r - MARInfinite <> _ = MARInfinite + -- See end of Note [Unification result] for why + MARInfinite <> _ = MARInfinite -- MARInfinite wins + MARTypeFamily <> r = r -- Otherwise it doesn't really matter MARTypeVsConstraint <> r = r + MARCast <> r = r instance Applicative UnifyResultM where pure = Unifiable @@ -547,76 +835,6 @@ instance Monad UnifyResultM where SurelyApart -> SurelyApart Unifiable x >>= f = f x --- | @tcUnifyTysFG bind_tv tys1 tys2@ attempts to find a substitution @s@ (whose --- domain elements all respond 'BindMe' to @bind_tv@) such that --- @s(tys1)@ and that of @s(tys2)@ are equal, as witnessed by the returned --- Coercions. This version requires that the kinds of the types are the same, --- if you unify left-to-right. -tcUnifyTysFG :: BindFun - -> [Type] -> [Type] - -> UnifyResult -tcUnifyTysFG bind_fn tys1 tys2 - = tc_unify_tys_fg False bind_fn tys1 tys2 - -tcUnifyTyKisFG :: BindFun - -> [Type] -> [Type] - -> UnifyResult -tcUnifyTyKisFG bind_fn tys1 tys2 - = tc_unify_tys_fg True bind_fn tys1 tys2 - -tc_unify_tys_fg :: Bool - -> BindFun - -> [Type] -> [Type] - -> UnifyResult -tc_unify_tys_fg match_kis bind_fn tys1 tys2 - = do { (env, _) <- tc_unify_tys bind_fn True False match_kis RespectMultiplicities rn_env - emptyTvSubstEnv emptyCvSubstEnv - tys1 tys2 - ; return $ niFixSubst in_scope env } - where - in_scope = mkInScopeSet $ tyCoVarsOfTypes tys1 `unionVarSet` tyCoVarsOfTypes tys2 - rn_env = mkRnEnv2 in_scope - --- | This function is actually the one to call the unifier -- a little --- too general for outside clients, though. -tc_unify_tys :: BindFun - -> AmIUnifying -- ^ True <=> unify; False <=> match - -> Bool -- ^ True <=> doing an injectivity check - -> Bool -- ^ True <=> treat the kinds as well - -> MultiplicityFlag -- ^ see Note [Rewrite rules ignore multiplicities in FunTy] in GHC.Core.Unify - -> RnEnv2 - -> TvSubstEnv -- ^ substitution to extend - -> CvSubstEnv - -> [Type] -> [Type] - -> UnifyResultM (TvSubstEnv, CvSubstEnv) --- NB: It's tempting to ASSERT here that, if we're not matching kinds, then --- the kinds of the types should be the same. However, this doesn't work, --- as the types may be a dependent telescope, where later types have kinds --- that mention variables occurring earlier in the list of types. Here's an --- example (from typecheck/should_fail/T12709): --- template: [rep :: RuntimeRep, a :: TYPE rep] --- target: [LiftedRep :: RuntimeRep, Int :: TYPE LiftedRep] --- We can see that matching the first pair will make the kinds of the second --- pair equal. Yet, we still don't need a separate pass to unify the kinds --- of these types, so it's appropriate to use the Ty variant of unification. --- See also Note [tcMatchTy vs tcMatchTyKi]. -tc_unify_tys bind_fn unif inj_check match_kis match_mults rn_env tv_env cv_env tys1 tys2 - = initUM tv_env cv_env $ - do { when match_kis $ - unify_tys env kis1 kis2 - ; unify_tys env tys1 tys2 - ; (,) <$> getTvSubstEnv <*> getCvSubstEnv } - where - env = UMEnv { um_bind_fun = bind_fn - , um_skols = emptyVarSet - , um_unif = unif - , um_inj_tf = inj_check - , um_arr_mult = match_mults - , um_rn_env = rn_env } - - kis1 = map typeKind tys1 - kis2 = map typeKind tys2 - instance Outputable a => Outputable (UnifyResultM a) where ppr SurelyApart = text "SurelyApart" ppr (Unifiable x) = text "Unifiable" <+> ppr x @@ -743,22 +961,6 @@ niFixSubst in_scope tenv where tv' = updateTyVarKind (substTy subst) tv -niSubstTvSet :: TvSubstEnv -> TyCoVarSet -> TyCoVarSet --- Apply the non-idempotent substitution to a set of type variables, --- remembering that the substitution isn't necessarily idempotent --- This is used in the occurs check, before extending the substitution -niSubstTvSet tsubst tvs - = nonDetStrictFoldUniqSet (unionVarSet . get) emptyVarSet tvs - -- It's OK to use a non-deterministic fold here because we immediately forget - -- the ordering by creating a set. - where - get tv - | Just ty <- lookupVarEnv tsubst tv - = niSubstTvSet tsubst (tyCoVarsOfType ty) - - | otherwise - = unitVarSet tv - {- ************************************************************************ * * @@ -835,7 +1037,7 @@ but only when using this algorithm for matching: Property M1 means that we must extend the substitution with, say (a ↦ a) when appropriate during matching. - See also Note [Self-substitution when matching]. + See also Note [Self-substitution when unifying or matching]. (M2) Completeness of matching. If θ(σ) = Ï„, then (match σ Ï„) = Unifiable φ, @@ -868,26 +1070,44 @@ of [ITF].) This extra parameter is a bit fiddly, perhaps, but seemingly less so than having two separate, almost-identical algorithms. -Note [Self-substitution when matching] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -What should happen when we're *matching* (not unifying) a1 with a1? We -should get a substitution [a1 |-> a1]. A successful match should map all -the template variables (except ones that disappear when expanding synonyms). -But when unifying, we don't want to do this, because we'll then fall into -a loop. +Note [Self-substitution when unifying or matching] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +What happens when we are unifying or matching two identical type variables? + a ~ a + +* When /unifying/, just succeed, without binding [a :-> a] in the substitution, + else we'd get an infinite substitution. We need to make this check before + we do the occurs check, of course. -This arrangement affects the code in three places: - - If we're matching a refined template variable, don't recur. Instead, just - check for equality. That is, if we know [a |-> Maybe a] and are matching - (a ~? Maybe Int), we want to just fail. +* When /matching/, and `a` is a bindable variable from the template, we /do/ + want to extend the substitution. Remember, a successful match should map all + the template variables (except ones that disappear when expanding synonyms), - - Skip the occurs check when matching. This comes up in two places, because - matching against variables is handled separately from matching against - full-on types. + But when `a` is /not/ a bindable variable (perhaps it is a globally-in-scope + skolem) we want to treat it like a constant `Int ~ Int` and succeed. + + Notice: no occurs check! It's fine to match (a ~ Maybe a), because the + template vars of the template come from a different name space to the free + vars of the target. + + Note that this arrangement was provoked by a real failure, where the same + unique ended up in the template as in the target. (It was a rule firing when + compiling Data.List.NonEmpty.) + +* What about matching a /non-bindable/ variable? For example: + template-vars : {a} + matching problem: (forall b. b -> a) ~ (forall c. c -> Int) + We want to emerge with the substitution [a :-> Int] + But on the way we will encounter (b ~ b), when we match the bits before the + arrow under the forall, having renamed `c` to `b`. This match should just + succeed, just like (Int ~ Int), without extending the substitution. + + It's important to do this for /non-bindable/ variables, not just for + forall-bound ones. In an associated type + instance C (Maybe a) where { type F (Maybe a) = Int } + `checkConsistentFamInst` matches (Maybe a) from the header against (Maybe a) + from the type-family instance, with `a` marked as non-bindable. -Note that this arrangement was provoked by a real failure, where the same -unique ended up in the template as in the target. (It was a rule firing when -compiling Data.List.NonEmpty.) Note [Matching coercion variables] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -921,55 +1141,84 @@ just match/unify their kinds, either, because this might gratuitously fail. After all, `co` is the witness that the kinds are the same -- they may look nothing alike. -So, we pass a kind coercion to the match/unify worker. This coercion witnesses +So, we pass a kind coercion `kco` to the main `unify_ty`. This coercion witnesses the equality between the substed kind of the left-hand type and the substed kind of the right-hand type. Note that we do not unify kinds at the leaves -(as we did previously). We thus have +(as we did previously). -Hence: (Unification Kind Invariant) ------------------------------------ -In the call +Hence: (UKINV) Unification Kind Invariant +* In the call unify_ty ty1 ty2 kco -it must be that + it must be that subst(kco) :: subst(kind(ty1)) ~N subst(kind(ty2)) -where `subst` is the ambient substitution in the UM monad. And in the call + where `subst` is the ambient substitution in the UM monad +* In the call unify_tys tys1 tys2 -(which has no kco), after we unify any prefix of tys1,tys2, the kinds of the -head of the remaining tys1,tys2 are identical after substitution. This -implies, for example, that the kinds of the head of tys1,tys2 are identical -after substitution. - -To get this coercion, we first have to match/unify -the kinds before looking at the types. Happily, we need look only one level -up, as all kinds are guaranteed to have kind *. - -When we're working with type applications (either TyConApp or AppTy) we -need to worry about establishing INVARIANT, as the kinds of the function -& arguments aren't (necessarily) included in the kind of the result. -When unifying two TyConApps, this is easy, because the two TyCons are -the same. Their kinds are thus the same. As long as we unify left-to-right, -we'll be sure to unify types' kinds before the types themselves. (For example, -think about Proxy :: forall k. k -> *. Unifying the first args matches up -the kinds of the second args.) - -For AppTy, we must unify the kinds of the functions, but once these are -unified, we can continue unifying arguments without worrying further about -kinds. - -The interface to this module includes both "...Ty" functions and -"...TyKi" functions. The former assume that INVARIANT is already -established, either because the kinds are the same or because the -list of types being passed in are the well-typed arguments to some -type constructor (see two paragraphs above). The latter take a separate -pre-pass over the kinds to establish INVARIANT. Sometimes, it's important -not to take the second pass, as it caused #12442. - -We thought, at one point, that this was all unnecessary: why should -casts be in types in the first place? But they are sometimes. In -dependent/should_compile/KindEqualities2, we see, for example the -constraint Num (Int |> (blah ; sym blah)). We naturally want to find -a dictionary for that constraint, which requires dealing with -coercions in this manner. + (which has no kco), after we unify any prefix of tys1,tys2, the kinds of the + head of the remaining tys1,tys2 are identical after substitution. This + implies, for example, that the kinds of the head of tys1,tys2 are identical + after substitution. + +Preserving (UKINV) takes a bit of work, governed by the `match_kis` flag in +`tc_unify_tys`: + +* When we're working with type applications (either TyConApp or AppTy) we + need to worry about establishing INVARIANT, as the kinds of the function + & arguments aren't (necessarily) included in the kind of the result. + When unifying two TyConApps, this is easy, because the two TyCons are + the same. Their kinds are thus the same. As long as we unify left-to-right, + we'll be sure to unify types' kinds before the types themselves. (For example, + think about Proxy :: forall k. k -> *. Unifying the first args matches up + the kinds of the second args.) + +* For AppTy, we must unify the kinds of the functions, but once these are + unified, we can continue unifying arguments without worrying further about + kinds. + +* The interface to this module includes both "...Ty" functions and + "...TyKi" functions. The former assume that INVARIANT is already + established, either because the kinds are the same or because the + list of types being passed in are the well-typed arguments to some + type constructor (see two paragraphs above). The latter take a separate + pre-pass over the kinds to establish INVARIANT. Sometimes, it's important + not to take the second pass, as it caused #12442. + +Wrinkles + +(KCU1) We ensure that the `kco` argument never mentions variables in the + domain of either RnEnvL or RnEnvR. Why? + + * `kco` is used only to build the final well-kinded substitution + a :-> ty |> kco + The range of the substitution never mentions forall-bound variables, + so `kco` cannot either. + + * `kco` mixes up types from both left and right arguments of + `unify_ty`, which have different renamings in the RnEnv2. + + The easiest thing is to insist that `kco` does not need renaming with + the RnEnv2; it mentions no forall-bound variables. + + To achieve this we do a `mentionsForAllBoundTyVars` test in the + `CastTy` cases of `unify_ty`. + +(KCU2) Suppose we are unifying + (forall a. x |> (...F a b...) ~ (forall a. y) + We can't bind y :-> x |> (...F a b...), becuase of that free `a`. + + But if we later learn that b=Int, and F a Int = Bool, + that free `a` might disappear, so we could unify with + y :-> x |> (...Bool...) + + Conclusion: if there is a free forall-bound variable in a cast, + return MaybeApart, with a MaybeApartReason of MARCast. + +(KCU3) We thought, at one point, that this was all unnecessary: why should + casts be in types in the first place? But they are sometimes. In + dependent/should_compile/KindEqualities2, we see, for example the + constraint Num (Int |> (blah ; sym blah)). We naturally want to find + a dictionary for that constraint, which requires dealing with + coercions in this manner. Note [Matching in the presence of casts (1)] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1137,10 +1386,17 @@ c.f. Note [Comparing type synonyms] in GHC.Core.TyCo.Compare type AmIUnifying = Bool -- True <=> Unifying -- False <=> Matching +type InType = Type -- Before applying the RnEnv2 +type OutCoercion = Coercion -- After applying the RnEnv2 + + unify_ty :: UMEnv - -> Type -> Type -- Types to be unified and a co - -> CoercionN -- A coercion between their kinds - -- See Note [Kind coercions in Unify] + -> InType -> InType -- Types to be unified + -> OutCoercion -- A nominal coercion between their kinds + -- OutCoercion: the RnEnv has already been applied + -- When matching, the coercion is in "target space", + -- not "template space" + -- See Note [Kind coercions in Unify] -> UM () -- Precondition: see (Unification Kind Invariant) -- @@ -1156,29 +1412,86 @@ unify_ty env ty1 ty2 kco -- Now handle the cases we can "look through": synonyms and casts. | Just ty1' <- coreView ty1 = unify_ty env ty1' ty2 kco | Just ty2' <- coreView ty2 = unify_ty env ty1 ty2' kco - | CastTy ty1' co <- ty1 = if um_unif env - then unify_ty env ty1' ty2 (co `mkTransCo` kco) - else -- See Note [Matching in the presence of casts (1)] - do { subst <- getSubst env - ; let co' = substCo subst co - ; unify_ty env ty1' ty2 (co' `mkTransCo` kco) } - | CastTy ty2' co <- ty2 = unify_ty env ty1 ty2' (kco `mkTransCo` mkSymCo co) + +unify_ty env (CastTy ty1 co1) ty2 kco + | mentionsForAllBoundTyVarsL env (tyCoVarsOfCo co1) + -- See (KCU1) in Note [Kind coercions in Unify] + = maybeApart MARCast -- See (KCU2) + + | um_unif env + = unify_ty env ty1 ty2 (co1 `mkTransCo` kco) + + | otherwise -- We are matching, not unifying + = do { subst <- getSubst env + ; let co' = substCo subst co1 + -- We match left-to-right, so the free template vars of the + -- coercion should already have been matched. + -- See Note [Matching in the presence of casts (1)] + ; unify_ty env ty1 ty2 (co' `mkTransCo` kco) } + +unify_ty env ty1 (CastTy ty2 co2) kco + | mentionsForAllBoundTyVarsR env (tyCoVarsOfCo co2) + -- See (KCU1) in Note [Kind coercions in Unify] + = maybeApart MARCast -- See (KCU2) + | otherwise + = unify_ty env ty1 ty2 (kco `mkTransCo` mkSymCo co2) + -- ToDo: what if co2 mentions forall-bound variables? + +-- Applications need a bit of care! +-- They can match FunTy and TyConApp, so use splitAppTy_maybe +unify_ty env (AppTy ty1a ty1b) ty2 _kco + | Just (ty2a, ty2b) <- tcSplitAppTyNoView_maybe ty2 + = unify_ty_app env ty1a [ty1b] ty2a [ty2b] + +unify_ty env ty1 (AppTy ty2a ty2b) _kco + | Just (ty1a, ty1b) <- tcSplitAppTyNoView_maybe ty1 + = unify_ty_app env ty1a [ty1b] ty2a [ty2b] + +unify_ty _ (LitTy x) (LitTy y) _kco | x == y = return () + +unify_ty env (ForAllTy (Bndr tv1 _) ty1) (ForAllTy (Bndr tv2 _) ty2) kco + = do { unify_ty env (varType tv1) (varType tv2) (mkNomReflCo liftedTypeKind) + ; let env' = umRnBndr2 env tv1 tv2 + ; unify_ty env' ty1 ty2 kco } + +-- See Note [Matching coercion variables] +unify_ty env (CoercionTy co1) (CoercionTy co2) kco + = do { c_subst <- getCvSubstEnv + ; case co1 of + CoVarCo cv + | not (um_unif env) + , not (cv `elemVarEnv` c_subst) -- Not forall-bound + , let (_mult_co, co_l, co_r) = decomposeFunCo kco + -- Because the coercion is used in a type, it should be safe to + -- ignore the multiplicity coercion, _mult_co + -- cv :: t1 ~ t2 + -- co2 :: s1 ~ s2 + -- co_l :: t1 ~ s1 + -- co_r :: t2 ~ s2 + rhs_co = co_l `mkTransCo` co2 `mkTransCo` mkSymCo co_r + , BindMe <- um_bind_tv_fun env cv (CoercionTy rhs_co) + -> if mentionsForAllBoundTyVarsR env (tyCoVarsOfCo co2) + then surelyApart + else extendCvEnv cv rhs_co + + _ -> return () } unify_ty env (TyVarTy tv1) ty2 kco - = uVar env tv1 ty2 kco -unify_ty env ty1 (TyVarTy tv2) kco - | um_unif env -- If unifying, can swap args - = uVar (umSwapRn env) tv2 ty1 (mkSymCo kco) + = uVarOrFam env (TyVarLHS tv1) ty2 kco -unify_ty env ty1 ty2 _kco +unify_ty env ty1 (TyVarTy tv2) kco + | um_unif env -- If unifying, can swap args; but not when matching + = uVarOrFam (umSwapRn env) (TyVarLHS tv2) ty1 (mkSymCo kco) +-- Deal with TyConApps +unify_ty env ty1 ty2 kco -- Handle non-oversaturated type families first -- See Note [Unifying type applications] -- -- (C1) If we have T x1 ... xn ~ T y1 ... yn, use injectivity information of T -- Note that both sides must not be oversaturated - | Just (tc1, tys1) <- isSatTyFamApp mb_tc_app1 - , Just (tc2, tys2) <- isSatTyFamApp mb_tc_app2 + | Just (tc1, tys1) <- mb_sat_fam_app1 + , Just (tc2, tys2) <- mb_sat_fam_app2 , tc1 == tc2 = do { let inj = case tyConInjectivityInfo tc1 of NotInjective -> repeat False @@ -1191,18 +1504,16 @@ unify_ty env ty1 ty2 _kco ; unless (um_inj_tf env) $ -- See (end of) Note [Specification of unification] don'tBeSoSure MARTypeFamily $ unify_tys env noninj_tys1 noninj_tys2 } - | Just _ <- isSatTyFamApp mb_tc_app1 -- (C2) A (not-over-saturated) type-family application - = maybeApart MARTypeFamily -- behaves like a type variable; might match + | Just (tc,tys) <- mb_sat_fam_app1 + = uVarOrFam env (TyFamLHS tc tys) ty2 kco - | Just _ <- isSatTyFamApp mb_tc_app2 -- (C2) A (not-over-saturated) type-family application - -- behaves like a type variable; might unify - -- but doesn't match (as in the TyVarTy case) - = if um_unif env then maybeApart MARTypeFamily else surelyApart + | um_unif env + , Just (tc,tys) <- mb_sat_fam_app2 + = uVarOrFam (umSwapRn env) (TyFamLHS tc tys) ty1 (mkSymCo kco) - -- Handle oversaturated type families. - -- - -- They can match an application (TyConApp/FunTy/AppTy), this is handled - -- the same way as in the AppTy case below. + -- Handle oversaturated type families. Suppose we have + -- (F a b) ~ (c d) where F has arity 1 + -- We definitely want to decompose that type application! (#22647) -- -- If there is no application, an oversaturated type family can only -- match a type variable or a saturated type family, @@ -1226,7 +1537,7 @@ unify_ty env ty1 ty2 _kco , Just (tc2, tys2) <- mb_tc_app2 , tc1 == tc2 = do { massertPpr (isInjectiveTyCon tc1 Nominal) (ppr tc1) - ; unify_tc_app tc1 tys1 tys2 + ; unify_tc_app env tc1 tys1 tys2 } -- TYPE and CONSTRAINT are not Apart @@ -1256,64 +1567,34 @@ unify_ty env ty1 ty2 _kco where mb_tc_app1 = splitTyConApp_maybe ty1 mb_tc_app2 = splitTyConApp_maybe ty2 + mb_sat_fam_app1 = isSatFamApp ty1 + mb_sat_fam_app2 = isSatFamApp ty2 - unify_tc_app tc tys1 tys2 - | tc == fUNTyCon - , IgnoreMultiplicities <- um_arr_mult env - , (_mult1 : no_mult_tys1) <- tys1 - , (_mult2 : no_mult_tys2) <- tys2 - = -- We're comparing function arrow types here (not constraint arrow - -- types!), and they have at least one argument, which is the arrow's - -- multiplicity annotation. The flag `um_arr_mult` instructs us to - -- ignore multiplicities in this very case. This is a little tricky: see - -- point (3) in Note [Rewrite rules ignore multiplicities in FunTy]. - unify_tys env no_mult_tys1 no_mult_tys2 - - | otherwise - = unify_tys env tys1 tys2 - - -- Applications need a bit of care! - -- They can match FunTy and TyConApp, so use splitAppTy_maybe - -- NB: we've already dealt with type variables, - -- so if one type is an App the other one jolly well better be too -unify_ty env (AppTy ty1a ty1b) ty2 _kco - | Just (ty2a, ty2b) <- tcSplitAppTyNoView_maybe ty2 - = unify_ty_app env ty1a [ty1b] ty2a [ty2b] - -unify_ty env ty1 (AppTy ty2a ty2b) _kco - | Just (ty1a, ty1b) <- tcSplitAppTyNoView_maybe ty1 - = unify_ty_app env ty1a [ty1b] ty2a [ty2b] - -unify_ty _ (LitTy x) (LitTy y) _kco | x == y = return () - -unify_ty env (ForAllTy (Bndr tv1 _) ty1) (ForAllTy (Bndr tv2 _) ty2) kco - = do { unify_ty env (varType tv1) (varType tv2) (mkNomReflCo liftedTypeKind) - ; let env' = umRnBndr2 env tv1 tv2 - ; unify_ty env' ty1 ty2 kco } +unify_ty _ _ _ _ = surelyApart --- See Note [Matching coercion variables] -unify_ty env (CoercionTy co1) (CoercionTy co2) kco - = do { c_subst <- getCvSubstEnv - ; case co1 of - CoVarCo cv - | not (um_unif env) - , not (cv `elemVarEnv` c_subst) - , let (_, co_l, co_r) = decomposeFunCo kco - -- Because the coercion is used in a type, it should be safe to - -- ignore the multiplicity coercion. - -- cv :: t1 ~ t2 - -- co2 :: s1 ~ s2 - -- co_l :: t1 ~ s1 - -- co_r :: t2 ~ s2 - rhs_co = co_l `mkTransCo` co2 `mkTransCo` mkSymCo co_r - , BindMe <- tvBindFlag env cv (CoercionTy rhs_co) - -> do { checkRnEnv env (tyCoVarsOfCo co2) - ; extendCvEnv cv rhs_co } - _ -> return () } +----------------------------- +unify_tc_app :: UMEnv -> TyCon -> [Type] -> [Type] -> UM () +-- Mainly just unifies the argument types; +-- but with a special case for fUNTyCon +unify_tc_app env tc tys1 tys2 + | tc == fUNTyCon + , IgnoreMultiplicities <- um_arr_mult env + , (_mult1 : no_mult_tys1) <- tys1 + , (_mult2 : no_mult_tys2) <- tys2 + = -- We're comparing function arrow types here (not constraint arrow + -- types!), and they have at least one argument, which is the arrow's + -- multiplicity annotation. The flag `um_arr_mult` instructs us to + -- ignore multiplicities in this very case. This is a little tricky: see + -- point (3) in Note [Rewrite rules ignore multiplicities in FunTy]. + unify_tys env no_mult_tys1 no_mult_tys2 -unify_ty _ _ _ _ = surelyApart + | otherwise + = unify_tys env tys1 tys2 +----------------------------- unify_ty_app :: UMEnv -> Type -> [Type] -> Type -> [Type] -> UM () +-- Deal with (t1 t1args) ~ (t2 t2args) +-- where length t1args = length t2args unify_ty_app env ty1 ty1args ty2 ty2args | Just (ty1', ty1a) <- splitAppTyNoView_maybe ty1 , Just (ty2', ty2a) <- splitAppTyNoView_maybe ty2 @@ -1329,6 +1610,7 @@ unify_ty_app env ty1 ty1args ty2 ty2args -- See Note [Matching in the presence of casts (2)] ; unify_tys env ty1args ty2args } +----------------------------- unify_tys :: UMEnv -> [Type] -> [Type] -> UM () -- Precondition: see (Unification Kind Invariant) unify_tys env orig_xs orig_ys @@ -1345,132 +1627,160 @@ unify_tys env orig_xs orig_ys -- Possibly different saturations of a polykinded tycon -- See Note [Polykinded tycon applications] -isSatTyFamApp :: Maybe (TyCon, [Type]) -> Maybe (TyCon, [Type]) +--------------------------------- +isSatFamApp :: Type -> Maybe (TyCon, [Type]) -- Return the argument if we have a saturated type family application --- If it is /over/ saturated then we return False. E.g. --- unify_ty (F a b) (c d) where F has arity 1 --- we definitely want to decompose that type application! (#22647) -isSatTyFamApp tapp@(Just (tc, tys)) +-- Why saturated? See (ATF4) in Note [Apartness and type families] +isSatFamApp (TyConApp tc tys) | isTypeFamilyTyCon tc && not (tys `lengthExceeds` tyConArity tc) -- Not over-saturated - = tapp -isSatTyFamApp _ = Nothing + = Just (tc, tys) +isSatFamApp _ = Nothing --------------------------------- -uVar :: UMEnv - -> InTyVar -- Variable to be unified - -> Type -- with this Type - -> Coercion -- :: kind tv ~N kind ty - -> UM () - -uVar env tv1 ty kco - = do { -- Apply the ambient renaming - let tv1' = umRnOccL env tv1 - - -- Check to see whether tv1 is refined by the substitution - ; subst <- getTvSubstEnv - ; case (lookupVarEnv subst tv1') of - Just ty' | um_unif env -- Unifying, so call - -> unify_ty env ty' ty kco -- back into unify - | otherwise - -> -- Matching, we don't want to just recur here. - -- this is because the range of the subst is the target - -- type, not the template type. So, just check for - -- normal type equality. - unless ((ty' `mkCastTy` kco) `tcEqType` ty) $ - surelyApart - -- NB: it's important to use `tcEqType` instead of `eqType` here, - -- otherwise we might not reject a substitution - -- which unifies `Type` with `Constraint`, e.g. - -- a call to tc_unify_tys with arguments - -- - -- tys1 = [k,k] - -- tys2 = [Type, Constraint] - -- - -- See test cases: T11715b, T20521. - Nothing -> uUnrefined env tv1' ty ty kco } -- No, continue - -uUnrefined :: UMEnv - -> OutTyVar -- variable to be unified - -> Type -- with this Type - -> Type -- (version w/ expanded synonyms) - -> Coercion -- :: kind tv ~N kind ty - -> UM () - --- We know that tv1 isn't refined - -uUnrefined env tv1' ty2 ty2' kco - | Just ty2'' <- coreView ty2' - = uUnrefined env tv1' ty2 ty2'' kco -- Unwrap synonyms - -- This is essential, in case we have - -- type Foo a = a - -- and then unify a ~ Foo a - - | TyVarTy tv2 <- ty2' - = do { let tv2' = umRnOccR env tv2 - ; unless (tv1' == tv2' && um_unif env) $ do - -- If we are unifying a ~ a, just return immediately - -- Do not extend the substitution - -- See Note [Self-substitution when matching] - - -- Check to see whether tv2 is refined - { subst <- getTvSubstEnv - ; case lookupVarEnv subst tv2 of - { Just ty' | um_unif env -> uUnrefined env tv1' ty' ty' kco - ; _ -> - - do { -- So both are unrefined - -- Bind one or the other, depending on which is bindable - ; let rhs1 = ty2 `mkCastTy` mkSymCo kco - rhs2 = ty1 `mkCastTy` kco - b1 = tvBindFlag env tv1' rhs1 - b2 = tvBindFlag env tv2' rhs2 - ty1 = mkTyVarTy tv1' - ; case (b1, b2) of - (BindMe, _) -> bindTv env tv1' rhs1 - (_, BindMe) | um_unif env - -> bindTv (umSwapRn env) tv2 rhs2 - - _ | tv1' == tv2' -> return () - -- How could this happen? If we're only matching and if - -- we're comparing forall-bound variables. - - _ -> surelyApart - }}}} - -uUnrefined env tv1' ty2 _ kco -- ty2 is not a type variable - = case tvBindFlag env tv1' rhs of - Apart -> surelyApart - BindMe -> bindTv env tv1' rhs +uVarOrFam :: UMEnv -> CanEqLHS -> InType -> OutCoercion -> UM () +-- Invariants: (a) If ty1 is a TyFamLHS, then ty2 is NOT a TyVarTy +-- (b) both args have had coreView already applied +-- Why saturated? See (ATF4) in Note [Apartness and type families] +uVarOrFam env ty1 ty2 kco + = do { substs <- getSubstEnvs + ; go NotSwapped substs ty1 ty2 kco } where - rhs = ty2 `mkCastTy` mkSymCo kco - -bindTv :: UMEnv -> OutTyVar -> Type -> UM () --- OK, so we want to extend the substitution with tv := ty --- But first, we must do a couple of checks -bindTv env tv1 ty2 - = do { let free_tvs2 = tyCoVarsOfType ty2 - - -- Make sure tys mentions no local variables - -- E.g. (forall a. b) ~ (forall a. [a]) - -- We should not unify b := [a]! - ; checkRnEnv env free_tvs2 - - -- Occurs check, see Note [Fine-grained unification] - -- Make sure you include 'kco' (which ty2 does) #14846 - ; occurs <- occursCheck env tv1 free_tvs2 - - ; if occurs then maybeApart MARInfinite - else extendTvEnv tv1 ty2 } - -occursCheck :: UMEnv -> TyVar -> VarSet -> UM Bool -occursCheck env tv free_tvs - | um_unif env - = do { tsubst <- getTvSubstEnv - ; return (tv `elemVarSet` niSubstTvSet tsubst free_tvs) } - - | otherwise -- Matching; no occurs check - = return False -- See Note [Self-substitution when matching] + -- `go` takes two bites at the cherry; if the first one fails + -- it swaps the arguments and tries again; and then it fails. + -- The SwapFlag argument tells `go` whether it is on the first + -- bite (NotSwapped) or the second (IsSwapped). + -- E.g. a ~ F p q + -- Starts with: go a (F p q) + -- if `a` not bindable, swap to: go (F p q) a + go swapped substs (TyVarLHS tv1) ty2 kco + = go_tv swapped substs tv1 ty2 kco + + go swapped substs (TyFamLHS tc tys) ty2 kco + = go_fam swapped substs tc tys ty2 kco + + ----------------------------- + -- go_tv: LHS is a type variable + -- The sequence of tests is very similar to go_tv + go_tv swapped substs tv1 ty2 kco + | Just ty1' <- lookupVarEnv (um_tv_env substs) tv1' + = -- We already have a substitution for tv1 + if | um_unif env -> unify_ty env ty1' ty2 kco + | (ty1' `mkCastTy` kco) `tcEqType` ty2 -> return () + | otherwise -> surelyApart + -- Unifying: recurse into unify_ty + -- Matching: we /don't/ want to just recurse here, because the range of + -- the subst is the target type, not the template type. So, just check + -- for normal type equality. + -- NB: it's important to use `tcEqType` instead of `eqType` here, + -- otherwise we might not reject a substitution + -- which unifies `Type` with `Constraint`, e.g. + -- a call to tc_unify_tys with arguments + -- + -- tys1 = [k,k] + -- tys2 = [Type, Constraint] + -- + -- See test cases: T11715b, T20521. + + -- If we are matching or unifying a ~ a, take care + -- See Note [Self-substitution when unifying or matching] + | TyVarTy tv2 <- ty2 + , let tv2' = umRnOccR env tv2 + , tv1' == tv2' + = if | um_unif env -> return () + | tv1_is_bindable -> extendTvEnv tv1' ty2 + | otherwise -> return () + + | tv1_is_bindable + , not (mentionsForAllBoundTyVarsR env ty2_fvs) + -- ty2_fvs: kco does not mention forall-bound vars + , not occurs_check + = -- No occurs check, nor skolem-escape; just bind the tv + -- We don't need to rename `rhs` because it mentions no forall-bound vars + extendTvEnv tv1' rhs -- Bind tv1:=rhs and continue + + -- When unifying, try swapping: + -- e.g. a ~ F p q with `a` not bindable: we might succeed with go_fam + -- e.g. a ~ beta with `a` not bindable: we might be able to bind `beta` + -- e.g. beta ~ F beta Int occurs check; but MaybeApart after swapping + | um_unif env + , NotSwapped <- swapped -- If we have swapped already, don't do so again + , Just lhs2 <- canEqLHS_maybe ty2 + = go IsSwapped substs lhs2 (mkTyVarTy tv1) (mkSymCo kco) + + | occurs_check = maybeApart MARInfinite -- Occurs check + | otherwise = surelyApart + + where + tv1' = umRnOccL env tv1 + ty2_fvs = tyCoVarsOfType ty2 + rhs_fvs = ty2_fvs `unionVarSet` tyCoVarsOfCo kco + rhs = ty2 `mkCastTy` mkSymCo kco + tv1_is_bindable | not (tv1' `elemVarSet` um_foralls env) + -- tv1' is not forall-bound, but tv1 can still differ + -- from tv1; see Note [Cloning the template binders] + -- in GHC.Core.Rules. So give tv1' to um_bind_tv_fun. + , BindMe <- um_bind_tv_fun env tv1' rhs + = True + | otherwise + = False + + occurs_check = um_unif env && + occursCheck (um_tv_env substs) tv1 rhs_fvs + -- Occurs check, only when unifying + -- see Note [Fine-grained unification] + -- Make sure you include `kco` in rhs_tvs #14846 + + ----------------------------- + -- go_fam: LHS is a saturated type-family application + -- Invariant: ty2 is not a TyVarTy + go_fam swapped substs tc1 tys1 ty2 kco + -- If we are under a forall, just give up and return MaybeApart + -- see (ATF3) in Note [Apartness and type families] + | not (isEmptyVarSet (um_foralls env)) + = maybeApart MARTypeFamily + + -- We are not under any foralls, so the RnEnv2 is empty + | Just ty1' <- lookupFamEnv (um_fam_env substs) tc1 tys1 + = if | um_unif env -> unify_ty env ty1' ty2 kco + | (ty1' `mkCastTy` kco) `tcEqType` ty2 -> maybeApart MARTypeFamily + | otherwise -> surelyApart + + -- Check for equality F tys ~ F tys + -- otherwise we'd build an infinite substitution + | TyConApp tc2 tys2 <- ty2 + , tcEqTyConApps tc1 tys1 tc2 tys2 + = return () + + -- Now check if we can bind the (F tys) to the RHS + | BindMe <- um_bind_fam_fun env tc1 tys1 rhs + = -- ToDo: do we need an occurs check here? + do { extendFamEnv tc1 tys1 rhs + ; maybeApart MARTypeFamily } + + -- Swap in case of (F a b) ~ (G c d e) + -- Maybe um_bind_fam_fun is False of (F a b) but true of (G c d e) + -- NB: a type family can appear on the template when matching + -- see (ATF6) in Note [Apartness and type families] + | um_unif env + , NotSwapped <- swapped + , Just lhs2 <- canEqLHS_maybe ty2 + = go IsSwapped substs lhs2 (mkTyConApp tc1 tys1) (mkSymCo kco) + + | otherwise -- See (ATF4) in Note [Apartness and type families] + = surelyApart + + where + rhs = ty2 `mkCastTy` mkSymCo kco + +occursCheck :: TvSubstEnv -> TyVar -> TyCoVarSet -> Bool +occursCheck env tv1 tvs + = anyVarSet bad tvs + where + bad tv | Just ty <- lookupVarEnv env tv + = anyVarSet bad (tyCoVarsOfType ty) + | otherwise + = tv == tv1 {- %************************************************************************ @@ -1486,7 +1796,7 @@ data BindFlag | Apart -- ^ Declare that this type variable is /apart/ from the -- type provided. That is, the type variable will never -- be instantiated to that type. - -- See also Note [Binding when looking up instances] + -- See also Note [Super skolems: binding when looking up instances] -- in GHC.Core.InstEnv. deriving Eq -- NB: It would be conceivable to have an analogue to MaybeApart here, @@ -1516,19 +1826,39 @@ data UMEnv -- shadowing, and lines up matching foralls on the left -- and right - , um_skols :: TyVarSet + , um_foralls :: TyVarSet -- OutTyVars bound by a forall in this unification; -- Do not bind these in the substitution! -- See the function tvBindFlag - , um_bind_fun :: BindFun + , um_bind_tv_fun :: BindTvFun -- User-supplied BindFlag function, - -- for variables not in um_skols + -- for variables not in um_foralls + + , um_bind_fam_fun :: BindFamFun + -- Similar to um_bind_tv_fun, but for type-family applications } +type FamSubstEnv = TyConEnv (ListMap TypeMap Type) + -- Map a TyCon and a list of types to a type + -- Domain of FamSubstEnv is exactly-saturated type-family + -- applications (F t1...tn) + +lookupFamEnv :: FamSubstEnv -> TyCon -> [Type] -> Maybe Type +lookupFamEnv env tc tys + = do { tys_map <- lookupTyConEnv env tc + ; lookupTM tys tys_map } + data UMState = UMState { um_tv_env :: TvSubstEnv - , um_cv_env :: CvSubstEnv } + , um_cv_env :: CvSubstEnv + , um_fam_env :: FamSubstEnv } + -- um_tv_env, um_cv_env, um_fam_env are all "global" substitutions; + -- that is, neither their domains nor their ranges mention any variables + -- in um_foralls; i.e. variables bound by foralls inside the types being unified + + -- When /matching/ um_fam_env is usually empty; but not quite always. + -- See (ATF6) and (ATF7) of Note [Apartness and type families] newtype UM a = UM' { unUM :: UMState -> UnifyResultM (UMState, a) } @@ -1560,20 +1890,18 @@ instance MonadFail UM where initUM :: TvSubstEnv -- subst to extend -> CvSubstEnv - -> UM a -> UnifyResultM a + -> UM () + -> UnifyResultM (TvSubstEnv, CvSubstEnv) initUM subst_env cv_subst_env um = case unUM um state of - Unifiable (_, subst) -> Unifiable subst - MaybeApart r (_, subst) -> MaybeApart r subst + Unifiable (state, _) -> Unifiable (get state) + MaybeApart r (state, _) -> MaybeApart r (get state) SurelyApart -> SurelyApart where state = UMState { um_tv_env = subst_env - , um_cv_env = cv_subst_env } - -tvBindFlag :: UMEnv -> OutTyVar -> Type -> BindFlag -tvBindFlag env tv rhs - | tv `elemVarSet` um_skols env = Apart - | otherwise = um_bind_fun env tv rhs + , um_cv_env = cv_subst_env + , um_fam_env = emptyTyConEnv } + get (UMState { um_tv_env = tv_env, um_cv_env = cv_env }) = (tv_env, cv_env) getTvSubstEnv :: UM TvSubstEnv getTvSubstEnv = UM $ \state -> Unifiable (state, um_tv_env state) @@ -1581,6 +1909,9 @@ getTvSubstEnv = UM $ \state -> Unifiable (state, um_tv_env state) getCvSubstEnv :: UM CvSubstEnv getCvSubstEnv = UM $ \state -> Unifiable (state, um_cv_env state) +getSubstEnvs :: UM UMState +getSubstEnvs = UM $ \state -> Unifiable (state, state) + getSubst :: UMEnv -> UM Subst getSubst env = do { tv_env <- getTvSubstEnv ; cv_env <- getCvSubstEnv @@ -1595,19 +1926,31 @@ extendCvEnv :: CoVar -> Coercion -> UM () extendCvEnv cv co = UM $ \state -> Unifiable (state { um_cv_env = extendVarEnv (um_cv_env state) cv co }, ()) +extendFamEnv :: TyCon -> [Type] -> Type -> UM () +extendFamEnv tc tys ty = UM $ \state -> + Unifiable (state { um_fam_env = extend (um_fam_env state) tc }, ()) + where + extend :: FamSubstEnv -> TyCon -> FamSubstEnv + extend = alterTyConEnv alter_tm + + alter_tm :: Maybe (ListMap TypeMap Type) -> Maybe (ListMap TypeMap Type) + alter_tm m_elt = Just (alterTM tys (\_ -> Just ty) (m_elt `orElse` emptyTM)) + umRnBndr2 :: UMEnv -> TyCoVar -> TyCoVar -> UMEnv umRnBndr2 env v1 v2 - = env { um_rn_env = rn_env', um_skols = um_skols env `extendVarSet` v' } + = env { um_rn_env = rn_env', um_foralls = um_foralls env `extendVarSet` v' } where (rn_env', v') = rnBndr2_var (um_rn_env env) v1 v2 -checkRnEnv :: UMEnv -> VarSet -> UM () -checkRnEnv env varset - | isEmptyVarSet skol_vars = return () - | varset `disjointVarSet` skol_vars = return () - | otherwise = surelyApart - where - skol_vars = um_skols env +mentionsForAllBoundTyVarsL, mentionsForAllBoundTyVarsR :: UMEnv -> VarSet -> Bool +mentionsForAllBoundTyVarsL = mentions_forall_bound_tvs inRnEnvL +mentionsForAllBoundTyVarsR = mentions_forall_bound_tvs inRnEnvR + +mentions_forall_bound_tvs :: (RnEnv2 -> TyVar -> Bool) -> UMEnv -> VarSet -> Bool +mentions_forall_bound_tvs in_rn_env env varset + | isEmptyVarSet (um_foralls env) = False + | anyVarSet (in_rn_env (um_rn_env env)) varset = True + | otherwise = False -- NB: That isEmptyVarSet guard is a critical optimization; -- it means we don't have to calculate the free vars of -- the type, often saving quite a bit of allocation. @@ -1890,325 +2233,3 @@ pushRefl co = , fco_kind = mkNomReflCo (varType tv) , fco_body = mkReflCo r ty }) _ -> Nothing - -{- -************************************************************************ -* * - Flattening -* * -************************************************************************ - -Note [Flattening type-family applications when matching instances] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -As described in "Closed type families with overlapping equations" -http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/axioms-extended.pdf -we need to flatten core types before unifying them, when checking for "surely-apart" -against earlier equations of a closed type family. -Flattening means replacing all top-level uses of type functions with -fresh variables, *taking care to preserve sharing*. That is, the type -(Either (F a b) (F a b)) should flatten to (Either c c), never (Either -c d). - -Here is a nice example of why it's all necessary: - - type family F a b where - F Int Bool = Char - F a b = Double - type family G a -- open, no instances - -How do we reduce (F (G Float) (G Float))? The first equation clearly doesn't match, -while the second equation does. But, before reducing, we must make sure that the -target can never become (F Int Bool). Well, no matter what G Float becomes, it -certainly won't become *both* Int and Bool, so indeed we're safe reducing -(F (G Float) (G Float)) to Double. - -This is necessary not only to get more reductions (which we might be -willing to give up on), but for substitutivity. If we have (F x x), we -can see that (F x x) can reduce to Double. So, it had better be the -case that (F blah blah) can reduce to Double, no matter what (blah) -is! Flattening as done below ensures this. - -We also use this flattening operation to check for class instances. -If we have - instance C (Maybe b) - instance {-# OVERLAPPING #-} C (Maybe Bool) - [W] C (Maybe (F a)) -we want to know that the second instance might match later. So we -flatten the (F a) in the target before trying to unify with instances. -(This is done in GHC.Core.InstEnv.lookupInstEnv'.) - -The algorithm works by building up a TypeMap TyVar, mapping -type family applications to fresh variables. This mapping must -be threaded through all the function calls, as any entry in -the mapping must be propagated to all future nodes in the tree. - -The algorithm also must track the set of in-scope variables, in -order to make fresh variables as it flattens. (We are far from a -source of fresh Uniques.) See Wrinkle 2, below. - -There are wrinkles, of course: - -1. The flattening algorithm must account for the possibility - of inner `forall`s. (A `forall` seen here can happen only - because of impredicativity. However, the flattening operation - is an algorithm in Core, which is impredicative.) - Suppose we have (forall b. F b) -> (forall b. F b). Of course, - those two bs are entirely unrelated, and so we should certainly - not flatten the two calls F b to the same variable. Instead, they - must be treated separately. We thus carry a substitution that - freshens variables; we must apply this substitution (in - `coreFlattenTyFamApp`) before looking up an application in the environment. - Note that the range of the substitution contains only TyVars, never anything - else. - - For the sake of efficiency, we only apply this substitution when absolutely - necessary. Namely: - - * We do not perform the substitution at all if it is empty. - * We only need to worry about the arguments of a type family that are within - the arity of said type family, so we can get away with not applying the - substitution to any oversaturated type family arguments. - * Importantly, we do /not/ achieve this substitution by recursively - flattening the arguments, as this would be wrong. Consider `F (G a)`, - where F and G are type families. We might decide that `F (G a)` flattens - to `beta`. Later, the substitution is non-empty (but does not map `a`) and - so we flatten `G a` to `gamma` and try to flatten `F gamma`. Of course, - `F gamma` is unknown, and so we flatten it to `delta`, but it really - should have been `beta`! Argh! - - Moral of the story: instead of flattening the arguments, just substitute - them directly. - -2. There are two different reasons we might add a variable - to the in-scope set as we work: - - A. We have just invented a new flattening variable. - B. We have entered a `forall`. - - Annoying here is that in-scope variable source (A) must be - threaded through the calls. For example, consider (F b -> forall c. F c). - Suppose that, when flattening F b, we invent a fresh variable c. - Now, when we encounter (forall c. F c), we need to know c is already in - scope so that we locally rename c to c'. However, if we don't thread through - the in-scope set from one argument of (->) to the other, we won't know this - and might get very confused. - - In contrast, source (B) increases only as we go deeper, as in-scope sets - normally do. However, even here we must be careful. The TypeMap TyVar that - contains mappings from type family applications to freshened variables will - be threaded through both sides of (forall b. F b) -> (forall b. F b). We - thus must make sure that the two `b`s don't get renamed to the same b1. (If - they did, then looking up `F b1` would yield the same flatten var for - each.) So, even though `forall`-bound variables should really be in the - in-scope set only when they are in scope, we retain these variables even - outside of their scope. This ensures that, if we encounter a fresh - `forall`-bound b, we will rename it to b2, not b1. Note that keeping a - larger in-scope set than strictly necessary is always OK, as in-scope sets - are only ever used to avoid collisions. - - Sadly, the freshening substitution described in (1) really mustn't bind - variables outside of their scope: note that its domain is the *unrenamed* - variables. This means that the substitution gets "pushed down" (like a - reader monad) while the in-scope set gets threaded (like a state monad). - Because a Subst contains its own in-scope set, we don't carry a Subst; - instead, we just carry a TvSubstEnv down, tying it to the InScopeSet - traveling separately as necessary. - -3. Consider `F ty_1 ... ty_n`, where F is a type family with arity k: - - type family F ty_1 ... ty_k :: res_k - - It's tempting to just flatten `F ty_1 ... ty_n` to `alpha`, where alpha is a - flattening skolem. But we must instead flatten it to - `alpha ty_(k+1) ... ty_n`—that is, by only flattening up to the arity of the - type family. - - Why is this better? Consider the following concrete example from #16995: - - type family Param :: Type -> Type - - type family LookupParam (a :: Type) :: Type where - LookupParam (f Char) = Bool - LookupParam x = Int - - foo :: LookupParam (Param ()) - foo = 42 - - In order for `foo` to typecheck, `LookupParam (Param ())` must reduce to - `Int`. But if we flatten `Param ()` to `alpha`, then GHC can't be sure if - `alpha` is apart from `f Char`, so it won't fall through to the second - equation. But since the `Param` type family has arity 0, we can instead - flatten `Param ()` to `alpha ()`, about which GHC knows with confidence is - apart from `f Char`, permitting the second equation to be reached. - - Not only does this allow more programs to be accepted, it's also important - for correctness. Not doing this was the root cause of the Core Lint error - in #16995. - -flattenTys is defined here because of module dependencies. --} - -data FlattenEnv - = FlattenEnv { fe_type_map :: TypeMap (TyVar, TyCon, [Type]) - -- domain: exactly-saturated type family applications - -- range: (fresh variable, type family tycon, args) - , fe_in_scope :: InScopeSet } - -- See Note [Flattening type-family applications when matching instances] - -emptyFlattenEnv :: InScopeSet -> FlattenEnv -emptyFlattenEnv in_scope - = FlattenEnv { fe_type_map = emptyTypeMap - , fe_in_scope = in_scope } - -updateInScopeSet :: FlattenEnv -> (InScopeSet -> InScopeSet) -> FlattenEnv -updateInScopeSet env upd = env { fe_in_scope = upd (fe_in_scope env) } - -flattenTys :: Traversable f => InScopeSet -> f Type -> f Type --- See Note [Flattening type-family applications when matching instances] -flattenTys = \ in_scope tys -> fst (flattenTysX in_scope tys) -{-# INLINE flattenTys #-} - -flattenTysX :: Traversable f => InScopeSet -> f Type -> (f Type, TyVarEnv (TyCon, [Type])) --- See Note [Flattening type-family applications when matching instances] --- NB: the returned types mention the fresh type variables --- in the domain of the returned env, whose range includes --- the original type family applications. Building a substitution --- from this information and applying it would yield the original --- types -- almost. The problem is that the original type might --- have something like (forall b. F a b); the returned environment --- can't really sensibly refer to that b. So it may include a locally- --- bound tyvar in its range. Currently, the only usage of this env't --- checks whether there are any meta-variables in it --- (in GHC.Tc.Solver.Monad.mightEqualLater), so this is all OK. -flattenTysX in_scope tys - = let (env, result) = coreFlattenTys emptyTvSubstEnv (emptyFlattenEnv in_scope) tys in - (result, build_env (fe_type_map env)) - where - build_env :: TypeMap (TyVar, TyCon, f Type) -> TyVarEnv (TyCon, f Type) - build_env env_in - = foldTM (\(tv, tc, tys) env_out -> extendVarEnv env_out tv (tc, tys)) - env_in emptyVarEnv -{-# SPECIALIZE flattenTysX :: InScopeSet -> [Type] -> ([Type], TyVarEnv (TyCon, [Type])) #-} - -coreFlattenTys :: Traversable f => TvSubstEnv -> FlattenEnv - -> f Type -> (FlattenEnv, f Type) -coreFlattenTys = mapAccumL . coreFlattenTy -{-# INLINE coreFlattenTys #-} - -coreFlattenTy :: TvSubstEnv -> FlattenEnv - -> Type -> (FlattenEnv, Type) -coreFlattenTy subst = go - where - go env ty | Just ty' <- coreView ty = go env ty' - - go env (TyVarTy tv) - | Just ty <- lookupVarEnv subst tv = (env, ty) - | otherwise = let (env', ki) = go env (tyVarKind tv) in - (env', mkTyVarTy $ setTyVarKind tv ki) - go env (AppTy ty1 ty2) = let (env1, ty1') = go env ty1 - (env2, ty2') = go env1 ty2 in - (env2, AppTy ty1' ty2') - go env (TyConApp tc tys) - -- NB: Don't just check if isFamilyTyCon: this catches *data* families, - -- which are generative and thus can be preserved during flattening - | not (isGenerativeTyCon tc Nominal) - = coreFlattenTyFamApp subst env tc tys - - | otherwise - = let (env', tys') = coreFlattenTys subst env tys in - (env', mkTyConApp tc tys') - - go env ty@(FunTy { ft_mult = mult, ft_arg = ty1, ft_res = ty2 }) - = let (env1, ty1') = go env ty1 - (env2, ty2') = go env1 ty2 - (env3, mult') = go env2 mult in - (env3, ty { ft_mult = mult', ft_arg = ty1', ft_res = ty2' }) - - go env (ForAllTy (Bndr tv vis) ty) - = let (env1, subst', tv') = coreFlattenVarBndr subst env tv - (env2, ty') = coreFlattenTy subst' env1 ty in - (env2, ForAllTy (Bndr tv' vis) ty') - - go env ty@(LitTy {}) = (env, ty) - - go env (CastTy ty co) - = let (env1, ty') = go env ty - (env2, co') = coreFlattenCo subst env1 co in - (env2, CastTy ty' co') - - go env (CoercionTy co) - = let (env', co') = coreFlattenCo subst env co in - (env', CoercionTy co') - - --- when flattening, we don't care about the contents of coercions. --- so, just return a fresh variable of the right (flattened) type -coreFlattenCo :: TvSubstEnv -> FlattenEnv - -> Coercion -> (FlattenEnv, Coercion) -coreFlattenCo subst env co - = (env2, mkCoVarCo covar) - where - (env1, kind') = coreFlattenTy subst env (coercionType co) - covar = mkFlattenFreshCoVar (fe_in_scope env1) kind' - -- Add the covar to the FlattenEnv's in-scope set. - -- See Note [Flattening type-family applications when matching instances], wrinkle 2A. - env2 = updateInScopeSet env1 (flip extendInScopeSet covar) - -coreFlattenVarBndr :: TvSubstEnv -> FlattenEnv - -> TyCoVar -> (FlattenEnv, TvSubstEnv, TyVar) -coreFlattenVarBndr subst env tv - = (env2, subst', tv') - where - -- See Note [Flattening type-family applications when matching instances], wrinkle 2B. - kind = varType tv - (env1, kind') = coreFlattenTy subst env kind - tv' = uniqAway (fe_in_scope env1) (setVarType tv kind') - subst' = extendVarEnv subst tv (mkTyVarTy tv') - env2 = updateInScopeSet env1 (flip extendInScopeSet tv') - -coreFlattenTyFamApp :: TvSubstEnv -> FlattenEnv - -> TyCon -- type family tycon - -> [Type] -- args, already flattened - -> (FlattenEnv, Type) -coreFlattenTyFamApp tv_subst env fam_tc fam_args - = case lookupTypeMap type_map fam_ty of - Just (tv, _, _) -> (env', mkAppTys (mkTyVarTy tv) leftover_args') - Nothing -> - let tyvar_name = mkFlattenFreshTyName fam_tc - tv = uniqAway in_scope $ - mkTyVar tyvar_name (typeKind fam_ty) - - ty' = mkAppTys (mkTyVarTy tv) leftover_args' - env'' = env' { fe_type_map = extendTypeMap type_map fam_ty - (tv, fam_tc, sat_fam_args) - , fe_in_scope = extendInScopeSet in_scope tv } - in (env'', ty') - where - arity = tyConArity fam_tc - tcv_subst = Subst (fe_in_scope env) emptyIdSubstEnv tv_subst emptyVarEnv - (sat_fam_args, leftover_args) = assert (arity <= length fam_args) $ - splitAt arity fam_args - -- Apply the substitution before looking up an application in the - -- environment. See Note [Flattening type-family applications when matching instances], - -- wrinkle 1. - -- NB: substTys short-cuts the common case when the substitution is empty. - sat_fam_args' = substTys tcv_subst sat_fam_args - (env', leftover_args') = coreFlattenTys tv_subst env leftover_args - -- `fam_tc` may be over-applied to `fam_args` (see - -- Note [Flattening type-family applications when matching instances] - -- wrinkle 3), so we split it into the arguments needed to saturate it - -- (sat_fam_args') and the rest (leftover_args') - fam_ty = mkTyConApp fam_tc sat_fam_args' - FlattenEnv { fe_type_map = type_map - , fe_in_scope = in_scope } = env' - -mkFlattenFreshTyName :: Uniquable a => a -> Name -mkFlattenFreshTyName unq - = mkSysTvName (getUnique unq) (fsLit "flt") - -mkFlattenFreshCoVar :: InScopeSet -> Kind -> CoVar -mkFlattenFreshCoVar in_scope kind - = let uniq = unsafeGetFreshLocalUnique in_scope - name = mkSystemVarName uniq (fsLit "flc") - in mkCoVar name kind - ===================================== compiler/GHC/Runtime/Heap/Inspect.hs ===================================== @@ -1128,7 +1128,7 @@ findPtrTyss i tys = foldM step (i, []) tys -- The types can contain skolem type variables, which need to be treated as normal vars. -- In particular, we want them to unify with things. improveRTTIType :: HscEnv -> RttiType -> RttiType -> Maybe Subst -improveRTTIType _ base_ty new_ty = U.tcUnifyTyKi base_ty new_ty +improveRTTIType _ base_ty new_ty = U.tcUnifyDebugger base_ty new_ty getDataConArgTys :: DataCon -> Type -> TR [Type] -- Given the result type ty of a constructor application (D a b c :: ty) ===================================== compiler/GHC/Tc/Errors.hs ===================================== @@ -2240,7 +2240,8 @@ mkDictErr ctxt orig_items -- and the result of evaluating ...". mk_dict_err :: HasCallStack => SolverReportErrCtxt -> (ErrorItem, ClsInstLookupResult) -> TcM ( TcSolverReportMsg, ([ImportError], [GhcHint]) ) -mk_dict_err ctxt (item, (matches, pot_unifiers, unsafe_overlapped)) = case (NE.nonEmpty matches, NE.nonEmpty unsafe_overlapped) of +mk_dict_err ctxt (item, (matches, pot_unifiers, unsafe_overlapped)) + = case (NE.nonEmpty matches, NE.nonEmpty unsafe_overlapped) of (Nothing, _) -> do -- No matches but perhaps several unifiers { (_, rel_binds, item) <- relevantBindings True ctxt item ; candidate_insts <- get_candidate_instances ===================================== compiler/GHC/Tc/Gen/Pat.hs ===================================== @@ -1177,7 +1177,7 @@ tcDataConPat (L con_span con_name) data_con pat_ty_scaled ; (tenv, ex_tvs') <- tcInstSuperSkolTyVarsX skol_info tenv1 ex_tvs -- Get location from monad, not from ex_tvs -- This freshens: See Note [Freshen existentials] - -- Why "super"? See Note [Binding when looking up instances] + -- Why "super"? See Note [Super skolems: binding when looking up instances] -- in GHC.Core.InstEnv. ; let arg_tys' = substScaledTys tenv arg_tys ===================================== compiler/GHC/Tc/Instance/FunDeps.hs ===================================== @@ -663,19 +663,19 @@ checkFunDeps inst_envs (ClsInst { is_tvs = qtvs1, is_cls = cls | instanceCantMatch trimmed_tcs rough_tcs2 = False | otherwise - = case tcUnifyTyKis bind_fn ltys1 ltys2 of + = case tcUnifyFunDeps qtvs ltys1 ltys2 of Nothing -> False Just subst -> isNothing $ -- Bogus legacy test (#10675) -- See Note [Bogus consistency check] - tcUnifyTyKis bind_fn (substTysUnchecked subst rtys1) (substTysUnchecked subst rtys2) + tcUnifyFunDeps qtvs (substTysUnchecked subst rtys1) (substTysUnchecked subst rtys2) where trimmed_tcs = trimRoughMatchTcs cls_tvs fd rough_tcs1 (ltys1, rtys1) = instFD fd cls_tvs tys1 (ltys2, rtys2) = instFD fd cls_tvs tys2 qtv_set2 = mkVarSet qtvs2 - bind_fn = matchBindFun (qtv_set1 `unionVarSet` qtv_set2) + qtvs = qtv_set1 `unionVarSet` qtv_set2 eq_inst i1 i2 = instanceDFunId i1 == instanceDFunId i2 -- A single instance may appear twice in the un-nubbed conflict list ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -1089,7 +1089,7 @@ Other notes: - natural numbers - Typeable -* See also Note [What might equal later?] in GHC.Tc.Solver.InertSet. +* See also Note [What might equal later?] in GHC.Tc.Utils.Unify * The given-overlap problem is arguably not easy to appear in practice due to our aggressive prioritization of equality solving over other ===================================== compiler/GHC/Tc/Solver/Equality.hs ===================================== @@ -33,7 +33,7 @@ import GHC.Core.TyCo.Rep -- cleverly decomposes types, good for completeness c import GHC.Core.Coercion import GHC.Core.Coercion.Axiom import GHC.Core.Reduction -import GHC.Core.Unify( tcUnifyTyWithTFs ) +import GHC.Core.Unify( tcUnifyTyForInjectivity ) import GHC.Core.FamInstEnv ( FamInstEnvs, FamInst(..), apartnessCheck , lookupFamInstEnvByTyCon ) import GHC.Core @@ -2446,10 +2446,9 @@ More details: However, we make no attempt to detect cases like a ~ (F a, F a) and use the same tyvar to replace F a. The constraint solver will common them up later! - (Cf. Note [Flattening type-family applications when matching instances] in - GHC.Core.Unify, which goes to this extra effort.) However, this is really - a very small corner case. The investment to craft a clever, performant - solution seems unworthwhile. + (Cf. Note [Apartness and type families] in GHC.Core.Unify, which goes to + this extra effort.) However, this is really a very small corner case. The + investment to craft a clever, performant solution seems unworthwhile. (6) We often get the predicate associated with a constraint from its evidence with ctPred. We thus must not only make sure the generated CEqCan's fields @@ -3031,7 +3030,7 @@ improve_injective_wanted_top fam_envs inj_args fam_tc lhs_tys rhs_ty do_one :: CoAxBranch -> TcS [TypeEqn] do_one branch@(CoAxBranch { cab_tvs = branch_tvs, cab_lhs = branch_lhs_tys, cab_rhs = branch_rhs }) | let in_scope1 = in_scope `extendInScopeSetList` branch_tvs - , Just subst <- tcUnifyTyWithTFs False in_scope1 branch_rhs rhs_ty + , Just subst <- tcUnifyTyForInjectivity False in_scope1 branch_rhs rhs_ty = do { let inSubst tv = tv `elemVarEnv` getTvSubstEnv subst unsubstTvs = filterOut inSubst branch_tvs -- The order of unsubstTvs is important; it must be @@ -3043,13 +3042,20 @@ improve_injective_wanted_top fam_envs inj_args fam_tc lhs_tys rhs_ty -- be sure to apply the current substitution to a's kind. -- Hence instFlexiX. #13135 was an example. + ; traceTcS "improve_inj_top" $ + vcat [ text "branch_rhs" <+> ppr branch_rhs + , text "rhs_ty" <+> ppr rhs_ty + , text "subst" <+> ppr subst + , text "subst1" <+> ppr subst1 ] ; if apartnessCheck (substTys subst1 branch_lhs_tys) branch - then return (mkInjectivityEqns inj_args (map (substTy subst1) branch_lhs_tys) lhs_tys) + then do { traceTcS "improv_inj_top1" (ppr branch_lhs_tys) + ; return (mkInjectivityEqns inj_args (map (substTy subst1) branch_lhs_tys) lhs_tys) } -- NB: The fresh unification variables (from unsubstTvs) are on the left -- See Note [Improvement orientation] - else return [] } + else do { traceTcS "improve_inj_top2" empty; return [] } } | otherwise - = return [] + = do { traceTcS "improve_inj_top:fail" (ppr branch_rhs $$ ppr rhs_ty $$ ppr in_scope $$ ppr branch_tvs) + ; return [] } in_scope = mkInScopeSet (tyCoVarsOfType rhs_ty) ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -1861,134 +1861,6 @@ prohibitedSuperClassSolve given_loc wanted_loc | otherwise = False -{- Note [What might equal later?] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We must determine whether a Given might later equal a Wanted. We -definitely need to account for the possibility that any metavariable -might be arbitrarily instantiated. Yet we do *not* want -to allow skolems in to be instantiated, as we've already rewritten -with respect to any Givens. (We're solving a Wanted here, and so -all Givens have already been processed.) - -This is best understood by example. - -1. C alpha ~? C Int - - That given certainly might match later. - -2. C a ~? C Int - - No. No new givens are going to arise that will get the `a` to rewrite - to Int. - -3. C alpha[tv] ~? C Int - - That alpha[tv] is a TyVarTv, unifiable only with other type variables. - It cannot equal later. - -4. C (F alpha) ~? C Int - - Sure -- that can equal later, if we learn something useful about alpha. - -5. C (F alpha[tv]) ~? C Int - - This, too, might equal later. Perhaps we have [G] F b ~ Int elsewhere. - Or maybe we have C (F alpha[tv] beta[tv]), these unify with each other, - and F x x = Int. Remember: returning True doesn't commit ourselves to - anything. - -6. C (F a) ~? C a - - No, this won't match later. If we could rewrite (F a) or a, we would - have by now. But see also Red Herring below. - -7. C (Maybe alpha) ~? C alpha - - We say this cannot equal later, because it would require - alpha := Maybe (Maybe (Maybe ...)). While such a type can be contrived, - we choose not to worry about it. See Note [Infinitary substitution in lookup] - in GHC.Core.InstEnv. Getting this wrong let to #19107, tested in - typecheck/should_compile/T19107. - -8. C cbv ~? C Int - where cbv = F a - - The cbv is a cycle-breaker var which stands for F a. See - Note [Type equality cycles] in GHC.Tc.Solver.Equality - This is just like case 6, and we say "no". Saying "no" here is - essential in getting the parser to type-check, with its use of DisambECP. - -9. C cbv ~? C Int - where cbv = F alpha - - Here, we might indeed equal later. Distinguishing between - this case and Example 8 is why we need the InertSet in mightEqualLater. - -10. C (F alpha, Int) ~? C (Bool, F alpha) - - This cannot equal later, because F a would have to equal both Bool and - Int. - -To deal with type family applications, we use the Core flattener. See -Note [Flattening type-family applications when matching instances] in GHC.Core.Unify. -The Core flattener replaces all type family applications with -fresh variables. The next question: should we allow these fresh -variables in the domain of a unifying substitution? - -A type family application that mentions only skolems (example 6) is settled: -any skolems would have been rewritten w.r.t. Givens by now. These type family -applications match only themselves. A type family application that mentions -metavariables, on the other hand, can match anything. So, if the original type -family application contains a metavariable, we use BindMe to tell the unifier -to allow it in the substitution. On the other hand, a type family application -with only skolems is considered rigid. - -This treatment fixes #18910 and is tested in -typecheck/should_compile/InstanceGivenOverlap{,2} - -Red Herring -~~~~~~~~~~~ -In #21208, we have this scenario: - -instance forall b. C b -[G] C a[sk] -[W] C (F a[sk]) - -What should we do with that wanted? According to the logic above, the Given -cannot match later (this is example 6), and so we use the global instance. -But wait, you say: What if we learn later (say by a future type instance F a = a) -that F a unifies with a? That looks like the Given might really match later! - -This mechanism described in this Note is *not* about this kind of situation, however. -It is all asking whether a Given might match the Wanted *in this run of the solver*. -It is *not* about whether a variable might be instantiated so that the Given matches, -or whether a type instance introduced in a downstream module might make the Given match. -The reason we care about what might match later is only about avoiding order-dependence. -That is, we don't want to commit to a course of action that depends on seeing constraints -in a certain order. But an instantiation of a variable and a later type instance -don't introduce order dependency in this way, and so mightMatchLater is right to ignore -these possibilities. - -Here is an example, with no type families, that is perhaps clearer: - -instance forall b. C (Maybe b) -[G] C (Maybe Int) -[W] C (Maybe a) - -What to do? We *might* say that the Given could match later and should thus block -us from using the global instance. But we don't do this. Instead, we rely on class -coherence to say that choosing the global instance is just fine, even if later we -call a function with (a := Int). After all, in this run of the solver, [G] C (Maybe Int) -will definitely never match [W] C (Maybe a). (Recall that we process Givens before -Wanteds, so there is no [G] a ~ Int hanging about unseen.) - -Interestingly, in the first case (from #21208), the behavior changed between -GHC 8.10.7 and GHC 9.2, with the latter behaving correctly and the former -reporting overlapping instances. - -Test case: typecheck/should_compile/T21208. - --} {- ********************************************************************* * * ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -352,10 +352,9 @@ does the same thing; it shows up in module Fraction.hs. Conclusion: when typechecking the methods in a C [a] instance, we want to treat the 'a' as an *existential* type variable, in the sense described -by Note [Binding when looking up instances]. That is why isOverlappableTyVar -responds True to an InstSkol, which is the kind of skolem we use in -tcInstDecl2. - +by Note [Super skolems: binding when looking up instances] in GHC.Core.InstEnv +That is why isOverlappableTyVar responds True to an InstSkol, which is the kind +of skolem we use in tcInstDecl2. Note [Tricky type variable scoping] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -46,10 +46,11 @@ module GHC.Tc.Types.Constraint ( cterHasNoProblem, cterHasProblem, cterHasOnlyProblem, cterHasOnlyProblems, cterRemoveProblem, cterHasOccursCheck, cterFromKind, - + -- Equality left-hand sides, re-exported from GHC.Core.Predicate CanEqLHS(..), canEqLHS_maybe, canTyFamEqLHS_maybe, canEqLHSKind, canEqLHSType, eqCanEqLHS, + -- Holes Hole(..), HoleSort(..), isOutOfScopeHole, DelayedError(..), NotConcreteError(..), @@ -286,17 +287,6 @@ data EqCt -- An equality constraint; see Note [Canonical equalities] eq_eq_rel :: EqRel -- INVARIANT: cc_eq_rel = ctEvEqRel cc_ev } --- | A 'CanEqLHS' is a type that can appear on the left of a canonical --- equality: a type variable or /exactly-saturated/ type family application. -data CanEqLHS - = TyVarLHS TcTyVar - | TyFamLHS TyCon -- ^ TyCon of the family - [Xi] -- ^ Arguments, /exactly saturating/ the family - -instance Outputable CanEqLHS where - ppr (TyVarLHS tv) = ppr tv - ppr (TyFamLHS fam_tc fam_args) = ppr (mkTyConApp fam_tc fam_args) - eqCtEvidence :: EqCt -> CtEvidence eqCtEvidence = eq_ev @@ -777,45 +767,6 @@ instance Outputable Ct where instance Outputable EqCt where ppr (EqCt { eq_ev = ev }) = ppr ev ------------------------------------ --- | Is a type a canonical LHS? That is, is it a tyvar or an exactly-saturated --- type family application? --- Does not look through type synonyms. -canEqLHS_maybe :: Xi -> Maybe CanEqLHS -canEqLHS_maybe xi - | Just tv <- getTyVar_maybe xi - = Just $ TyVarLHS tv - - | otherwise - = canTyFamEqLHS_maybe xi - -canTyFamEqLHS_maybe :: Xi -> Maybe CanEqLHS -canTyFamEqLHS_maybe xi - | Just (tc, args) <- tcSplitTyConApp_maybe xi - , isTypeFamilyTyCon tc - , args `lengthIs` tyConArity tc - = Just $ TyFamLHS tc args - - | otherwise - = Nothing - --- | Convert a 'CanEqLHS' back into a 'Type' -canEqLHSType :: CanEqLHS -> TcType -canEqLHSType (TyVarLHS tv) = mkTyVarTy tv -canEqLHSType (TyFamLHS fam_tc fam_args) = mkTyConApp fam_tc fam_args - --- | Retrieve the kind of a 'CanEqLHS' -canEqLHSKind :: CanEqLHS -> TcKind -canEqLHSKind (TyVarLHS tv) = tyVarKind tv -canEqLHSKind (TyFamLHS fam_tc fam_args) = piResultTys (tyConKind fam_tc) fam_args - --- | Are two 'CanEqLHS's equal? -eqCanEqLHS :: CanEqLHS -> CanEqLHS -> Bool -eqCanEqLHS (TyVarLHS tv1) (TyVarLHS tv2) = tv1 == tv2 -eqCanEqLHS (TyFamLHS fam_tc1 fam_args1) (TyFamLHS fam_tc2 fam_args2) - = tcEqTyConApps fam_tc1 fam_args1 fam_tc2 fam_args2 -eqCanEqLHS _ _ = False - {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Utils/Instantiate.hs ===================================== @@ -579,7 +579,7 @@ tcSkolDFunType dfun_ty ; (subst, inst_tvs) <- tcInstSuperSkolTyVars skol_info tvs -- We instantiate the dfun_tyd with superSkolems. -- See Note [Subtle interaction of recursion and overlap] - -- and Note [Binding when looking up instances] + -- and Note [Super skolems: binding when looking up instances] ; let inst_tys = substTys subst tys skol_info_anon = mkClsInstSkol cls inst_tys } @@ -590,7 +590,7 @@ tcSuperSkolTyVars :: TcLevel -> SkolemInfo -> [TyVar] -> (Subst, [TcTyVar]) -- Make skolem constants, but do *not* give them new names, as above -- As always, allocate them one level in -- Moreover, make them "super skolems"; see GHC.Core.InstEnv --- Note [Binding when looking up instances] +-- Note [Super skolems: binding when looking up instances] -- See Note [Kind substitution when instantiating] -- Precondition: tyvars should be ordered by scoping tcSuperSkolTyVars tc_lvl skol_info = mapAccumL do_one emptySubst ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -606,7 +606,8 @@ data TcTyVarDetails -- how this level number is used Bool -- True <=> this skolem type variable can be overlapped -- when looking up instances - -- See Note [Binding when looking up instances] in GHC.Core.InstEnv + -- See Note [Super skolems: binding when looking up instances] + -- in GHC.Core.InstEnv | RuntimeUnk -- Stands for an as-yet-unknown type in the GHCi -- interactive context ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -112,7 +112,6 @@ import GHC.Driver.DynFlags import GHC.Data.Bag import GHC.Data.FastString import GHC.Data.Maybe (firstJusts) -import GHC.Data.Pair import Control.Monad import Data.Functor.Identity (Identity(..)) @@ -4139,6 +4138,155 @@ makeTypeConcrete occ_fs conc_orig ty = orig = case conc_orig of ConcreteFRR frr_orig -> FRROrigin frr_orig + +{- ********************************************************************* +* * + mightEqualLater +* * +********************************************************************* -} + +{- Note [What might equal later?] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We must determine whether a Given might later equal a Wanted: + see Note [Instance and Given overlap] in GHC.Tc.Solver.Dict + +We definitely need to account for the possibility that any metavariable might be +arbitrarily instantiated. Yet we do *not* want to allow skolems in to be +instantiated, as we've already rewritten with respect to any Givens. (We're +solving a Wanted here, and so all Givens have already been processed.) + +This is best understood by example. + +1. C alpha ~? C Int + + That given certainly might match later. + +2. C a ~? C Int + + No. No new givens are going to arise that will get the `a` to rewrite + to Int. Example: + f :: forall a. C a => blah + f = rhs -- Gives rise to [W] C Int + It would be silly to fail to solve ([W] C Int), just because we have + ([G] C a) in the Givens! + +3. C alpha[tv] ~? C Int + + In this variant of (1) that alpha[tv] is a TyVarTv, unifiable only with + other type /variables/. It cannot equal Int later. + +4. C (F alpha) ~? C Int + + Sure -- that can equal later, if we learn something useful about alpha. + +5. C (F alpha[tv]) ~? C Int + + This, too, might equal later. Perhaps we have [G] F b ~ Int elsewhere. + Or maybe we have C (F alpha[tv] beta[tv]), these unify with each other, + and F x x = Int. Remember: returning True doesn't commit ourselves to + anything. + +6. C (F a) ~? C Int, where a is a skolem. For example + f :: forall a. C (F a) => blah + f = rhs -- Gives rise to [W] C Int + + No, this won't match later. If we could rewrite (F a), we would + have by now. But see also Red Herring below. + + This arises in instance decls too. For example in GHC.Core.Ppr we see + instance Outputable (XTickishId pass) + => Outputable (GenTickish pass) where + If we have [W] Outputable Int in the body, we don't want to fail to solve + it because (XTickishId pass) might simplify to Int. + +7. C (Maybe alpha) ~? C alpha + + We say this cannot equal later, because it would require + alpha := Maybe (Maybe (Maybe ...)). While such a type can be contrived, + we choose not to worry about it. See Note [Infinitary substitution in lookup] + in GHC.Core.InstEnv. Getting this wrong let to #19107, tested in + typecheck/should_compile/T19107. + +8. C cbv ~? C Int + where cbv = F a + + The cbv is a cycle-breaker var which stands for F a. See + Note [Type equality cycles] in GHC.Tc.Solver.Equality + This is just like case 6, and we say "no". Saying "no" here is + essential in getting the parser to type-check, with its use of DisambECP. + +9. C cbv ~? C Int + where cbv = F alpha + + Here, we might indeed equal later. Distinguishing between + this case and Example 8 is why we need the InertSet in mightEqualLater. + +10. C (F alpha, Int) ~? C (Bool, F alpha) + + This cannot equal later, because F a would have to equal both Bool and + Int. + +To deal with type family applications, we use the "fine-grain" Core unifier. +See Note [Apartness and type families] in GHC.Core.Unify. +The Core flattener replaces all type family applications with +fresh variables. The next question: should we allow these fresh +variables in the domain of a unifying substitution? + +A type family application that mentions only skolems (example 6) is settled: +any skolems would have been rewritten w.r.t. Givens by now. These type family +applications match only themselves. A type family application that mentions +metavariables, on the other hand, can match anything. So, if the original type +family application contains a metavariable, we use BindMe to tell the unifier +to allow it in the substitution. On the other hand, a type family application +with only skolems is considered rigid. + +This treatment fixes #18910 and is tested in +typecheck/should_compile/InstanceGivenOverlap{,2} + +Red Herring +~~~~~~~~~~~ +In #21208, we have this scenario: + + instance forall b. C b + [G] C a[sk] + [W] C (F a[sk]) + +What should we do with that wanted? According to the logic above, the Given +cannot match later (this is example 6), and so we use the global instance. +But wait, you say: What if we learn later (say by a future type instance F a = a) +that F a unifies with a? That looks like the Given might really match later! + +This mechanism described in this Note is *not* about this kind of situation, however. +It is all asking whether a Given might match the Wanted *in this run of the solver*. +It is *not* about whether a variable might be instantiated so that the Given matches, +or whether a type instance introduced in a downstream module might make the Given match. +The reason we care about what might match later is only about avoiding order-dependence. +That is, we don't want to commit to a course of action that depends on seeing constraints +in a certain order. But an instantiation of a variable and a later type instance +don't introduce order dependency in this way, and so mightMatchLater is right to ignore +these possibilities. + +Here is an example, with no type families, that is perhaps clearer: + + instance forall b. C (Maybe b) + [G] C (Maybe Int) + [W] C (Maybe a) + +What to do? We *might* say that the Given could match later and should thus block +us from using the global instance. But we don't do this. Instead, we rely on class +coherence to say that choosing the global instance is just fine, even if later we +call a function with (a := Int). After all, in this run of the solver, [G] C (Maybe Int) +will definitely never match [W] C (Maybe a). (Recall that we process Givens before +Wanteds, so there is no [G] a ~ Int hanging about unseen.) + +Interestingly, in the first case (from #21208), the behavior changed between +GHC 8.10.7 and GHC 9.2, with the latter behaving correctly and the former +reporting overlapping instances. + +Test case: typecheck/should_compile/T21208. + +-} + -------------------------------------------------------------------------------- -- mightEqualLater @@ -4150,7 +4298,7 @@ mightEqualLater inert_set given_pred given_loc wanted_pred wanted_loc = Nothing | otherwise - = case tcUnifyTysFG bind_fun [flattened_given] [flattened_wanted] of + = case tcUnifyTysFG bind_fam bind_tv [given_pred] [wanted_pred] of Unifiable subst -> Just subst MaybeApart reason subst @@ -4161,31 +4309,21 @@ mightEqualLater inert_set given_pred given_loc wanted_pred wanted_loc SurelyApart -> Nothing where - in_scope = mkInScopeSet $ tyCoVarsOfTypes [given_pred, wanted_pred] - - -- NB: flatten both at the same time, so that we can share mappings - -- from type family applications to variables, and also to guarantee - -- that the fresh variables are really fresh between the given and - -- the wanted. Flattening both at the same time is needed to get - -- Example 10 from the Note. - (Pair flattened_given flattened_wanted, var_mapping) - = flattenTysX in_scope (Pair given_pred wanted_pred) - - bind_fun :: BindFun - bind_fun tv rhs_ty + bind_tv :: BindTvFun + bind_tv tv rhs_ty | MetaTv { mtv_info = info } <- tcTyVarDetails tv - = if ok_shape tv info rhs_ty && can_unify tv rhs_ty - then BindMe - else Apart - - -- See Examples 4, 5, and 6 from the Note - | Just (_fam_tc, fam_args) <- lookupVarEnv var_mapping tv - , anyFreeVarsOfTypes mentions_meta_ty_var fam_args + , ok_shape tv info rhs_ty + , can_unify tv rhs_ty = BindMe | otherwise = Apart - where + + bind_fam :: BindFamFun + -- See Examples (4), (5), and (6) from the Note, especially (6) + bind_fam _fam_tc fam_args _rhs + | anyFreeVarsOfTypes mentions_meta_ty_var fam_args = BindMe + | otherwise = Apart can_unify :: TcTyVar -> TcType -> Bool can_unify tv rhs_ty @@ -4203,9 +4341,8 @@ mightEqualLater inert_set given_pred given_loc wanted_pred wanted_loc | isMetaTyVar tv = case metaTyVarInfo tv of -- See Examples 8 and 9 in the Note - CycleBreakerTv - -> anyFreeVarsOfType mentions_meta_ty_var - (lookupCycleBreakerVar tv inert_set) + CycleBreakerTv -> anyFreeVarsOfType mentions_meta_ty_var + (lookupCycleBreakerVar tv inert_set) _ -> True | otherwise = False @@ -4235,7 +4372,7 @@ false positives: 3. Concreteness: ty1 = kappa[conc] /~ ty2 = k[sk]. In these examples, ty1 and ty2 cannot unify; to inform the pure unifier of this -fact, we use 'checkTyEqRhs' to provide the 'BindFun'. +fact, we use 'checkTyEqRhs' to provide the 'BindTvFun'. Failing to account for this caused #25744: ===================================== compiler/GHC/Utils/Panic.hs ===================================== @@ -191,7 +191,7 @@ pprPanic :: HasCallStack => String -> SDoc -> a pprPanic s doc = panicDoc s (doc $$ callStackDoc) -- | Throw an exception saying "bug in GHC" -panicDoc :: String -> SDoc -> a +panicDoc :: HasCallStack => String -> SDoc -> a panicDoc x doc = throwGhcException (PprPanic x doc) -- | Throw an exception saying "this isn't finished yet" ===================================== testsuite/tests/indexed-types/should_compile/T25657.hs ===================================== @@ -0,0 +1,42 @@ +{-# language AllowAmbiguousTypes #-} +{-# language TypeData #-} +{-# language DataKinds, TypeFamilyDependencies #-} + +{- This test checks that + MyEq (Var A) (Var B) --> False + MyEq (Var A) (Var A) --> True + +remembering that Var is injective. + +To achieve this we need + MyEq (Var A) (Var B) +to be apart from + MyEq a a +o +-} +module T25657 where + +import Data.Kind (Type) +import Data.Type.Equality ((:~:) (Refl)) + + +type Tag :: Type +type data Tag = A | B + + +type Var :: forall {k}. Tag -> k +type family Var tag = a | a -> tag + + +type MyEq :: k -> k -> Bool +type family MyEq a b where + MyEq a a = 'True + MyEq _ _ = 'False + + +true :: MyEq (Var A) (Var A) :~: 'True +true = Refl + + +false :: MyEq (Var A) (Var B) :~: 'False +false = Refl ===================================== testsuite/tests/indexed-types/should_compile/all.T ===================================== @@ -315,3 +315,4 @@ test('T25611a', normal, compile, ['']) test('T25611b', normal, compile, ['']) test('T25611c', normal, compile, ['']) test('T25611d', normal, compile, ['']) +test('T25657', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_compile/InstanceGivenOverlap.hs ===================================== @@ -19,5 +19,26 @@ type family F a b where wob :: forall a b. (Q [F a b], R b a) => a -> Int wob = undefined -g :: forall a. Q [a] => [a] -> Int -g x = wob x +g :: forall c. Q [c] => [c] -> Int +g x = wob x -- Instantiate wob @[c] @beta + +{- Constraint solving for g + +[G] Q [c] +[W] Q [F [c] beta] -- Do NOT fire Q [x] instance +[W] R beta [c] +--> instance for R +[G] Q [c] +[W] Q [F [c] beta] +[W] beta ~ c +--> +[G] Q [c] +[W] Q [F [c] c] +--> Eqn for F +[G] Q [c] +[W] Q [c] +--> done + +c ~ F [c] beta + +-} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da2b4e474d3164fa1637244778750b4c7b72d5a3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da2b4e474d3164fa1637244778750b4c7b72d5a3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/56324e7e/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 14:21:44 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 05 Mar 2025 09:21:44 -0500 Subject: [Git][ghc/ghc][wip/T25647] Improve documentation on wildcard interpretation in type families, clarifying... Message-ID: <67c85df892ec7_3f5b51c5d501908b@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 2523547c by Patrick at 2025-03-05T22:21:33+08:00 Improve documentation on wildcard interpretation in type families, clarifying the relationship with class arguments and enhancing the explanation of FamArgFlavour categories. - - - - - 1 changed file: - compiler/GHC/Core/TyCon.hs Changes: ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2985,11 +2985,15 @@ Wildcards in type families are used to represent type/kind information that are not specified by the user. See Note [Wildcards in family instances] for more intuition. -It is controversial how to interpret wildcards in type families. Hence We -classify kinds of wildcards in type families into three categories represented -by the FamArgFlavour data type: ClassArg, FreeArg, and SigArg, see Note [FamArgFlavour] -for more detail. This flexibility allows us to flip the interpretation of wildcards in -type families. +It is controversial how to interpret wildcards in type families because of their +close connection with the class arguments of associated families. The main challenge +arises from the fact that some wildcard occurrences correspond to arguments provided +by the parent class (class arguments), while others are supplied freely by the user. +To resolve this ambiguity, we classify wildcards into three categories using the +FamArgFlavour data type—namely, ClassArg, FreeArg, and SigArg. This categorization +provides the flexibility to adjust the interpretation of wildcards in type families, +allowing us to experiment with different behaviors. See Note [FamArgFlavour] for more +details. Some common agreements: @@ -3031,7 +3035,7 @@ For more discussion, see #13908. -} {- Note [FamArgFlavour] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~~~~~~~~~ The FamArgFlavour is used to distinguish the different kinds of arguments that may appear in an type family declaration/instance. In an associated type family, some arguments come directly from the parent class (the “class argumentsâ€) while View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2523547c99d797c02f29c2ad87b94b3d848dbf66 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2523547c99d797c02f29c2ad87b94b3d848dbf66 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/e0ecb559/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 14:24:05 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 05 Mar 2025 09:24:05 -0500 Subject: [Git][ghc/ghc][wip/T25647] Add comment to clarify implementation details for wildcards in family instances Message-ID: <67c85e85c5cbe_3f5b51c5e901975d@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: f8b64564 by Patrick at 2025-03-05T22:23:56+08:00 Add comment to clarify implementation details for wildcards in family instances - - - - - 1 changed file: - compiler/GHC/Tc/Gen/HsType.hs Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -2261,12 +2261,13 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) } HM_FamPat _ -> fsLit "_" HM_VTA -> fsLit "w" HM_TyAppPat -> fsLit "_" + + -- see Note [Implementation tweak for wildCards in family instances] mk_wc_details = case hole_mode of HM_FamPat FreeArg -> newTyVarMetaVarDetailsAtLevel HM_FamPat ClassArg -> newTauTvDetailsAtLevel HM_FamPat SigArg -> newTauTvDetailsAtLevel _ -> newTauTvDetailsAtLevel - -- see Note [Implementation tweak for wildCards in family instances] emit_holes = case hole_mode of HM_Sig -> True HM_FamPat _ -> False View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f8b64564d411b8e688884257e7ddf100b0ed6aa6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f8b64564d411b8e688884257e7ddf100b0ed6aa6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/00ccf8e1/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 14:25:29 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 05 Mar 2025 09:25:29 -0500 Subject: [Git][ghc/ghc][wip/T25647] 140 commits: Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. Message-ID: <67c85ed9d836f_3f5b5113b7bc204de@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-â” |---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | â””-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - 05b0ce39 by Simon Peyton Jones at 2025-03-05T14:25:19+00:00 WIP towards #25267 - - - - - d53fb10c by Simon Peyton Jones at 2025-03-05T14:25:19+00:00 Wibbles - - - - - 9301af1a by Simon Peyton Jones at 2025-03-05T14:25:19+00:00 Default tyvars in data/newtype insnstances This is what fixes #25647 - - - - - 05fcdc48 by Simon Peyton Jones at 2025-03-05T14:25:19+00:00 wibbles Including fix for #25725 - - - - - b2bd65af by Simon Peyton Jones at 2025-03-05T14:25:19+00:00 Wibble - - - - - dae7472b by Patrick at 2025-03-05T14:25:19+00:00 add more tests - - - - - 2b6a1890 by Patrick at 2025-03-05T14:25:19+00:00 Fix up T25611d with explicit kind annotation - - - - - daf05085 by Patrick at 2025-03-05T14:25:19+00:00 fix up T25647_fail - - - - - 880c4ae7 by Patrick at 2025-03-05T14:25:19+00:00 cleanup whitespace - - - - - b31eb018 by Patrick at 2025-03-05T14:25:19+00:00 fix up T23512a - - - - - 2487259c by Patrick at 2025-03-05T14:25:19+00:00 add more examples to T25647b - - - - - 59bddf82 by Patrick at 2025-03-05T14:25:19+00:00 add Dix6 to T25647_fail - - - - - 83c9b1d6 by Patrick at 2025-03-05T14:25:19+00:00 add Dix7 for T25647a - - - - - b3092b83 by Patrick at 2025-03-05T14:25:19+00:00 change DefaultingStrategy of tcTyFamInstEqnGuts as well - - - - - b1b9a128 by Patrick at 2025-03-05T14:25:19+00:00 align wildcard with named typevar on wether it is skolem - - - - - b7ca097b by Patrick at 2025-03-05T14:25:19+00:00 fix T17536c - - - - - ac0e4111 by Patrick at 2025-03-05T14:25:19+00:00 Fix T9357 - - - - - e35c133a by Patrick at 2025-03-05T14:25:19+00:00 remove wildcard usage - - - - - 4ed32185 by Patrick at 2025-03-05T14:25:19+00:00 Revert "align wildcard with named typevar on wether it is skolem" This reverts commit d1f61858328cc190de9b34c9a24e8d6b28ee5fa9. - - - - - 88bf0a23 by Patrick at 2025-03-05T14:25:19+00:00 add WildCardTv to forbid wildcard from defaulting - - - - - 2eb5c513 by Patrick at 2025-03-05T14:25:19+00:00 Fix wildcard related tests - - - - - 518bfc63 by Patrick at 2025-03-05T14:25:19+00:00 add wildcards testcase for T25647a - - - - - c2399de7 by Patrick at 2025-03-05T14:25:19+00:00 Fix T25647a - - - - - 429ef9cd by Patrick at 2025-03-05T14:25:19+00:00 Revert "Fix wildcard related tests" This reverts commit 8756ab87f4e3d74968d3937f84f811f78a861852. - - - - - 99e8e0e9 by Patrick at 2025-03-05T14:25:19+00:00 limit WildCardTv to only HM_FamPat - - - - - 51476fff by Patrick at 2025-03-05T14:25:19+00:00 fix - - - - - d4d691ad by Patrick at 2025-03-05T14:25:19+00:00 Revert "remove wildcard usage" This reverts commit ccc9152f23177ab7a542852ffedf626edcdcef95. - - - - - 102ce884 by Patrick at 2025-03-05T14:25:19+00:00 rename WildCardTv to NoDefTauTv - - - - - 12f513e9 by Patrick at 2025-03-05T14:25:19+00:00 update note - - - - - 0288f91a by Patrick at 2025-03-05T14:25:19+00:00 rename isWildCardMetaTyVar to isNoDefTauMetaTyVar and fix defaultTyVarTcS - - - - - 0499b4ce by Patrick at 2025-03-05T14:25:19+00:00 fix comment - - - - - 141a9db7 by Patrick at 2025-03-05T14:25:19+00:00 format - - - - - 559bf494 by Patrick at 2025-03-05T14:25:19+00:00 remove NonStandardDefaultingStrategy and update Note [NoDefTauTv] - - - - - 73b1e0ca by Patrick at 2025-03-05T14:25:19+00:00 add DixC10 to T25647a - - - - - 9b7d53cd by Patrick at 2025-03-05T14:25:19+00:00 use TyVarTv for wildcard in HM_FamPat - - - - - b258c499 by Patrick at 2025-03-05T14:25:19+00:00 Revert "use TyVarTv for wildcard in HM_FamPat" This reverts commit 638d6763d0b972f3c9a0e2c4218d8c7ce34dc800. - - - - - 651f533e by Patrick at 2025-03-05T14:25:19+00:00 Add FamArgType to in AssocInstInfo to guide the create of tv for wildcard - - - - - f028b93d by Patrick at 2025-03-05T14:25:19+00:00 Fix mode args passing down - - - - - 5bf0dc58 by Patrick at 2025-03-05T14:25:19+00:00 Fix under application for data fam - - - - - 47968d71 by Patrick at 2025-03-05T14:25:19+00:00 use HM_Sig for (a :: _) in type family - - - - - 3cebfc7d by Patrick at 2025-03-05T14:25:19+00:00 add and use HM_FamSig for (a :: _) in type family - - - - - ae71f916 by Patrick at 2025-03-05T14:25:19+00:00 use TyVarTv instead of SkolemTv for freeArg `_`, since we also do not default TyVarTv in defaultTyVar and defaultTyVarTcS - - - - - ae358a14 by Patrick at 2025-03-05T14:25:19+00:00 Revert "add and use HM_FamSig for (a :: _) in type family" and use ClassArg for _ in (a :: _) in type family This reverts commit 9ab780da39c2afbce2411c2b96fef4108d6b8b70. - - - - - 38339d57 by Patrick at 2025-03-05T14:25:19+00:00 fix - - - - - 70df483e by Patrick at 2025-03-05T14:25:19+00:00 remove unused updateHoleMode function from TcTyMode - - - - - e97b35a1 by Patrick at 2025-03-05T14:25:19+00:00 flip the classVar to TyVarTv to observe any breakage - - - - - eca5806f by Patrick at 2025-03-05T14:25:19+00:00 fix - - - - - 27064980 by Patrick at 2025-03-05T14:25:19+00:00 disable DixC10 from T25647a - - - - - 3f10fdfb by Patrick at 2025-03-05T14:25:19+00:00 update ExplicitForAllFams4b - - - - - 44ed5333 by Patrick at 2025-03-05T14:25:19+00:00 cleanup NoDefTauTv - - - - - c25b0c36 by Patrick at 2025-03-05T14:25:19+00:00 move [FamArgFlavour] to tyCon - - - - - 07301c18 by Patrick at 2025-03-05T14:25:19+00:00 add note - - - - - 417af292 by Patrick at 2025-03-05T14:25:19+00:00 refactor documentation for FamArgFlavour and clean up comments - - - - - b87c353a by Patrick at 2025-03-05T14:25:19+00:00 enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging - - - - - 6cc1b70a by Patrick at 2025-03-05T14:25:19+00:00 Ensure wildcard behave correctly - - - - - 88ea2dc7 by Patrick at 2025-03-05T14:25:19+00:00 Revert "update ExplicitForAllFams4b" This reverts commit 90a2858278668bc6ad66ef43a5651808d8f24a0f. - - - - - 81517711 by Patrick at 2025-03-05T14:25:19+00:00 Add detailed notes on wildcard handling in type families and refine related documentation - - - - - 2b8048e6 by Patrick at 2025-03-05T14:25:19+00:00 Refine documentation on wildcard handling in type families and clarify design choices for FamArgFlavour - - - - - ea278d3c by Patrick at 2025-03-05T14:25:19+00:00 Fix typos in documentation regarding wildcards in type families and clarify references - - - - - e6d2ce3d by Patrick at 2025-03-05T14:25:19+00:00 Clarify wildcard handling in type families documentation and improve explanations for FamArgFlavour - - - - - 9163649e by Patrick at 2025-03-05T14:25:19+00:00 Enhance documentation on FamArgFlavour handling in type families and clarify implementation details in TyCon and HsType modules - - - - - 67cead12 by Patrick at 2025-03-05T14:25:19+00:00 format - - - - - 6e6ff507 by Patrick at 2025-03-05T14:25:19+00:00 Refactor documentation on wildcards in type families and clarify implementation details in TyCon, Rename, and HsType modules - - - - - 6893f1f2 by Patrick at 2025-03-05T14:25:19+00:00 Rename variable `famArgFlvs` to `fam_arg_flvs` for consistency in type inference functions - - - - - 84923367 by Patrick at 2025-03-05T14:25:19+00:00 Improve documentation on wildcard interpretation in type families, clarifying the relationship with class arguments and enhancing the explanation of FamArgFlavour categories. - - - - - ebed7dce by Patrick at 2025-03-05T14:25:19+00:00 Add comment to clarify implementation details for wildcards in family instances - - - - - 369 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.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/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Parser.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/wasm/JSFFI.c - testsuite/driver/testlib.py - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - + testsuite/tests/indexed-types/should_compile/T11450a.hs - testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod185.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23512a.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/all.T - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T25647_fail.hs - + testsuite/tests/typecheck/should_compile/T25647_fail.stderr - + testsuite/tests/typecheck/should_compile/T25647a.hs - + testsuite/tests/typecheck/should_compile/T25647b.hs - + testsuite/tests/typecheck/should_compile/T25647c.hs - + testsuite/tests/typecheck/should_compile/T25725.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f8b64564d411b8e688884257e7ddf100b0ed6aa6...ebed7dcec5f0b07ef821d694dc251fd37d64e3a2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f8b64564d411b8e688884257e7ddf100b0ed6aa6...ebed7dcec5f0b07ef821d694dc251fd37d64e3a2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/f1416e7a/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 15:07:31 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 10:07:31 -0500 Subject: [Git][ghc/ghc][wip/backports-9.10] Revert "hadrian: Bump directory bound to >=1.3.9" Message-ID: <67c868b3bb436_7e0a1a85b0-22f@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: 400cfabe by Ben Gamari at 2025-03-05T10:05:55-05:00 Revert "hadrian: Bump directory bound to >=1.3.9" This reverts commit 15ca7b2c06f9727b7a8c5ca663c3b6779489daa6 as it breaks bootstrapping with 9.8 and 9.6, where `directory-1.3.9` is not shipped. - - - - - 4 changed files: - .gitlab/ci.sh - hadrian/cabal.project - hadrian/hadrian.cabal - hadrian/stack.yaml Changes: ===================================== .gitlab/ci.sh ===================================== @@ -7,8 +7,7 @@ set -Eeuo pipefail # Configuration: -# N.B. You may want to also update the index-state in hadrian/cabal.project. -HACKAGE_INDEX_STATE="2025-02-03T15:14:19Z" +HACKAGE_INDEX_STATE="2024-05-13T15:04:38Z" MIN_HAPPY_VERSION="1.20" MAX_HAPPY_VERSION="1.21" # Exclusive upper bound MIN_ALEX_VERSION="3.2.6" ===================================== hadrian/cabal.project ===================================== @@ -3,7 +3,7 @@ packages: ./ ../libraries/ghc-platform/ -- This essentially freezes the build plan for hadrian --- It would be wise to keep this up to date with the state set in .gitlab/ci.sh. +-- It would be wise to keep this up to date with the state set in ci.sh index-state: 2025-02-03T15:14:19Z -- unordered-containers-0.2.20-r1 requires template-haskell < 2.22 ===================================== hadrian/hadrian.cabal ===================================== @@ -156,10 +156,7 @@ executable hadrian , base >= 4.11 && < 5 , bytestring >= 0.10 && < 0.13 , containers >= 0.5 && < 0.8 - - -- N.B. directory >=1.3.9 as earlier versions are - -- afflicted by #24382. - , directory >= 1.3.9.0 && < 1.4 + , directory >= 1.3.1.0 && < 1.4 , extra >= 1.4.7 , filepath , time ===================================== hadrian/stack.yaml ===================================== @@ -21,10 +21,3 @@ nix: extra-deps: - Cabal-3.10.1.0 - Cabal-syntax-3.10.1.0 - -# needed due to Hadrian's lower bound on directory - - directory-1.3.9.0 - - file-io-0.1.4 - - filepath-1.4.300.2 - - process-1.6.25.0 - - unix-2.8.5.1 \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/400cfabee02ee6b3c940e1657573c3e50222b27c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/400cfabee02ee6b3c940e1657573c3e50222b27c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/6519241a/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 15:36:09 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 10:36:09 -0500 Subject: [Git][ghc/ghc][wip/backports-9.10] gitlab-ci: Drop CentOS 7 binary distributions Message-ID: <67c86f69670f_18915152aac100ef@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: 24cd3827 by Ben Gamari at 2025-03-05T10:35:55-05:00 gitlab-ci: Drop CentOS 7 binary distributions CentOS 7 is EoL and moreover we cannot even build images for it. See #25061. - - - - - 3 changed files: - .gitlab/generate-ci/flake.lock - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml Changes: ===================================== .gitlab/generate-ci/flake.lock ===================================== @@ -5,11 +5,11 @@ "systems": "systems" }, "locked": { - "lastModified": 1687709756, - "narHash": "sha256-Y5wKlQSkgEK2weWdOu4J3riRd+kV/VCgHsqLNTTWQ/0=", + "lastModified": 1731533236, + "narHash": "sha256-l0KFg5HjrsfsO/JpG+r7fRrqm12kzFHyUHqHCVpMMbI=", "owner": "numtide", "repo": "flake-utils", - "rev": "dbabf0ca0c0c4bce6ea5eaf65af5cb694d2082c7", + "rev": "11707dc2f618dd54ca8739b309ec4fc024de578b", "type": "github" }, "original": { @@ -20,12 +20,10 @@ }, "nixpkgs": { "locked": { - "lastModified": 1687886075, - "narHash": "sha256-PeayJDDDy+uw1Ats4moZnRdL1OFuZm1Tj+KiHlD67+o=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "a565059a348422af5af9026b5174dc5c0dcefdae", - "type": "github" + "lastModified": 0, + "narHash": "sha256-OnSAY7XDSx7CtDoqNh8jwVwh4xNL/2HaJxGjryLWzX8=", + "path": "/nix/store/lv9bmgm6v1wc3fiz00v29gi4rk13ja6l-source", + "type": "path" }, "original": { "id": "nixpkgs", ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -113,7 +113,6 @@ data LinuxDistro | Fedora38 | Ubuntu2004 | Ubuntu1804 - | Centos7 | Alpine312 | Alpine318 | AlpineWasm @@ -293,7 +292,6 @@ distroName Fedora33 = "fedora33" distroName Fedora38 = "fedora38" distroName Ubuntu1804 = "ubuntu18_04" distroName Ubuntu2004 = "ubuntu20_04" -distroName Centos7 = "centos7" distroName Alpine312 = "alpine3_12" distroName Alpine318 = "alpine3_18" distroName AlpineWasm = "alpine3_18-wasm" @@ -445,10 +443,6 @@ alpineVariables = mconcat distroVariables :: LinuxDistro -> Variables distroVariables Alpine312 = alpineVariables distroVariables Alpine318 = alpineVariables -distroVariables Centos7 = mconcat [ - "HADRIAN_ARGS" =: "--docs=no-sphinx" - , "BROKEN_TESTS" =: "T22012" -- due to #23979 - ] distroVariables Fedora33 = mconcat -- LLC/OPT do not work for some reason in our fedora images -- These tests fail with this error: T11649 T5681 T7571 T8131b @@ -984,7 +978,6 @@ job_groups = , disableValidate (standardBuilds Amd64 (Linux Ubuntu1804)) , disableValidate (standardBuilds Amd64 (Linux Ubuntu2004)) , disableValidate (standardBuilds Amd64 (Linux Rocky8)) - , disableValidate (standardBuildsWithConfig Amd64 (Linux Centos7) (splitSectionsBroken vanilla)) -- Fedora33 job is always built with perf so there's one job in the normal -- validate pipeline which is built with perf. , fastCI (standardBuildsWithConfig Amd64 (Linux Fedora33) releaseConfig) ===================================== .gitlab/jobs.yaml ===================================== @@ -1207,70 +1207,6 @@ "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-centos7-validate": { - "after_script": [ - ".gitlab/ci.sh save_cache", - ".gitlab/ci.sh save_test_output", - ".gitlab/ci.sh clean", - "cat ci_timings" - ], - "allow_failure": false, - "artifacts": { - "expire_in": "8 weeks", - "paths": [ - "ghc-x86_64-linux-centos7-validate.tar.xz", - "junit.xml", - "unexpected-test-output.tar.gz" - ], - "reports": { - "junit": "junit.xml" - }, - "when": "always" - }, - "cache": { - "key": "x86_64-linux-centos7-$CACHE_REV", - "paths": [ - "cabal-cache", - "toolchain" - ] - }, - "dependencies": [], - "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV", - "needs": [ - { - "artifacts": false, - "job": "hadrian-ghc-in-ghci" - } - ], - "rules": [ - { - "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)", - "when": "on_success" - } - ], - "script": [ - "sudo chown ghc:ghc -R .", - ".gitlab/ci.sh setup", - ".gitlab/ci.sh configure", - ".gitlab/ci.sh build_hadrian", - ".gitlab/ci.sh test_hadrian" - ], - "stage": "full-build", - "tags": [ - "x86_64-linux" - ], - "variables": { - "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-validate", - "BROKEN_TESTS": "T22012", - "BUILD_FLAVOUR": "validate", - "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "HADRIAN_ARGS": "--docs=no-sphinx", - "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-centos7-validate", - "XZ_OPT": "-9" - } - }, "nightly-x86_64-linux-deb10-int_native-validate": { "after_script": [ ".gitlab/ci.sh save_cache", @@ -3433,71 +3369,6 @@ "XZ_OPT": "-9" } }, - "release-x86_64-linux-centos7-release+no_split_sections": { - "after_script": [ - ".gitlab/ci.sh save_cache", - ".gitlab/ci.sh save_test_output", - ".gitlab/ci.sh clean", - "cat ci_timings" - ], - "allow_failure": false, - "artifacts": { - "expire_in": "1 year", - "paths": [ - "ghc-x86_64-linux-centos7-release+no_split_sections.tar.xz", - "junit.xml", - "unexpected-test-output.tar.gz" - ], - "reports": { - "junit": "junit.xml" - }, - "when": "always" - }, - "cache": { - "key": "x86_64-linux-centos7-$CACHE_REV", - "paths": [ - "cabal-cache", - "toolchain" - ] - }, - "dependencies": [], - "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV", - "needs": [ - { - "artifacts": false, - "job": "hadrian-ghc-in-ghci" - } - ], - "rules": [ - { - "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)", - "when": "on_success" - } - ], - "script": [ - "sudo chown ghc:ghc -R .", - ".gitlab/ci.sh setup", - ".gitlab/ci.sh configure", - ".gitlab/ci.sh build_hadrian", - ".gitlab/ci.sh test_hadrian" - ], - "stage": "full-build", - "tags": [ - "x86_64-linux" - ], - "variables": { - "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-release+no_split_sections", - "BROKEN_TESTS": "T22012", - "BUILD_FLAVOUR": "release+no_split_sections", - "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "HADRIAN_ARGS": "--hash-unit-ids --docs=no-sphinx", - "IGNORE_PERF_FAILURES": "all", - "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-centos7-release+no_split_sections", - "XZ_OPT": "-9" - } - }, "release-x86_64-linux-deb10-release": { "after_script": [ ".gitlab/ci.sh save_cache", View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24cd3827a5fbec5f72f7c42264c7efe0890dc0ee -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24cd3827a5fbec5f72f7c42264c7efe0890dc0ee You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/b405f1f3/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 15:42:45 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 10:42:45 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/darwin-bootstrap-bump Message-ID: <67c870f5e1870_1891518d2ec102f5@gitlab.mail> Ben Gamari pushed new branch wip/darwin-bootstrap-bump at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/darwin-bootstrap-bump You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/2e521228/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 15:48:11 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 10:48:11 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ann-frame Message-ID: <67c8723b72602_189151911e4130a7@gitlab.mail> Ben Gamari pushed new branch wip/ann-frame at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ann-frame You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/76405927/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 15:54:09 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 10:54:09 -0500 Subject: [Git][ghc/ghc][wip/backports-9.10] gitlab-ci: Drop CentOS 7 binary distributions Message-ID: <67c873a1786e4_189151de0d41958c@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: 3057ebc4 by Ben Gamari at 2025-03-05T10:53:57-05:00 gitlab-ci: Drop CentOS 7 binary distributions CentOS 7 is EoL and moreover we cannot even build images for it. See #25061. - - - - - 4 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/flake.lock - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1143,8 +1143,6 @@ ghcup-metadata-nightly: needs: - job: nightly-x86_64-linux-fedora33-release artifacts: false - - job: nightly-x86_64-linux-centos7-validate - artifacts: false - job: nightly-x86_64-linux-ubuntu20_04-validate artifacts: false - job: nightly-x86_64-linux-ubuntu18_04-validate ===================================== .gitlab/generate-ci/flake.lock ===================================== @@ -5,11 +5,11 @@ "systems": "systems" }, "locked": { - "lastModified": 1687709756, - "narHash": "sha256-Y5wKlQSkgEK2weWdOu4J3riRd+kV/VCgHsqLNTTWQ/0=", + "lastModified": 1731533236, + "narHash": "sha256-l0KFg5HjrsfsO/JpG+r7fRrqm12kzFHyUHqHCVpMMbI=", "owner": "numtide", "repo": "flake-utils", - "rev": "dbabf0ca0c0c4bce6ea5eaf65af5cb694d2082c7", + "rev": "11707dc2f618dd54ca8739b309ec4fc024de578b", "type": "github" }, "original": { @@ -20,12 +20,10 @@ }, "nixpkgs": { "locked": { - "lastModified": 1687886075, - "narHash": "sha256-PeayJDDDy+uw1Ats4moZnRdL1OFuZm1Tj+KiHlD67+o=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "a565059a348422af5af9026b5174dc5c0dcefdae", - "type": "github" + "lastModified": 0, + "narHash": "sha256-OnSAY7XDSx7CtDoqNh8jwVwh4xNL/2HaJxGjryLWzX8=", + "path": "/nix/store/lv9bmgm6v1wc3fiz00v29gi4rk13ja6l-source", + "type": "path" }, "original": { "id": "nixpkgs", ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -113,7 +113,6 @@ data LinuxDistro | Fedora38 | Ubuntu2004 | Ubuntu1804 - | Centos7 | Alpine312 | Alpine318 | AlpineWasm @@ -293,7 +292,6 @@ distroName Fedora33 = "fedora33" distroName Fedora38 = "fedora38" distroName Ubuntu1804 = "ubuntu18_04" distroName Ubuntu2004 = "ubuntu20_04" -distroName Centos7 = "centos7" distroName Alpine312 = "alpine3_12" distroName Alpine318 = "alpine3_18" distroName AlpineWasm = "alpine3_18-wasm" @@ -445,10 +443,6 @@ alpineVariables = mconcat distroVariables :: LinuxDistro -> Variables distroVariables Alpine312 = alpineVariables distroVariables Alpine318 = alpineVariables -distroVariables Centos7 = mconcat [ - "HADRIAN_ARGS" =: "--docs=no-sphinx" - , "BROKEN_TESTS" =: "T22012" -- due to #23979 - ] distroVariables Fedora33 = mconcat -- LLC/OPT do not work for some reason in our fedora images -- These tests fail with this error: T11649 T5681 T7571 T8131b @@ -984,7 +978,6 @@ job_groups = , disableValidate (standardBuilds Amd64 (Linux Ubuntu1804)) , disableValidate (standardBuilds Amd64 (Linux Ubuntu2004)) , disableValidate (standardBuilds Amd64 (Linux Rocky8)) - , disableValidate (standardBuildsWithConfig Amd64 (Linux Centos7) (splitSectionsBroken vanilla)) -- Fedora33 job is always built with perf so there's one job in the normal -- validate pipeline which is built with perf. , fastCI (standardBuildsWithConfig Amd64 (Linux Fedora33) releaseConfig) ===================================== .gitlab/jobs.yaml ===================================== @@ -1207,70 +1207,6 @@ "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-centos7-validate": { - "after_script": [ - ".gitlab/ci.sh save_cache", - ".gitlab/ci.sh save_test_output", - ".gitlab/ci.sh clean", - "cat ci_timings" - ], - "allow_failure": false, - "artifacts": { - "expire_in": "8 weeks", - "paths": [ - "ghc-x86_64-linux-centos7-validate.tar.xz", - "junit.xml", - "unexpected-test-output.tar.gz" - ], - "reports": { - "junit": "junit.xml" - }, - "when": "always" - }, - "cache": { - "key": "x86_64-linux-centos7-$CACHE_REV", - "paths": [ - "cabal-cache", - "toolchain" - ] - }, - "dependencies": [], - "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV", - "needs": [ - { - "artifacts": false, - "job": "hadrian-ghc-in-ghci" - } - ], - "rules": [ - { - "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)", - "when": "on_success" - } - ], - "script": [ - "sudo chown ghc:ghc -R .", - ".gitlab/ci.sh setup", - ".gitlab/ci.sh configure", - ".gitlab/ci.sh build_hadrian", - ".gitlab/ci.sh test_hadrian" - ], - "stage": "full-build", - "tags": [ - "x86_64-linux" - ], - "variables": { - "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-validate", - "BROKEN_TESTS": "T22012", - "BUILD_FLAVOUR": "validate", - "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "HADRIAN_ARGS": "--docs=no-sphinx", - "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-centos7-validate", - "XZ_OPT": "-9" - } - }, "nightly-x86_64-linux-deb10-int_native-validate": { "after_script": [ ".gitlab/ci.sh save_cache", @@ -3433,71 +3369,6 @@ "XZ_OPT": "-9" } }, - "release-x86_64-linux-centos7-release+no_split_sections": { - "after_script": [ - ".gitlab/ci.sh save_cache", - ".gitlab/ci.sh save_test_output", - ".gitlab/ci.sh clean", - "cat ci_timings" - ], - "allow_failure": false, - "artifacts": { - "expire_in": "1 year", - "paths": [ - "ghc-x86_64-linux-centos7-release+no_split_sections.tar.xz", - "junit.xml", - "unexpected-test-output.tar.gz" - ], - "reports": { - "junit": "junit.xml" - }, - "when": "always" - }, - "cache": { - "key": "x86_64-linux-centos7-$CACHE_REV", - "paths": [ - "cabal-cache", - "toolchain" - ] - }, - "dependencies": [], - "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV", - "needs": [ - { - "artifacts": false, - "job": "hadrian-ghc-in-ghci" - } - ], - "rules": [ - { - "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)", - "when": "on_success" - } - ], - "script": [ - "sudo chown ghc:ghc -R .", - ".gitlab/ci.sh setup", - ".gitlab/ci.sh configure", - ".gitlab/ci.sh build_hadrian", - ".gitlab/ci.sh test_hadrian" - ], - "stage": "full-build", - "tags": [ - "x86_64-linux" - ], - "variables": { - "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-release+no_split_sections", - "BROKEN_TESTS": "T22012", - "BUILD_FLAVOUR": "release+no_split_sections", - "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "HADRIAN_ARGS": "--hash-unit-ids --docs=no-sphinx", - "IGNORE_PERF_FAILURES": "all", - "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-centos7-release+no_split_sections", - "XZ_OPT": "-9" - } - }, "release-x86_64-linux-deb10-release": { "after_script": [ ".gitlab/ci.sh save_cache", View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3057ebc455c2aab5a5c854b5c9964273df2ca87f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3057ebc455c2aab5a5c854b5c9964273df2ca87f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/480feaa9/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 15:59:12 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 10:59:12 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/drop-centos Message-ID: <67c874d08a972_189151911e4235d9@gitlab.mail> Ben Gamari pushed new branch wip/drop-centos at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/drop-centos You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/46dca0e1/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 17:19:20 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 05 Mar 2025 12:19:20 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/wasm-prim-improve Message-ID: <67c887987fca3_4cf02f82f029553@gitlab.mail> Cheng Shao deleted branch wip/wasm-prim-improve at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/e185a292/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 17:19:49 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 05 Mar 2025 12:19:49 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/cross-fix-docs Message-ID: <67c887b51c36b_4cf02c5da029749@gitlab.mail> Cheng Shao deleted branch wip/cross-fix-docs at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/fab28092/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 17:20:26 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 05 Mar 2025 12:20:26 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/fix-cross-ghc-heap Message-ID: <67c887dae9416_4cf0234eab829930@gitlab.mail> Cheng Shao deleted branch wip/fix-cross-ghc-heap at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/a3a8733d/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 18:48:19 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 13:48:19 -0500 Subject: [Git][ghc/ghc][wip/T25560] users guide: Fix typo Message-ID: <67c89c73f120c_74b7b14a9c4923a4@gitlab.mail> Ben Gamari pushed to branch wip/T25560 at Glasgow Haskell Compiler / GHC Commits: 8cd73648 by Ben Gamari at 2025-03-05T18:48:17+00:00 users guide: Fix typo - - - - - 1 changed file: - docs/users_guide/using-concurrent.rst Changes: ===================================== docs/users_guide/using-concurrent.rst ===================================== @@ -157,7 +157,7 @@ use the RTS :rts-flag:`-N ⟨x⟩` options. .. note:: The maximum number of capabilities supported by the GHC runtime system is - determined when at RTS startup to be either 256, the value given by + determined at RTS startup to be either 256, the value given by :rts-flag:`-N ⟨x⟩`, or the number of logical CPU cores, whichever is greater. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8cd73648fb9cd406956d0f05b7bf40cf80021984 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8cd73648fb9cd406956d0f05b7bf40cf80021984 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/ec8827fa/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 18:48:58 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 13:48:58 -0500 Subject: [Git][ghc/ghc][wip/T25560] 224 commits: Add missing @since documentation for (!?) function Message-ID: <67c89c9ae2208_74b7bc5d009414e@gitlab.mail> Ben Gamari pushed to branch wip/T25560 at Glasgow Haskell Compiler / GHC Commits: a83b7ed6 by Matthew Stephenson at 2024-12-10T14:01:22-05:00 Add missing @since documentation for (!?) function - - - - - e745e3a3 by Ben Gamari at 2024-12-10T14:01:59-05:00 compiler: Don't attempt to TSAN-instrument SIMD operations TSAN only provides instrumentation for 8, 16, 32, and 64-bit memory loads/stores. Don't attempt to instrument wider operations. Fixes #25563. - - - - - 684c0018 by Ben Gamari at 2024-12-10T14:02:35-05:00 gitlab/ci: Don't clobber RUNTEST_ARGS Previously the logic handling `IGNORE_PERF_FAILURES` clobbered the user's `RUNTEST_ARGS`. Fix this. - - - - - 41dae5b8 by Ben Gamari at 2024-12-10T14:03:11-05:00 hadrian: Mitigate mktexfmt race At least some versions of Texlive's `mktexfmt` utility cannot be invoked concurrently in their initial run since they fail to handle failure of `mkdir` due to racing. Specifically, we see ``` | Run Xelatex: users_guide.tex => /tmp/extra-dir-9616886274866 | Run Xelatex: Haddock.tex => /tmp/extra-dir-9616886274869 This is XeTeX, Version 3.14159265-2.6-0.999992 (TeX Live 2020) (preloaded format=xelatex) restricted \write18 enabled. kpathsea: Running mktexfmt xelatex.fmt mktexfmt: mktexfmt is using the following fmtutil.cnf files (in precedence order): mktexfmt: /usr/share/texlive/texmf-dist/web2c/fmtutil.cnf mktexfmt: mktexfmt is using the following fmtutil.cnf file for writing changes: mktexfmt: /builds/ghc/ghc/tmp-home/.texlive2020/texmf-config/web2c/fmtutil.cnf /usr/bin/mktexfmt: mkdir(/builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c/) failed for tree /builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c: File exists at /usr/share/texlive/tlpkg/TeXLive/TLUtils.pm line 937. I can't find the format file `xelatex.fmt'! ``` That is two `mktexfmt` invocations (for the user's guide and haddock builds) attempted to create `$HOME/texlive2020/texmf-var/web2c` and raced. One of the two `mkdir`'s consequently failed, bringing down the entire build. We avoid this by ensuring that the first `xelatex` invocation is always performed serially. Fixes #25564. - - - - - 9efbc51f by Ben Gamari at 2024-12-10T14:03:48-05:00 rts/CheckUnload: Reset old_objects if unload is skipped Previously `checkUnload` failed to reset `old_objects` when it decided not to unload (e.g. due to heap profiling being enabled). Fixes #24935. - - - - - 5192a75f by Ben Gamari at 2024-12-11T04:28:11-05:00 rts: Annotate BCOs with their Name This introduces a new bytecode instruction, `BCO_NAME`, to aid in debugging bytecode execution. This instruction is injected by `mkProtoBCO` and captures the Haskell name of the BCO. It is then printed by the disassembler, allowing ready correlation with STG dumps. - - - - - 99225996 by Ben Gamari at 2024-12-11T04:28:48-05:00 configure: Implement ld override whitelist Bring `configure` into alignment with `ghc-toolchain`, ensuring that the ld-override logic will only take effect on Linux and Windows. Fixes #25501. - - - - - 4a8fc928 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Unmark T14028 as broken on FreeBSD This now appears to pass on FreeBSD 14. Closes #19723. - - - - - d7c0eb5a by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Migrate FreeBSD runner tag to FreeBSD 14 - - - - - 7246dacc by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Reintroduce FreeBSD 14 job - - - - - 4af936da by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Allow use of newer cabal-install bindists Newer cabal-install bindists have internal directory structure. Here we detect and account for the presence of such structure. - - - - - cbf38c1b by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Enable documentation build on FreeBSD 14 - - - - - d68107fb by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Use system libffi on FreeBSD - - - - - fea3b590 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark linker_unload as broken on FreeeBSD Due to #25491. - - - - - ccf171ee by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Prefer system toolchain on FreeBSD It's not uncommon to find machines with gcc installed via ports. We should be using the system's default clang-based toolchain instead. - - - - - cfb34738 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T21969 as broken on FreeBSD Due to #25512. - - - - - 0b64e37c by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark RestartEventLogging as broken on FreeBSD I am seeing this fail quite reproducibly. Due to #19724. - - - - - 3b412019 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T16180 as "broken" on FreeBSD Sadly we in fact need to skip it as it merely times out during compilation. See #14012. - - - - - 57e3cab5 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Skip T16992 unless in slow speed This test has extraordinary memory requirements and tests a rather niche aspect of the compact region mechanism. It has been suggested multiple times that we shouldn't run it in the default testsuite configuration. Finally implement this. See #21890. See #21892. - - - - - f08a72eb by Ben Gamari at 2024-12-11T19:30:54-05:00 rts(setNumCapabilities): Assert that n_caps < MAX_N_CAPS It was noticed in #25560 that this would previously be allowed, resulting in a segfault. I will add a proper exception in `base` in a future commit. - - - - - e10d31ad by Ben Gamari at 2024-12-11T19:30:55-05:00 ghc-internal: Fix inconsistent FFI import types The foreign imports of `enabled_capabilities` and `getNumberOfProcessors` were declared as `CInt` whereas they are defined as `uint32_t`. - - - - - 06265655 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Mention maximum capability count in users guide Addresses #25560. - - - - - d488470b by Ben Gamari at 2024-12-11T19:30:55-05:00 rts/Capability: Move induction variable declaration into `for`s Just a stylistic change. - - - - - 71f050b7 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Determine max_n_capabilities at RTS startup Previously the maximum number of capabilities supported by the RTS was statically capped at 256. However, this bound is uncomfortably low given the size of today's machine. While supporting unbounded, fully-dynamic adjustment would be nice, it is complex and so instead we do something simpler: Probe the logical core count at RTS startup and use this as the static bound for the rest of our execution. This should avoid users running into the capability limit on large machines while avoiding wasting memory on a large capabilities array for most users and keeping complexity at bay. Addresses #25560. - - - - - 1e84b411 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Introduce req_c_rts As suggested by @hsyl20, this is intended to mark tests that rely on the behavior of the C RTS. - - - - - 683115a4 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Add test for #25560 - - - - - ef2052a8 by Ben Gamari at 2024-12-12T04:42:32-05:00 testsuite: Only run T14497_compact in normal way This test targets the compacting GC so it makes little sense to run it across all ways. Moreover, it outright conflicts with the `nonmoving` way. - - - - - 34d3e8e6 by Ben Gamari at 2024-12-12T04:43:08-05:00 rts/CheckUnload: Don't prepare to unload if we can't unload Previously `prepareUnloadCheck` would move the `objects` list to `old_objects` even when profiling (where we cannot unload). This caused us to vacate the `objects` list during major GCs, losing track of loaded objects. Fix this by ensuring that `prepareUnloadCheck` and `checkUnload` both use the same short-cutting logic. - - - - - 9c53489d by Andrei Borzenkov at 2024-12-12T15:06:42-05:00 Update GHCi :info type declaration printing (#24459) - Do not print result's kind in type families because we have full kind in SAKS and we display invisible arity using @-binders - Do not suppress significant invisible binders An invisible binder is considered significant when it meets at least one of the following two criteria: - It visibly occurs in the declaration's body - It is followed by a significant binder, so it affects positioning For non-generative type declarations (type synonyms and type families) there is one additional criterion: - It is not followed by a visible binder, so it affects the arity of a type synonym See Note [Print invisible binders in interface declarations] for more information about what is "visibly occurs" - - - - - 13fe48d4 by Matthew Pickering at 2024-12-12T15:07:19-05:00 typechecker: Perform type family consistency checks in topological order Consider a module M importing modules A, B and C. We can waste a lot of work depending on the order that the modules are checked for family consistency. Consider that C imports A and B. When compiling C we must have already checked A and B for consistency, therefore if C is processed first then A and B will not need to be checked for consistency again. If A and B are compared first, then the consistency checks will be performed against (wasted as we already performed them for C). At the moment the order which modules are checked is non-deterministic. Clearly we should engineer that C is checked before B and A, but by what scheme? A simple one is to observe that if a module M is in the transitive closure of X then the size of the consistent family set of M is less than or equal to size of the consistent family set of X. Therefore by sorting the imports by the size of the consistent family set and processing the largest first, you make sure to process modules in topological order. In practice we have observed that this strategy has reduced the amount of consistency checks performed. One solution to #25554 - - - - - 62a2b25f by Sylvain Henry at 2024-12-14T04:31:09-05:00 TNTC: set CmmProc entry_label properly (#25565) Before this patch we were renaming the entry label of a CmmProc late in the CmmToAsm pass. It led to inconsistencies and to some labels being used in info tables but not being emitted (#25565). Now we set the CmmProc entry label earlier in the StgToCmm monad and we don't renamed it afterwards. - - - - - b339e7c3 by Simon Hengel at 2024-12-14T04:31:47-05:00 Make filter functionality for system tools line-based This is more efficient as: - All existing filter functions were line-based anyway. They broke up the input into lines and then joined it back together. - We already break up the output from system tools into lines when processing it. Splitting up the output of system tools once and then filtering and processing it reduces both code and runtime complexity. - - - - - 39669077 by Simon Hengel at 2024-12-14T04:31:47-05:00 Refactoring: Don't use a `Chan` when parsing SysTools output - - - - - 64756530 by Simon Peyton Jones at 2024-12-14T22:28:04-05:00 Tidy up the handling of `assert` Fixes #25493 - - - - - 8658fbc1 by Rodrigo Mesquita at 2024-12-14T22:28:41-05:00 base: displayException for SomeAsyncException Provide a better implementation of `SomeException` for `SomeAsyncException`. The previous, implicit, implementation, would not use the `displayException` of the exception wrapped by `SomeAsyncException`. Implements CLC-Proposal#309 Closes #25513 - - - - - 2d3a0a70 by ARATA Mizuki at 2024-12-15T18:35:30-05:00 LLVM: When emitting a vector literal with ppTypeLit, include the type information Fixes #25561 - - - - - bfacc086 by Simon Peyton Jones at 2024-12-15T18:36:05-05:00 Fix signature lookup in instance declarations This fixes a bug introduced by the fix to #16610 - - - - - 80f0e02d by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Improve GHC build times Two small changes * In GHC.Data.Unboxed, never omit interface pragmas. In "fast builds" one might omit them generally, but doing so gives very bad performance for code that imports this module. * In GHC.Hs.Dump don't do type-class specialisation. For some reason it goes mad and generates vast amounts of useless code. See #25463. - - - - - 175a1355 by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Refactor Lint Refactor Lint for two reasons: * To improve performance * To prepare for type-lets The big changes are all in GHC.Core.Lint: * Change the main APIs: * `lintType` returns nothing rather than returning a `LintedType`; * `lintCoercion` return nothing rather than returning a `LintedCoercion` Reason: these functions did a lot of allocation to return a substituted type/coercion that was often discarded, or used only to extract its kind. Instead we now return nothing, and, when needed, extract the kind and substitute. * Applications are treated as a whole, by `lintApp`. By treating multiple arguments all at once we avoid performing multiple substitutions, each substituting a single type variable. This can make an absolutely huge difference. Overall this led to a pretty massive rewrite of Lint, with many smaller changes. Smaller chnages elsewhere * Rename `GHC.Core.TyCo.Subst.getSubstInScope` to `substInScopeSet` for consistency * Define and use `GHC.Core.Type.liftedTypeOrConstraintKind` Performance. This MR someimtes gives gives a very large improvement in compile time, when Lint is on. here is a selection of changes over 5% in perf/compiler (with -dcore-lint) T25196 -97.0% T14766 -89.7% T14683 -74.4% T5631 -60.9% T20261 -56.7% T18923 -17.6% T13035 -15.8% T6048 -15.8% CoOpt_Read -14.4% T9630 -10.9% T5642 -7.3% Eliminating the egregious offenders is a big win. However, in some cases the compiler allocation /increases/. Here ae the changes over 1%: T9961 1.5% T8095 2.8% T14052 3.9% T12545 4.5% T14052Type 5.5% T5030 8.0% T5321Fun 8.3% T3064 12.7% CoOpt_Singletons 15.6% T9198 16.0% LargeRecord 18.1% I looked at the two biggest increases in compile-time bytes allocated. Interestingly, they both show substantial *decreases* in actual compile time, due to much smaller GC times. I'm honestly not sure either why the allocation increases, or why the GC time decreases; but I'm going to take the win! T9198 Baseline With patch No Lint Alloc 44.6M 44.6M Mut time 0.23s 0.22s GC time 0.21s 0.21s With Lint Alloc 309M 360M Mut time 1.51s 0.85s GC time 2.97s 0.25s ------------------- LargeRecord Baseline With patch No Lint Alloc 1.37G 1.37G Mut time 2.33s 2.33s GC time 2.40s 2.42s With Lint Alloc 3.4G 4.0G Mut time 6.02s 5.68s GC time 3.67s 3.03s IMPORTANT NOTE: These changes don't show up in CI because in CI the tests in perf/compiler are all run with -dcore-lint switched off. I gathered this data with some manual runs. - - - - - 8ef2dad6 by Simon Peyton Jones at 2024-12-17T02:48:09-05:00 Add Note [Typechecking overloaded literals] See #25494. - - - - - e86b1b20 by Ben Gamari at 2024-12-17T13:51:39-05:00 testsuite: Use math.inf instead of division-by-zero This both more directly captures the intent and also fixes #25580. - - - - - 430d965a by Ben Gamari at 2024-12-17T13:52:15-05:00 rts: Fix incorrect format specifiers in era profiling Fixes #25581. - - - - - 267098ad by Andreas Klebinger at 2024-12-18T23:43:13-05:00 Document `-prof` and non `-prof` code being incompatible. Fixes #25518. - - - - - 04433916 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: output metadata fragment in CI (cherry picked from commit 52b58a660e735b20961d792d8fa9267f01247a50) - - - - - 7c78804e by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metatdata: use fedora33 for redhat Redhat 9 doesn't have libtinfo.so.5 anymore (cherry picked from commit dc86785eb43afd1bd292287c064fb5ad94fe8c7f) - - - - - 1d72cfb2 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: still use centos for redhat <9 - - - - - 3f7ebc58 by Sylvain Henry at 2024-12-19T20:40:14-05:00 Merge ghc-bignum into ghc-internal (#24453) First step towards merging ghc-bignum and ghc-prim into ghc-internal. After this patch, ghc-bignum is deprecated and is just a shallow package reexporting modules from ghc-internal and base. Use those directly instead. Move `gmp` submodule into ghc-internal directory. - - - - - ee0150c2 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Improve performance of deriving Show Significantly improves performance of deriving Show instances by avoiding using the very polymorphic `.` operator in favour of inlining its definition. We were generating tons of applications of it, each which had 3 type arguments! Improves on #9557 ------------------------- Metric Decrease: InstanceMatching T12707 T3294 ------------------------ - - - - - 8b266671 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Don't eta expand cons when deriving Data This eta expansion was introduced with the initial commit for Linear types. I believe this isn't needed any longer. My guess is it is an artifact from the initial linear types implementation: data constructors are linear, but they shouldn't need to be eta expanded to be used as higher order functions. I suppose in the early days this wasn't true. For instance, this works now: data T x = T x f = \(x :: forall y. y -> T y) -> x True f T -- ok! T is linear, but can be passed where an unrestricted higher order function is expected. I recall there being some magic around to make this work for data constructors... Since this works, there's no need to eta_expand the data constructors in the derived Data instances. - - - - - 1f67ad21 by Andrei Borzenkov at 2024-12-25T01:42:31-05:00 Flip the order of arguments of setField (#24668) GHC Proposal 583 "HasField redesign" specifies the following order of a setField function arguments as this: setField :: forall fld a b. SetField fld a b. b -> a -> a This patch flips the application order to match the spec. - - - - - 3e0c948d by Ben Gamari at 2024-12-25T01:43:08-05:00 rel-eng/upload: Add set_symlink mode This slightly eases updating of the `latest` symlinks. - - - - - 63d63f9d by Simon Peyton Jones at 2024-12-25T01:43:45-05:00 Preserve orientation when unifying kinds This MR fixes yet another manifestation of the trickiness caused by Note [Fundeps with instances, and equality orientation]. I wish there was a more robust way to do this, but this fix is a definite improvement. Fixes #25597 - - - - - 94ba9a6a by ARATA Mizuki at 2024-12-26T10:47:57-05:00 x86 NCG SIMD: Support pack/insert/broadcast/unpack of 128-bit integer vectors - - - - - 6bf0d587 by Andrew Lelechenko at 2024-12-26T10:48:33-05:00 docs: fix haddock formatting in Control.Monad.Fix - - - - - feb14af1 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Remove unnecessary irrefutable patterns from NonEmpty functions Implementation of https://github.com/haskell/core-libraries-committee/issues/107 - - - - - 6a0d91b4 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Make cons, Semigroup, IsList, and Monad instances stricter - - - - - 1249e597 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Restore some laziness in <| and Semigroup instance, improve Monad instance The Monad instance shouldn't produce the outer :| unless f a reduces to WHNF. (Notice that the b :| bs match is implicitly lazy.) - - - - - 8699d826 by Sergey Vinokurov at 2024-12-27T15:12:30+00:00 Add comment outlining Data.List.NonEmpty implementation guiding principles - - - - - 7febe00e by Sergey Vinokurov at 2024-12-27T22:24:43+00:00 Fix tests since location of ‘>>=’ changed - - - - - a928c326 by ARATA Mizuki at 2024-12-28T03:06:14-05:00 Fix LLVM version detection With a recent LLVM, `llc -version` emits the version on the first line if the vendor is set. It emits the version on the second line otherwise. Therefore, we need to check the both lines to detect the version. GHC now emits a warning if it fails to detect the LLVM version, so we can notice if the output of `llc -version` changes in the future. Also, the warning for using LLVM < 10 on s390x is removed, because we assume LLVM >= 13 now. This fixes the definition of __GLASGOW_HASKELL_LLVM__ macro. Fixes #25606 - - - - - 7f79257a by Zubin Duggal at 2024-12-29T13:04:35+00:00 Bump base, ghc-prim and template-haskell versions for 9.12 Also bump various submodules. (cherry picked from commit 6fc1fa3bdc8f53acdb19e47145789274060e498f) Bump base bound to 4.21 for GHC 9.12 (cherry picked from commit 473a201c6b55aea5bf9c9db0836a66ea1b657e04) Bump binary submodule to 0.8.9.2 (cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20) (cherry picked from commit ec2f40b45c1a3d82d17a2fc07e9ddb9218bc3940) Bump exceptions submodule to 0.10.9 (cherry picked from commit f5b5d1dc2d326368e5b173d622630d77f019b629) Bump file-io submodule to 0.1.4 (cherry picked from commit ba786681de6ac5fa49938e2cd71a5988f0f40d1f) bump os-string submodule to 2.0.6 (cherry picked from commit 3a7ffdbb832c045a55fd1ef24f546abdd9d9e30f) bump transformers submodule to 0.6.1.2 (cherry picked from commit 53b46fd437421b9e5a001edc6d1c427439d7714f) Bump directory submodule to v1.3.9.0 (cherry picked from commit 27dc2664c5404bb462092bb216c2c37b418fd1f8) Bump Win32 submodule to v2.14.1.0 (cherry picked from commit 80df88086180f5e39212b2feacf70a9d2b263c6c) Bump filepath submodule to 1.5.3.0 (cherry picked from commit 29bfae2c58a7303a081a6e7956b9f55e5faf3eeb) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 97b0dff223a6c4cc003adec448104c277f214645) Bump unix submodule to 2.8.6.0 (cherry picked from commit a1f56d6d6a99c100f88ef0a8b4d51298cf24a42d) Bump os-string submodule to 2.0.8 (cherry picked from commit 0121b76fd52ea0c0ce5d07085bc195666b63c625) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 962ceb50c8a6fc370e1c0a267f5cd5562a8cf759) Bump filepath submodule to 1.5.4.0 (cherry picked from commit 7bc6877fd5d41c6d5900678ad5e73ed30f366569) Bump file-io submodule to 0.1.5 (cherry picked from commit 9478b5aefe2877d58baf527edcf936dddbb955b7) Bump Cabal submodule to 3.14.1.0 (cherry picked from commit 5c9c3e3f79a79bb6d9a77a17c716dc3a0bcbd2aa) Bump directory submodule to 0.12.2.0 (cherry picked from commit 897906265db37af34ae2aaa016cec417f263407b) Bump array submodule for base bump Bump stm submodule for base bump Bump process submodule for base bump - - - - - f6079408 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix ghc-e005 after HasCallstack changes (cherry picked from commit 77f340a24561cea8a6f2ada296b3ea356ab1823c) - - - - - 3e10fa75 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Add haskeline to stage0Packages Otherwise we link against boot inplace and boot unix as boot haskeline depends on boot unix. (cherry picked from commit 90b493769ebdf3cd7be404d18462dc20ac1044df) - - - - - 4ad6aec4 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix TH changelog - - - - - ea3f7fd5 by Zubin Duggal at 2024-12-29T13:04:35+00:00 release: copy index.html from correct directory (cherry picked from commit cbfd0829cd61928976c9eb17ba4af18272466063) - - - - - fafb70db by Zubin Duggal at 2024-12-29T13:04:35+00:00 hadrian-multi: warn on unused imports os-string has redundant imports (cherry picked from commit dde3796be689ea57543936e22aa5ea4ef7ed995e) - - - - - c02b1e46 by Simon Peyton Jones at 2024-12-29T17:04:30-05:00 Fix in-scope set for CSE Ticket #25468 showed an assertion failure in CSE because a top-level Id was being used before it was defined. Reason: Note [Glomming] in GHC.Core.Opt.OccurAnal. Solution (used in many places): just put all the top-level bindings in scope at the beginning of CSE. Compile-time allocation wobbles up and down a tiny bit; geo mean is zero. But MultiLayerModulesTH_OneShot and hard_hole_fits increase (on some architectures only) by a bit oever 2% . I think these are just a random fluctuations. Metric Increase: MultiLayerModulesTH_OneShot hard_hole_fits - - - - - 559d4f84 by Krzysztof Gogolewski at 2024-12-30T11:53:19-05:00 Add tests for #23883 The issue has been fixed by commit f5d3e03c56ffc63. Only T23883a is the actual regression test, the remaining ones are tricky cases found during development of an independent fix !11313. - - - - - 278a53ee by Sergey Vinokurov at 2024-12-30T11:53:59-05:00 Update changelog for CLC proposal #107 (NonEmpty laziness) - - - - - f56558be by Matthew Pickering at 2025-01-07T13:53:03-05:00 warnings: Find out if a qualified name is in the interactive scope directly There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600 - - - - - 84155cdb by Simon Peyton Jones at 2025-01-07T13:53:40-05:00 Tidy up kcConDecls Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types - - - - - 6c12b6cf by Bryan Richter at 2025-01-07T18:15:02-05:00 Remove tmp files after toolchain check Fixes #25620 - - - - - 42826a89 by Cheng Shao at 2025-01-07T18:15:39-05:00 xxhash: bump to v0.8.3 - - - - - 185f17e4 by sheaf at 2025-01-07T18:16:15-05:00 Fix typo in GHC.Tc.Solver.Solve.runTcPluginsWanted - - - - - 23099752 by Luite Stegeman at 2025-01-08T00:33:33+01:00 Add flags for switching off speculative evaluation. We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284 - - - - - 0161badc by Ben Gamari at 2025-01-09T17:30:05-05:00 rts/printClosure: Print IPE information for thunks and functions This makes it considerably easier to grok the structure of the heap when IPE information is available. - - - - - 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz GoÅ›linowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-â” |---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | â””-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - c561105b by Ben Gamari at 2025-03-05T18:48:51+00:00 users guide: Fix typo - - - - - 1500 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload.sh - .gitlab/rel_eng/upload_ghc_libs.py - .gitmodules - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/Unboxed.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Config/CoreToStg/Prep.hs - compiler/GHC/Driver/Config/Linker.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Config.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Llvm/Ppr.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Info.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/cbits/genSym.c - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/debugging.rst - docs/users_guide/diagnostics-as-json-schema-1_0.json - docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/expected-undocumented-flags.txt - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/overloaded_record_update.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/profiling.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/wasm.rst - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/bindist/Makefile - hadrian/cabal.project - hadrian/cfg/system.config.in - hadrian/src/CommandLine.hs - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Warnings.hs - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/array - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Control/Monad/Fix.hs - libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/Data/Semigroup.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Exts.hs - + libraries/base/src/GHC/Num/BigNat.hs - + libraries/base/src/GHC/Num/Integer.hs - + libraries/base/src/GHC/Num/Natural.hs - libraries/base/src/System/Timeout.hs - libraries/binary - libraries/bytestring - libraries/deepseq - libraries/directory - libraries/exceptions - libraries/file-io - libraries/filepath - − libraries/ghc-bignum/.gitignore - + libraries/ghc-bignum/Dummy.hs - − libraries/ghc-bignum/Setup.hs - − libraries/ghc-bignum/aclocal.m4 - libraries/ghc-bignum/changelog.md - − libraries/ghc-bignum/config.mk.in - − libraries/ghc-bignum/configure.ac - − libraries/ghc-bignum/ghc-bignum.buildinfo.in - libraries/ghc-bignum/ghc-bignum.cabal - − libraries/ghc-bignum/install-sh - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-compact/tests/all.T - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-experimental/src/Data/Sum/Experimental.hs - libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/stack_big_ret.hs - libraries/ghc-internal/.gitignore - libraries/ghc-internal/aclocal.m4 - libraries/ghc-bignum/README.rst → libraries/ghc-internal/bignum-backend.rst - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-bignum/cbits/gmp_wrappers.c → libraries/ghc-internal/cbits/gmp_wrappers.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/ghc-internal/configure.ac - libraries/ghc-internal/ghc-internal.buildinfo.in - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-bignum/GMP.rst → libraries/ghc-internal/gmp-backend.rst - libraries/ghc-bignum/gmp/ghc-gmp.h → libraries/ghc-internal/gmp/ghc-gmp.h - libraries/ghc-bignum/gmp/gmp-tarballs → libraries/ghc-internal/gmp/gmp-tarballs - libraries/ghc-bignum/include/HsIntegerGmp.h.in → libraries/ghc-internal/include/HsIntegerGmp.h.in - libraries/ghc-bignum/include/WordSize.h → libraries/ghc-internal/include/WordSize.h - libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-bignum/src/GHC/Num/Backend.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Check.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - libraries/ghc-bignum/src/GHC/Num/Backend/FFI.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Native.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Selected.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Selected.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - libraries/ghc-bignum/src/GHC/Num/Integer.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-bignum/src/GHC/Num/Integer.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - libraries/ghc-bignum/src/GHC/Num/Natural.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-bignum/src/GHC/Num/Natural.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - libraries/ghc-bignum/src/GHC/Num/Primitives.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-bignum/src/GHC/Num/WordArray.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - libraries/ghc-internal/src/GHC/Internal/Char.hs - libraries/ghc-prim/GHC/Classes.hs → libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - libraries/ghc-internal/src/GHC/Internal/Err.hs - libraries/ghc-internal/src/GHC/Internal/Event.hs - libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Float/ConversionUtils.hs - libraries/ghc-internal/src/GHC/Internal/Float/RealFracMethods.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - libraries/ghc-internal/src/GHC/Internal/Generics.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Int.hs - libraries/ghc-internal/src/GHC/Internal/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - libraries/ghc-internal/src/GHC/Internal/IsList.hs - libraries/ghc-internal/src/GHC/Internal/Ix.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - libraries/ghc-internal/src/GHC/Internal/Maybe.hs - libraries/ghc-internal/src/GHC/Internal/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs-boot - libraries/ghc-internal/src/GHC/Internal/Numeric/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-prim/GHC/Prim/Exception.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Read.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - libraries/ghc-internal/src/GHC/Internal/Records.hs - libraries/ghc-internal/src/GHC/Internal/Show.hs - libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - libraries/ghc-prim/GHC/Tuple.hs → libraries/ghc-internal/src/GHC/Internal/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats/Internal.hs - libraries/ghc-prim/GHC/Types.hs → libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghc-internal/src/GHC/Internal/Word.hs - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/integer-gmp/integer-gmp.cabal - libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs - libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - libraries/terminfo - libraries/text - libraries/transformers - libraries/unix - linters/lint-codes/LintCodes/Static.hs - linters/lint-codes/Main.hs - m4/find_ld.m4 - m4/fp_settings.m4 - m4/ghc_toolchain.m4 - rts/Capability.c - rts/Capability.h - rts/CheckUnload.c - rts/Disassembler.c - rts/Exception.cmm - rts/Interpreter.c - rts/Interpreter.h - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/ProfHeap.c - rts/RtsMain.c - rts/RtsSymbols.c - rts/Schedule.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStdThunks.cmm - rts/configure.ac - rts/external-symbols.list.in - rts/include/RtsAPI.h - rts/include/Stg.h - rts/include/rts/Bytecodes.h - rts/include/rts/Config.h - rts/include/rts/Threads.h - rts/include/stg/Prim.h - rts/js/environment.js - rts/js/mem.js - rts/js/verify.js - rts/linker/MachO.c - rts/rts.cabal - rts/wasm/JSFFI.c - rts/wasm/scheduler.cmm - rts/win32/libHSghc-prim.def - rts/xxhash.h - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/all.T - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - testsuite/tests/bytecode/T24634/Makefile - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - testsuite/tests/codeGen/should_compile/T25166.stdout - testsuite/tests/codeGen/should_run/T23146/all.T - testsuite/tests/codeGen/should_run/T25364.hs - testsuite/tests/codeGen/should_run/T25364.stdout - testsuite/tests/concurrent/should_run/all.T - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - + testsuite/tests/core-to-stg/T25284/A.hs - + testsuite/tests/core-to-stg/T25284/B.hs - + testsuite/tests/core-to-stg/T25284/Cls.hs - + testsuite/tests/core-to-stg/T25284/Main.hs - + testsuite/tests/core-to-stg/T25284/T25284.stdout - + testsuite/tests/core-to-stg/T25284/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/default/DefaultImportFail01.stderr - testsuite/tests/default/DefaultImportFail02.stderr - testsuite/tests/default/DefaultImportFail03.stderr - testsuite/tests/default/DefaultImportFail04.stderr - testsuite/tests/default/DefaultImportFail05.stderr - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail07.stderr - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/deriving/should_run/T9576.stderr - testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/driver/T20604/T20604.stdout - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/recomp24656/recomp24656.stdout - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - testsuite/tests/ghc-e/should_fail/T23663.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghc-e/should_run/ghc-e005.stderr - testsuite/tests/ghci.debugger/scripts/break006.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T19310.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T21294a.stdout - testsuite/tests/ghci/scripts/T23686.stderr - + testsuite/tests/ghci/scripts/T24459.script - + testsuite/tests/ghci/scripts/T24459.stdout - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/T11361a.stderr - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs → testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12522a.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/javascript/Makefile - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLet10.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/llvm/should_compile/T25606.hs - testsuite/tests/llvm/should_compile/all.T - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19892.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - testsuite/tests/parser/should_run/RecordDotSyntax1.hs - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/perf/compiler/T11068.stdout - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/perf/size/all.T - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/all.T - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/profiling/should_run/ioprof.prof.sample - testsuite/tests/profiling/should_run/toplevel_scc_1.prof.sample - testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quasiquotation/all.T - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/T18263.stderr - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_localname.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TTH_top_splice.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/T12686a.stderr - testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23740i.stderr - + testsuite/tests/rename/should_fail/T25437.hs - + testsuite/tests/rename/should_fail/T25437.stderr - testsuite/tests/rename/should_fail/T5001b.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyMcGuard.stderr - testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T12709.stderr - testsuite/tests/rep-poly/T23153.stderr - + testsuite/tests/rep-poly/T23153b.hs - testsuite/tests/rep-poly/T23154.stderr - + testsuite/tests/rep-poly/T23883a.hs - + testsuite/tests/rep-poly/T23883a.stderr - + testsuite/tests/rep-poly/T23883b.hs - + testsuite/tests/rep-poly/T23883b.stderr - + testsuite/tests/rep-poly/T23883c.hs - + testsuite/tests/rep-poly/T23883c.stderr - testsuite/tests/rep-poly/all.T - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T1791/Makefile - + testsuite/tests/rts/T25560.hs - testsuite/tests/rts/all.T - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/ipe/T24005/t24005.hs - testsuite/tests/rts/linker/all.T - testsuite/tests/safeHaskell/check/pkg01/all.T - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/Orphans.stdout - + testsuite/tests/simd/should_run/T25561.hs - + testsuite/tests/simd/should_run/T25561.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/int16x8_basic.hs - + testsuite/tests/simd/should_run/int16x8_basic.stdout - + testsuite/tests/simd/should_run/int16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/int16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/int32x4_basic.hs - + testsuite/tests/simd/should_run/int32x4_basic.stdout - + testsuite/tests/simd/should_run/int32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/int32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/int64x2_basic.hs - + testsuite/tests/simd/should_run/int64x2_basic.stdout - + testsuite/tests/simd/should_run/int64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/int64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/int8x16_basic.hs - + testsuite/tests/simd/should_run/int8x16_basic.stdout - + testsuite/tests/simd/should_run/int8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/int8x16_basic_baseline.stdout - + testsuite/tests/simd/should_run/word16x8_basic.hs - + testsuite/tests/simd/should_run/word16x8_basic.stdout - + testsuite/tests/simd/should_run/word16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/word16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/word32x4_basic.hs - + testsuite/tests/simd/should_run/word32x4_basic.stdout - + testsuite/tests/simd/should_run/word32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/word32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/word64x2_basic.hs - + testsuite/tests/simd/should_run/word64x2_basic.stdout - + testsuite/tests/simd/should_run/word64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/word64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/word8x16_basic.hs - + testsuite/tests/simd/should_run/word8x16_basic.stdout - + testsuite/tests/simd/should_run/word8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/word8x16_basic_baseline.stdout - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T21286.stderr - testsuite/tests/simplCore/should_compile/T21851_2.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T22428.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10279.hs - testsuite/tests/th/T10279.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15360b.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T16980.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23927.stdout - testsuite/tests/th/T24111.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - testsuite/tests/typecheck/should_compile/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.stderr - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25597.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T15883d.stderr - testsuite/tests/typecheck/should_fail/T15883e.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_fail/T23734.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T23778.stderr - testsuite/tests/typecheck/should_fail/T24298.stderr - testsuite/tests/typecheck/should_fail/T24553.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T7279.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail1.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T22510.stdout - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - testsuite/tests/vdq-rta/should_compile/T23739_th_pprint1.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/T24396.stderr - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/Instances.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - utils/hsc2hs - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8cd73648fb9cd406956d0f05b7bf40cf80021984...c561105bb0f43ecaf19ef0165b504bb7aad22fd0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8cd73648fb9cd406956d0f05b7bf40cf80021984...c561105bb0f43ecaf19ef0165b504bb7aad22fd0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/95b11313/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 20:20:38 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 15:20:38 -0500 Subject: [Git][ghc/ghc][wip/ann-frame] Annotate frame Message-ID: <67c8b2163e4b_a11b8c5d2824370@gitlab.mail> Ben Gamari pushed to branch wip/ann-frame at Glasgow Haskell Compiler / GHC Commits: e5b0ed0c by Ben Gamari at 2025-03-05T15:20:12-05:00 Annotate frame - - - - - 25 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/StgToCmm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - libraries/ghc-heap/GHC/Exts/Stack.hs - libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc - libraries/ghc-heap/GHC/Exts/Stack/Decode.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/ann_frame.hs - libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs - rts/ClosureFlags.c - rts/LdvProfile.c - rts/PrimOps.cmm - rts/Printer.c - rts/RetainerProfile.c - rts/TraverseHeap.c - rts/include/rts/storage/ClosureTypes.h - rts/include/rts/storage/Closures.h - rts/js/profiling.js - rts/sm/Compact.c - rts/sm/Evac.c - rts/sm/NonMovingMark.c - rts/sm/Sanity.c - rts/sm/Scav.c - utils/deriveConstants/Main.hs Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -3927,6 +3927,16 @@ primop ClearCCSOp "clearCCS#" GenPrimOp with out_of_line = True +------------------------------------------------------------------------ +section "Annotating call stacks" +------------------------------------------------------------------------ + +primop AnnotateStackOp "annotateStack#" GenPrimOp + b -> a_reppoly -> a_reppoly + { Pushes an annotation frame to the stack which can be reported by backtraces. } + with + out_of_line = True + ------------------------------------------------------------------------ section "Info Table Origin" ------------------------------------------------------------------------ ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1763,6 +1763,7 @@ emitPrimOp cfg primop = WhereFromOp -> alwaysExternal GetApStackValOp -> alwaysExternal ClearCCSOp -> alwaysExternal + AnnotateStackOp -> alwaysExternal TraceEventOp -> alwaysExternal TraceEventBinaryOp -> alwaysExternal TraceMarkerOp -> alwaysExternal ===================================== libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs ===================================== @@ -84,6 +84,7 @@ data ClosureType | SMALL_MUT_ARR_PTRS_FROZEN_CLEAN | COMPACT_NFDATA | CONTINUATION + | ANN_FRAME | N_CLOSURE_TYPES deriving (Enum, Eq, Ord, Show, Generic) #endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/Closures.hs ===================================== @@ -574,11 +574,15 @@ data GenStackFrame b = , retFunPayload :: ![GenStackField b] } - | RetBCO + | RetBCO { info_tbl :: !StgInfoTable , bco :: !b -- ^ always a BCOClosure , bcoArgs :: ![GenStackField b] } + | AnnFrame + { info_tbl :: !StgInfoTable + , annotation :: !b + } deriving (Foldable, Functor, Generic, Show, Traversable) data PrimType ===================================== libraries/ghc-heap/GHC/Exts/Stack.hs ===================================== @@ -1,5 +1,5 @@ {-# LANGUAGE CPP #-} -#if MIN_TOOL_VERSION_ghc(9,9,0) +#if MIN_TOOL_VERSION_ghc(9,13,0) {-# LANGUAGE RecordWildCards #-} module GHC.Exts.Stack @@ -30,6 +30,7 @@ stackFrameSize (RetFun {..}) = sizeStgRetFunFrame + length retFunPayload stackFrameSize (RetBCO {..}) = sizeStgClosure + 1 + length bcoArgs -- The one additional word is a pointer to the next stack chunk stackFrameSize (UnderflowFrame {}) = sizeStgClosure + 1 +stackFrameSize (AnnFrame {}) = sizeStgAnnFrame stackFrameSize _ = error "Unexpected stack frame type" #else ===================================== libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc ===================================== @@ -3,7 +3,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} module GHC.Exts.Stack.Constants where -#if MIN_TOOL_VERSION_ghc(9,9,0) +#if MIN_TOOL_VERSION_ghc(9,13,0) import Prelude @@ -88,6 +88,13 @@ offsetStgRetFunFramePayload = byteOffsetToWordOffset (#const OFFSET_StgRetFun_pa sizeStgRetFunFrame :: Int sizeStgRetFunFrame = bytesToWords (#const SIZEOF_StgRetFun) +sizeStgAnnFrame :: Int +sizeStgAnnFrame = bytesToWords (#const SIZEOF_StgAnnFrame) + +offsetStgAnnFrameAnn :: WordOffset +offsetStgAnnFrameAnn = byteOffsetToWordOffset $ + (#const OFFSET_StgAnnFrame_ann) + (#size StgHeader) + offsetStgBCOFrameInstrs :: ByteOffset offsetStgBCOFrameInstrs = (#const OFFSET_StgBCO_instrs) + (#size StgHeader) ===================================== libraries/ghc-heap/GHC/Exts/Stack/Decode.hs ===================================== @@ -1,5 +1,5 @@ {-# LANGUAGE CPP #-} -#if MIN_TOOL_VERSION_ghc(9,9,0) +#if MIN_TOOL_VERSION_ghc(9,13,0) {-# LANGUAGE BangPatterns #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE FlexibleInstances #-} @@ -377,6 +377,14 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do catchFrameCode = catchFrameCode', handler = handler' } + ANN_FRAME -> + let annotation = getClosureBox stackSnapshot# (index + offsetStgAnnFrameAnn) + in + pure $ + AnnFrame + { info_tbl = info, + annotation = annotation + } x -> error $ "Unexpected closure type on stack: " ++ show x -- | Unbox 'Int#' from 'Int' ===================================== libraries/ghc-heap/tests/all.T ===================================== @@ -103,3 +103,5 @@ test('stack_misc_closures', ] , '-debug' # Debug RTS to use checkSTACK() (Sanity.c) ]) + +test('ann_frame', normal, compile_and_run, ['']) ===================================== libraries/ghc-heap/tests/ann_frame.hs ===================================== @@ -0,0 +1,36 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE GADTs #-} + +import Data.Typeable +import GHC.Exts +import GHC.Exts.Heap.Closures as Closures +import GHC.Exts.Stack.Decode +import GHC.Stack.CloneStack +import System.IO.Unsafe +import Unsafe.Coerce + +data StackAnnotation where + StackAnnotation :: forall a. (Typeable a, Show a) => a -> StackAnnotation + +annotateStack + :: forall a r b. + (Typeable a, Show a) + => a -> b -> b +annotateStack ann = + annotateStack# (StackAnnotation ann) + +hello :: Int -> Int -> Int +hello x y = annotateStack (x,y) $ unsafePerformIO $ do + stack <- GHC.Stack.CloneStack.cloneMyStack + decoded <- GHC.Exts.Stack.Decode.decodeStack stack + print [ show x + | Closures.AnnFrame _ (Box ann) <- Closures.ssc_stack decoded + , StackAnnotation x <- pure $ unsafeCoerce ann + ] + return $ x + y + 42 +{-# OPAQUE hello #-} + +main :: IO () +main = + print $ hello 2 3 + ===================================== libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs ===================================== @@ -83,5 +83,6 @@ data ClosureType | SMALL_MUT_ARR_PTRS_FROZEN_CLEAN | COMPACT_NFDATA | CONTINUATION + | ANN_FRAME | N_CLOSURE_TYPES deriving (Enum, Eq, Ord, Show, Generic) ===================================== rts/ClosureFlags.c ===================================== @@ -88,8 +88,9 @@ const StgWord16 closure_flags[] = { [SMALL_MUT_ARR_PTRS_FROZEN_CLEAN] = (_HNF| _NS| _UPT ), [COMPACT_NFDATA] = (_HNF| _NS ), [CONTINUATION] = (_HNF| _NS| _UPT ), + [ANN_FRAME] = ( _BTM| _FRM ), }; -#if N_CLOSURE_TYPES != 65 +#if N_CLOSURE_TYPES != 66 #error Closure types changed: update ClosureFlags.c! #endif ===================================== rts/LdvProfile.c ===================================== @@ -154,6 +154,7 @@ processHeapClosureForDead( const StgClosure *c ) case CATCH_STM_FRAME: case CATCH_RETRY_FRAME: case ATOMICALLY_FRAME: + case ANN_FRAME: // others case INVALID_OBJECT: case COMPACT_NFDATA: ===================================== rts/PrimOps.cmm ===================================== @@ -2804,6 +2804,28 @@ stg_clearCCSzh (P_ arg) jump stg_ap_v_fast(arg); } +#define ANN_FRAME_FIELDS(w_,p_,info_ptr,p1,p2,ann) \ + w_ info_ptr, \ + PROF_HDR_FIELDS(w_,p1,p2) \ + p_ ann + +INFO_TABLE_RET (stg_ann_frame, ANN_FRAME, + ANN_FRAME_FIELDS(W_,P_, info_ptr, p1, p2, ann)) + /* no args => explicit stack */ +{ + unwind Sp = W_[Sp + SIZEOF_StgAnnFrame]; + Sp = Sp + SIZEOF_StgAnnFrame; + jump %ENTRY_CODE(Sp(0)) GP_ARG_REGS; // NB. all GP arg regs live! +} + +stg_annotateStackzh (P_ ann, P_ cont) +{ + STK_CHK_GEN(); + jump stg_ap_0_fast + (ANN_FRAME_FIELDS(,,stg_ann_frame_info, CCCS, 0, ann))(cont); + +} + stg_numSparkszh () { W_ n; ===================================== rts/Printer.c ===================================== @@ -270,6 +270,17 @@ printClosure( const StgClosure *obj ) case RET_FUN: */ + case ANN_FRAME: + { + StgAnnFrame* frame = (StgAnnFrame*)obj; + debugBelch("ANN_FRAME("); + printPtr((StgPtr)GET_INFO((StgClosure *)frame)); + debugBelch(","); + printPtr((StgPtr)frame->ann); + debugBelch(")\n"); + break; + } + case UPDATE_FRAME: { StgUpdateFrame* frame = (StgUpdateFrame*)obj; @@ -1123,6 +1134,7 @@ const char *closure_type_names[] = { [RET_FUN] = "RET_FUN", [UPDATE_FRAME] = "UPDATE_FRAME", [CATCH_FRAME] = "CATCH_FRAME", + [ANN_FRAME] = "ANN_FRAME", [UNDERFLOW_FRAME] = "UNDERFLOW_FRAME", [STOP_FRAME] = "STOP_FRAME", [BLOCKING_QUEUE] = "BLOCKING_QUEUE", @@ -1155,7 +1167,7 @@ const char *closure_type_names[] = { [CONTINUATION] = "CONTINUATION", }; -#if N_CLOSURE_TYPES != 65 +#if N_CLOSURE_TYPES != 66 #error Closure types changed: update Printer.c! #endif ===================================== rts/RetainerProfile.c ===================================== @@ -217,6 +217,7 @@ isRetainer( const StgClosure *c ) case RET_SMALL: case RET_BIG: case RET_FUN: + case ANN_FRAME: // other cases case IND: case INVALID_OBJECT: ===================================== rts/TraverseHeap.c ===================================== @@ -529,6 +529,7 @@ traverseGetChildren(StgClosure *c, StgClosure **first_child, bool *other_childre case RET_BCO: case RET_SMALL: case RET_BIG: + case ANN_FRAME: // invalid objects case IND: case INVALID_OBJECT: @@ -832,6 +833,7 @@ traversePop(traverseState *ts, StgClosure **c, StgClosure **cp, stackData *data, case RET_BCO: case RET_SMALL: case RET_BIG: + case ANN_FRAME: // invalid objects case IND: case INVALID_OBJECT: @@ -965,6 +967,7 @@ traversePushStack(traverseState *ts, StgClosure *cp, stackElement *sep, case CATCH_RETRY_FRAME: case ATOMICALLY_FRAME: case RET_SMALL: + case ANN_FRAME: bitmap = BITMAP_BITS(info->i.layout.bitmap); size = BITMAP_SIZE(info->i.layout.bitmap); p++; ===================================== rts/include/rts/storage/ClosureTypes.h ===================================== @@ -89,4 +89,5 @@ #define SMALL_MUT_ARR_PTRS_FROZEN_CLEAN 62 #define COMPACT_NFDATA 63 #define CONTINUATION 64 -#define N_CLOSURE_TYPES 65 +#define ANN_FRAME 65 +#define N_CLOSURE_TYPES 66 ===================================== rts/include/rts/storage/Closures.h ===================================== @@ -312,6 +312,15 @@ typedef struct { StgClosure *result; } StgDeadThreadFrame; +// Stack frame annotating an execution context with a Haskell value +// for backtrace purposes. +// +// Closure types: ANN_FRAME +typedef struct { + StgHeader header; + StgClosure *ann; +} StgAnnFrame; + // A function return stack frame: used when saving the state for a // garbage collection at a function entry point. The function // arguments are on the stack, and we also save the function (its ===================================== rts/js/profiling.js ===================================== @@ -333,3 +333,8 @@ function h$buildCCSPtr(o) { function h$clearCCS(a) { throw new Error("ClearCCSOp not implemented"); } + +// we throw away the annotation here. +function h$annotateStack(o) { + return o; +} ===================================== rts/sm/Compact.c ===================================== @@ -351,6 +351,7 @@ thread_stack(P_ p, P_ stack_end) case STOP_FRAME: case CATCH_FRAME: case RET_SMALL: + case ANN_FRAME: { W_ bitmap = BITMAP_BITS(info->i.layout.bitmap); W_ size = BITMAP_SIZE(info->i.layout.bitmap); ===================================== rts/sm/Evac.c ===================================== @@ -996,6 +996,7 @@ loop: case CATCH_STM_FRAME: case CATCH_RETRY_FRAME: case ATOMICALLY_FRAME: + case ANN_FRAME: // shouldn't see these barf("evacuate: stack frame at %p\n", q); ===================================== rts/sm/NonMovingMark.c ===================================== @@ -1180,6 +1180,7 @@ trace_stack_ (MarkQueue *queue, StgPtr sp, StgPtr spBottom) case STOP_FRAME: case CATCH_FRAME: case RET_SMALL: + case ANN_FRAME: { StgWord bitmap = BITMAP_BITS(info->i.layout.bitmap); StgWord size = BITMAP_SIZE(info->i.layout.bitmap); ===================================== rts/sm/Sanity.c ===================================== @@ -128,6 +128,7 @@ checkStackFrame( StgPtr c ) case UNDERFLOW_FRAME: case STOP_FRAME: case RET_SMALL: + case ANN_FRAME: size = BITMAP_SIZE(info->i.layout.bitmap); checkSmallBitmap((StgPtr)c + 1, BITMAP_BITS(info->i.layout.bitmap), size); ===================================== rts/sm/Scav.c ===================================== @@ -1983,6 +1983,7 @@ scavenge_stack(StgPtr p, StgPtr stack_end) case STOP_FRAME: case CATCH_FRAME: case RET_SMALL: + case ANN_FRAME: bitmap = BITMAP_BITS(info->i.layout.bitmap); size = BITMAP_SIZE(info->i.layout.bitmap); // NOTE: the payload starts immediately after the info-ptr, we ===================================== utils/deriveConstants/Main.hs ===================================== @@ -443,6 +443,8 @@ wanteds os = concat ,closureSize C "StgStopFrame" ,closureSize C "StgDeadThreadFrame" ,closureField C "StgDeadThreadFrame" "result" + ,structSize C "StgAnnFrame" + ,closureField C "StgAnnFrame" "ann" ,closureSize Both "StgMutArrPtrs" ,closureField Both "StgMutArrPtrs" "ptrs" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e5b0ed0c2085cca93a61e24c4425d32de98afeb5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e5b0ed0c2085cca93a61e24c4425d32de98afeb5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/51554224/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 20:39:43 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 05 Mar 2025 15:39:43 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T25806 Message-ID: <67c8b68f6e402_a11b82febbc2491f@gitlab.mail> Ben Gamari pushed new branch wip/T25806 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25806 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/595532ab/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 20:44:18 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 05 Mar 2025 15:44:18 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/wasm-fix-lto Message-ID: <67c8b7a25fe50_a11b8303c9832452@gitlab.mail> Cheng Shao pushed new branch wip/wasm-fix-lto at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/wasm-fix-lto You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/47b0758a/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 22:08:48 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Wed, 05 Mar 2025 17:08:48 -0500 Subject: [Git][ghc/ghc][wip/az/ghc-cpp] 94 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67c8cb70296fd_b4cd97517b4207f8@gitlab.mail> Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - 923437ac by Alan Zimmerman at 2025-03-05T20:04:03+00:00 GHC-CPP: first rough proof of concept Processes #define FOO #ifdef FOO x = 1 #endif Into [ITcppIgnored [L loc ITcppDefine] ,ITcppIgnored [L loc ITcppIfdef] ,ITvarid "x" ,ITequal ,ITinteger (IL {il_text = SourceText "1", il_neg = False, il_value = 1}) ,ITcppIgnored [L loc ITcppEndif] ,ITeof] In time, ITcppIgnored will be pushed into a comment - - - - - 12d4b888 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Tidy up before re-visiting the continuation mechanic - - - - - aaab3053 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Switch preprocessor to continuation passing style Proof of concept, needs tidying up - - - - - b35ef73c by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Small cleanup - - - - - ec94fea4 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Get rid of some cruft - - - - - 571b05b1 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Starting to integrate. Need to get the pragma recognised and set - - - - - bc8ac9a7 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Make cppTokens extend to end of line, and process CPP comments - - - - - 3da647ee by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Remove unused ITcppDefined - - - - - 2c1a415c by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Allow spaces between # and keyword for preprocessor directive - - - - - 29617346 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Process CPP continuation lines They are emited as separate ITcppContinue tokens. Perhaps the processing should be more like a comment, and keep on going to the end. BUT, the last line needs to be slurped as a whole. - - - - - e21b3bc4 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Accumulate CPP continuations, process when ready Can be simplified further, we only need one CPP token - - - - - 5e3ec770 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Simplify Lexer interface. Only ITcpp We transfer directive lines through it, then parse them from scratch in the preprocessor. - - - - - f96b9a46 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Deal with directive on last line, with no trailing \n - - - - - 4546da52 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Start parsing and processing the directives - - - - - 36327835 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Prepare for processing include files - - - - - 04b471d3 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Move PpState into PreProcess And initParserState, initPragState too - - - - - a5c55ff9 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Process nested include files Also move PpState out of Lexer.x, so it is easy to evolve it in a ghci session, loading utils/check-cpp/Main.hs - - - - - 5772d8d6 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Split into separate files - - - - - 8d14c935 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Starting on expression parser. But it hangs. Time for Text.Parsec.Expr - - - - - 958365a0 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Start integrating the ghc-cpp work >From https://github.com/alanz/ghc-cpp - - - - - 3eff4526 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 WIP - - - - - 6152421c by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Fixup after rebase - - - - - f1e40345 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 WIP - - - - - 55f4b6f7 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Fixup after rebase, including all tests pass - - - - - 27e38e39 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Change pragma usage to GHC_CPP from GhcCPP - - - - - 567bc69a by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Some comments - - - - - 50cfad8a by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Reformat - - - - - 09be66dd by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Delete unused file - - - - - 7d0be6a6 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Rename module Parse to ParsePP - - - - - 8a2d6b03 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 Clarify naming in the parser - - - - - 346a3ba9 by Alan Zimmerman at 2025-03-05T20:04:03+00:00 WIP. Switching to alex/happy to be able to work in-tree Since Parsec is not available - - - - - 2f8c0704 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Layering is now correct - GHC lexer, emits CPP tokens - accumulated in Preprocessor state - Lexed by CPP lexer, CPP command extracted, tokens concated with spaces (to get rid of token pasting via comments) - if directive lexed and parsed by CPP lexer/parser, and evaluated - - - - - 10f3e807 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 First example working Loading Example1.hs into ghci, getting the right results ``` {-# LANGUAGE GHC_CPP #-} module Example1 where y = 3 x = "hello" "bye now" foo = putStrLn x ``` - - - - - 044cb383 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Rebase, and all tests pass except whitespace for generated parser - - - - - 9d800e10 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 More plumbing. Ready for testing tomorrow. - - - - - c9df69dd by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Proress. Renamed module State from Types And at first blush it seems to handle preprocessor scopes properly. - - - - - d2b34481 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Insert basic GHC version macros into parser __GLASGOW_HASKELL__ __GLASGOW_HASKELL_FULL_VERSION__ __GLASGOW_HASKELL_PATCHLEVEL1__ __GLASGOW_HASKELL_PATCHLEVEL2__ - - - - - 645a02cd by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Re-sync check-cpp for easy ghci work - - - - - 40e2c574 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Get rid of warnings - - - - - a15d67df by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Rework macro processing, in check-cpp Macros kept at the top level, looked up via name, multiple arity versions per name can be stored - - - - - 38f90577 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 WIP. Can crack arguments for #define Next step it to crack out args in an expansion - - - - - 0974ca53 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 WIP on arg parsing. - - - - - 7a372e0a by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Progress. Still screwing up nested parens. - - - - - f2ce0e2d by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Seems to work, but has redundant code - - - - - 504a287b by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Remove redundant code - - - - - 92cb727a by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Reformat - - - - - c780865d by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Expand args, single pass Still need to repeat until fixpoint - - - - - 41cd52bf by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Fixed point expansion - - - - - dee3b2f1 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Sync the playground to compiler - - - - - d271371d by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Working on dumping the GHC_CPP result But We need to keep the BufSpan in a comment - - - - - 0f789c51 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Keep BufSpan in queued comments in GHC.Parser.Lexer - - - - - 7ce9b4a0 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Getting close to being able to print the combined tokens showing what is in and what is out - - - - - 37d0d216 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 First implementation of dumpGhcCpp. Example output First dumps all macros in the state, then the source, showing which lines are in and which are out ------------------------------ - |#define FOO(A,B) A + B - |#define FOO(A,B,C) A + B + C - |#if FOO(1,FOO(3,4)) == 8 - |-- a comment |x = 1 - |#else - |x = 5 - |#endif - - - - - 1c9d7b2d by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Clean up a bit - - - - - 01170c1a by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Add -ddump-ghc-cpp option and a test based on it - - - - - 67c00187 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Restore Lexer.x rules, we need them for continuation lines - - - - - 6e6fa3b6 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Lexer.x: trying to sort out the span for continuations - We need to match on \n at the end of the line - We cannot simply back up for it - - - - - 6dee6086 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Inserts predefined macros. But does not dump properly Because the cpp tokens have a trailing newline - - - - - 0bf210e1 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Remove unnecessary LExer rules We *need* the ones that explicitly match to the end of the line. - - - - - 02712c41 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Generate correct span for ITcpp Dump now works, except we do not render trailing `\` for continuation lines. This is good enough for use in test output. - - - - - e3d574f2 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Reduce duplication in lexer - - - - - e131465f by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Tweaks - - - - - 018e0a25 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Insert min_version predefined macros into state The mechanism now works. Still need to flesh out the full set. - - - - - 969b0da1 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Trying my alternative pragma syntax. It works, but dumpGhcCpp is broken, I suspect from the ITcpp token span update. - - - - - 885296a7 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Pragma extraction now works, with both CPP and GHC_CPP For the following {-# LANGUAGE CPP #-} #if __GLASGOW_HASKELL__ >= 913 {-# LANGUAGE GHC_CPP #-} #endif We will enable GHC_CPP only - - - - - f1fe5f77 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Remove some tracing - - - - - c1776b6b by Alan Zimmerman at 2025-03-05T20:04:04+00:00 Fix test exes for changes - - - - - fccf2abd by Alan Zimmerman at 2025-03-05T20:04:04+00:00 For GHC_CPP tests, normalise config-time-based macros - - - - - 139ed51f by Alan Zimmerman at 2025-03-05T20:04:04+00:00 WIP - - - - - 60519208 by Alan Zimmerman at 2025-03-05T20:04:04+00:00 WIP again. What is wrong? - - - - - ac43746c by Alan Zimmerman at 2025-03-05T21:37:50+00:00 Revert to dynflags for normal not pragma lexing - - - - - 156 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Parser/Monad.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Parser.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.hs-boot - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - + compiler/GHC/Parser/PreProcess.hs - + compiler/GHC/Parser/PreProcess/Eval.hs - + compiler/GHC/Parser/PreProcess/Lexer.x - + compiler/GHC/Parser/PreProcess/Macro.hs - + compiler/GHC/Parser/PreProcess/ParsePP.hs - + compiler/GHC/Parser/PreProcess/Parser.y - + compiler/GHC/Parser/PreProcess/ParserM.hs - + compiler/GHC/Parser/PreProcess/State.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Parser/Utils.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/debugging.rst - docs/users_guide/ghci.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/stack.yaml.lock - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/include/RtsAPI.h - rts/wasm/JSFFI.c - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/T4437.hs - testsuite/tests/ghc-api/T11579.hs - + testsuite/tests/ghc-cpp/GhcCpp01.hs - + testsuite/tests/ghc-cpp/GhcCpp01.stderr - + testsuite/tests/ghc-cpp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/linters/notes.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + utils/check-cpp/.ghci - + utils/check-cpp/.gitignore - + utils/check-cpp/Eval.hs - + utils/check-cpp/Example1.hs - + utils/check-cpp/Example2.hs - + utils/check-cpp/Example3.hs - + utils/check-cpp/Example4.hs - + utils/check-cpp/Lexer.x - + utils/check-cpp/Macro.hs - + utils/check-cpp/Main.hs - + utils/check-cpp/ParsePP.hs - + utils/check-cpp/ParseSimulate.hs - + utils/check-cpp/Parser.y - + utils/check-cpp/ParserM.hs - + utils/check-cpp/PreProcess.hs - + utils/check-cpp/README.md - + utils/check-cpp/State.hs - + utils/check-cpp/run.sh - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Parsers.hs - utils/check-exact/Preprocess.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs - utils/haddock/haddock-api/src/Haddock/Parser.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6416d190834100a491ccaa14fa7cc9a567aae019...ac43746cbb702fb50738a81c54d56d8a21d91bac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6416d190834100a491ccaa14fa7cc9a567aae019...ac43746cbb702fb50738a81c54d56d8a21d91bac You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/be6c92a8/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 5 22:11:24 2025 From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo)) Date: Wed, 05 Mar 2025 17:11:24 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T25705-1 Message-ID: <67c8cc0c2925c_b4cd97518b82096e@gitlab.mail> Teo Camarasu pushed new branch wip/T25705-1 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25705-1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/fb2b2f05/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 22:11:39 2025 From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo)) Date: Wed, 05 Mar 2025 17:11:39 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/th-export-list Message-ID: <67c8cc1bc07a7_b4cd97518cc211f4@gitlab.mail> Teo Camarasu pushed new branch wip/th-export-list at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/th-export-list You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/8031d822/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 22:20:29 2025 From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo)) Date: Wed, 05 Mar 2025 17:20:29 -0500 Subject: [Git][ghc/ghc][wip/T25705-1] template-haskell: fix haddocks Message-ID: <67c8ce2dac59f_b4cd99624cc257a0@gitlab.mail> Teo Camarasu pushed to branch wip/T25705-1 at Glasgow Haskell Compiler / GHC Commits: 57c25aca by Teo Camarasu at 2025-03-05T22:19:12+00:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks Resolves #25705 - - - - - 1 changed file: - libraries/template-haskell/template-haskell.cabal.in Changes: ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -53,6 +53,10 @@ Library build-depends: base >= 4.11 && < 4.22, + -- We don't directly depend on any of the modules from `ghc-internal` + -- But we need to depend on it to work around a Haddock bug. + -- See: https://gitlab.haskell.org/ghc/ghc/-/issues/25705 + ghc-internal == @ProjectVersionForLib at .*, ghc-boot-th == @ProjectVersionMunged@ other-modules: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57c25aca5f5371d5ff05a67d113e814c27b551f3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57c25aca5f5371d5ff05a67d113e814c27b551f3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/50705fc0/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 5 22:49:12 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 05 Mar 2025 17:49:12 -0500 Subject: [Git][ghc/ghc][wip/T25657] Wibble comments [skip ci] Message-ID: <67c8d4e88dbfb_e49011111ec68858@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25657 at Glasgow Haskell Compiler / GHC Commits: b4758f0b by Simon Peyton Jones at 2025-03-05T22:48:56+00:00 Wibble comments [skip ci] - - - - - 1 changed file: - compiler/GHC/Core/Unify.hs Changes: ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -422,16 +422,14 @@ tcUnifyTys bind_fn tys1 tys2 Unifiable result -> Just result _ -> Nothing --- | @tcUnifyTysFG bind_tv tys1 tys2@ attempts to find a substitution @s@ (whose --- domain elements all respond 'BindMe' to @bind_tv@) such that --- @s(tys1)@ and that of @s(tys2)@ are equal, as witnessed by the returned --- Coercions. This version requires that the kinds of the types are the same, --- if you unify left-to-right. +-- | `tcUnifyTysFG` does "fine-grained" unification of `tys1` and `tys2` +-- See Note [Fine-grained unification]. +-- This version requires that the kinds of the types are the same, +-- provided you unify them left-to-right. tcUnifyTysFG :: BindFamFun -> BindTvFun -> [Type] -> [Type] -> UnifyResult -tcUnifyTysFG bind_fam bind_tv tys1 tys2 - = tc_unify_tys_fg False bind_fam bind_tv tys1 tys2 +tcUnifyTysFG = tc_unify_tys_fg False -- False: don't match kinds tc_unify_tys_fg :: Bool -> BindFamFun -> BindTvFun View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b4758f0bd29ea59fc569fc797eed5a0f84c20b43 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b4758f0bd29ea59fc569fc797eed5a0f84c20b43 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/d678eea3/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 00:05:17 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 05 Mar 2025 19:05:17 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/wasm-dyld-no-type-reflection Message-ID: <67c8e6bd889ce_fc95e18b8488075b@gitlab.mail> Cheng Shao pushed new branch wip/wasm-dyld-no-type-reflection at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/wasm-dyld-no-type-reflection You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/35e7c377/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 01:30:15 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Wed, 05 Mar 2025 20:30:15 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/un_strake Message-ID: <67c8faa791559_fc95eca7a88842a6@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/un_strake at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/un_strake You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250305/7f8849a5/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 09:54:15 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 06 Mar 2025 04:54:15 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/multi-repl-ghci-ui Message-ID: <67c970c7690cf_1f449c2bf61089124@gitlab.mail> Matthew Pickering pushed new branch wip/multi-repl-ghci-ui at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/multi-repl-ghci-ui You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/5bc6375f/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 11:40:20 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 06 Mar 2025 06:40:20 -0500 Subject: [Git][ghc/ghc][wip/t25571] 12 commits: perf: Speed up the bytecode assembler Message-ID: <67c989a429c44_20b379400aec507b3@gitlab.mail> Matthew Pickering pushed to branch wip/t25571 at Glasgow Haskell Compiler / GHC Commits: 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - c5fa0226 by Matthew Pickering at 2025-03-06T11:34:02+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - def66aef by Matthew Pickering at 2025-03-06T11:34:02+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - fbe973e4 by Matthew Pickering at 2025-03-06T11:34:14+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 90 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/wasm/JSFFI.c - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70b5f1da951de72f23f57c2da99e8fabc0fb2ded...fbe973e4aff63e953415337cba57aad42fb9fc75 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70b5f1da951de72f23f57c2da99e8fabc0fb2ded...fbe973e4aff63e953415337cba57aad42fb9fc75 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/39d0dace/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 11:40:40 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 06 Mar 2025 06:40:40 -0500 Subject: [Git][ghc/ghc][wip/22188] 11 commits: perf: Speed up the bytecode assembler Message-ID: <67c989b8d8f2a_20b379241a0851317@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - c5fa0226 by Matthew Pickering at 2025-03-06T11:34:02+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - def66aef by Matthew Pickering at 2025-03-06T11:34:02+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 83 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/wasm/JSFFI.c - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cf4972430f38429b07ca978faef21d3d4a17d12c...def66aef4d6b511532f5af92864f8724ff3e93ff -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cf4972430f38429b07ca978faef21d3d4a17d12c...def66aef4d6b511532f5af92864f8724ff3e93ff You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/31a69665/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 11:44:02 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 06 Mar 2025 06:44:02 -0500 Subject: [Git][ghc/ghc][wip/22188] 2 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67c98a82e2804_20b379619c20521ab@gitlab.mail> Matthew Pickering pushed to branch wip/22188 at Glasgow Haskell Compiler / GHC Commits: a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 28 changed files: - compiler/GHC.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -104,10 +104,8 @@ module GHC ( mi_module, mi_sig_of, mi_hsc_src, - mi_src_hash, mi_hi_bytes, mi_deps, - mi_usages, mi_exports, mi_used_th, mi_fixities, ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1178,7 +1178,8 @@ defaultFlags settings Opt_ShowErrorContext, Opt_SuppressStgReps, Opt_UnoptimizedCoreForInterpreter, - Opt_SpecialiseIncoherents + Opt_SpecialiseIncoherents, + Opt_WriteSelfRecompInfo ] ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns] ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -692,6 +692,7 @@ data GeneralFlag | Opt_ExposeOverloadedUnfoldings | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code + | Opt_WriteSelfRecompInfo | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1243,11 +1243,11 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h (cg_guts, details) <- liftIO $ hscTidy hsc_env simplified_guts - let !partial_iface = + !partial_iface <- liftIO $ {-# SCC "GHC.Driver.Main.mkPartialIface" #-} -- This `force` saves 2M residency in test T10370 -- See Note [Avoiding space leaks in toIface*] for details. - force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) + fmap force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) return HscRecomp { hscs_guts = cg_guts, hscs_mod_location = ms_location summary, ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -875,10 +875,10 @@ pruneCache hpt summ modl = miKey iface linkable' | Just ms <- M.lookup modl ms_map - , mi_src_hash iface /= ms_hs_hash ms - = emptyHomeModInfoLinkable - | otherwise + , mi_src_hash iface == Just (ms_hs_hash ms) = linkable + | otherwise + = emptyHomeModInfoLinkable -- Using UFM Module is safe for determinism because the map is just used for a transient lookup. The cache should be unique and a key clash is an error. ms_map = M.fromListWith ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,6 +2528,7 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, + flagSpec "write-if-self-recomp" Opt_WriteSelfRecompInfo, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -22,14 +22,12 @@ import GHC.Driver.DynFlags import GHC.Driver.Config import GHC.Driver.Config.Core.Lint ( endPassHscEnvIO ) import GHC.Driver.Config.HsToCore.Ticks -import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env import GHC.Driver.Backend import GHC.Driver.Plugins import GHC.Hs -import GHC.HsToCore.Usage import GHC.HsToCore.Monad import GHC.HsToCore.Errors.Types import GHC.HsToCore.Expr @@ -42,7 +40,7 @@ import GHC.HsToCore.Docs import GHC.Tc.Types import GHC.Tc.Types.Origin ( Position(..) ) -import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceLoad ) +import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances ) import GHC.Tc.Module ( runTcInteractive ) import GHC.Core.Type @@ -100,6 +98,7 @@ import GHC.Unit.Module.Deps import Data.List (partition) import Data.IORef import Data.Traversable (for) +import GHC.Iface.Make (mkRecompUsageInfo) {- ************************************************************************ @@ -127,12 +126,10 @@ deSugar hsc_env tcg_fix_env = fix_env, tcg_inst_env = inst_env, tcg_fam_inst_env = fam_inst_env, - tcg_merged = merged, tcg_warns = warns, tcg_anns = anns, tcg_binds = binds, tcg_imp_specs = imp_specs, - tcg_dependent_files = dependent_files, tcg_ev_binds = ev_binds, tcg_th_foreign_files = th_foreign_files_var, tcg_fords = fords, @@ -228,8 +225,7 @@ deSugar hsc_env ; endPassHscEnvIO hsc_env name_ppr_ctx CoreDesugarOpt ds_binds ds_rules_for_imps - ; let used_names = mkUsedNames tcg_env - pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) + ; let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) home_unit = hsc_home_unit hsc_env ; let deps = mkDependencies home_unit (tcg_mod tcg_env) @@ -237,17 +233,10 @@ deSugar hsc_env (map mi_module pluginModules) ; used_th <- readIORef tc_splice_used - ; dep_files <- readIORef dependent_files ; safe_mode <- finalSafeMode dflags tcg_env - ; (needed_mods, needed_pkgs) <- readIORef (tcg_th_needed_deps tcg_env) - - ; let uc = initUsageConfig hsc_env - ; let plugins = hsc_plugins hsc_env - ; let fc = hsc_FC hsc_env - ; let unit_env = hsc_unit_env hsc_env - ; usages <- initIfaceLoad hsc_env $ - mkUsageInfo uc plugins fc unit_env mod (imp_mods imports) used_names - dep_files merged needed_mods needed_pkgs + + ; usages <- mkRecompUsageInfo hsc_env tcg_env + -- id_mod /= mod when we are processing an hsig, but hsigs -- never desugared and compiled (there's no code!) -- Consequently, this should hold for any ModGuts that make ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -49,7 +49,6 @@ import GHC.Types.Name.Cache import GHC.Types.SrcLoc import GHC.Platform import GHC.Settings.Constants -import GHC.Utils.Fingerprint import GHC.Iface.Type (IfaceType(..), getIfaceType, putIfaceType, ifaceTypeSharedByte) import Control.Monad @@ -114,7 +113,7 @@ readBinIfaceHeader -> CheckHiWay -> TraceBinIFace -> FilePath - -> IO (Fingerprint, ReadBinHandle) + -> IO ReadBinHandle readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do let platform = profilePlatform profile @@ -156,8 +155,7 @@ readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do when (checkHiWay == CheckHiWay) $ errorOnMismatch "mismatched interface file profile tag" tag check_tag - src_hash <- get bh - pure (src_hash, bh) + pure bh -- | Read an interface file. -- @@ -170,12 +168,11 @@ readBinIface -> FilePath -> IO ModIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do - (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path + bh <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path mod_iface <- getIfaceWithExtFields name_cache bh return $ mod_iface - & addSourceFingerprint src_hash getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface @@ -259,7 +256,6 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh (show hiVersion) let tag = profileBuildTag profile put_ bh tag - put_ bh (mi_src_hash mod_iface) putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1259,21 +1259,25 @@ pprModIfaceSimple unit_state iface = -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc pprModIface unit_state iface - = vcat [ text "interface" + = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) + <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash exts)) , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) + , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat + [ nest 2 (text "src_hash:" <+> ppr src) + , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "opt_hash:" <+> ppr opt_hash) + , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) + , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) + , vcat (map pprUsage usages) + ] , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) - , nest 2 (text "flag hash:" <+> ppr (mi_flag_hash exts)) - , nest 2 (text "opt_hash:" <+> ppr (mi_opt_hash exts)) - , nest 2 (text "hpc_hash:" <+> ppr (mi_hpc_hash exts)) - , nest 2 (text "plugin_hash:" <+> ppr (mi_plugin_hash exts)) - , nest 2 (text "src_hash:" <+> ppr (mi_src_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "used TH splices:" <+> ppr (mi_used_th iface)) , nest 2 (text "where") @@ -1282,7 +1286,6 @@ pprModIface unit_state iface , text "defaults:" , nest 2 (vcat (map ppr (mi_defaults iface))) , pprDeps unit_state (mi_deps iface) - , vcat (map pprUsage (mi_usages iface)) , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] @@ -1302,6 +1305,7 @@ pprModIface unit_state iface ] where exts = mi_final_exts iface + pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -13,6 +13,7 @@ module GHC.Iface.Make ( mkPartialIface , mkFullIface , mkIfaceTc + , mkRecompUsageInfo , mkIfaceExports ) where @@ -110,7 +111,7 @@ mkPartialIface :: HscEnv -> ModSummary -> [ImportUserSpec] -> ModGuts - -> PartialModIface + -> IO PartialModIface mkPartialIface hsc_env core_prog mod_details mod_summary import_decls ModGuts{ mg_module = this_mod , mg_hsc_src = hsc_src @@ -125,8 +126,10 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_trust_pkg = self_trust , mg_docs = docs } - = mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust - safe_mode usages docs mod_summary mod_details + = do + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages + return $ mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust + safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code -- generator produced information. @@ -181,9 +184,8 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = restoreFromOldModIface mi res - forceModIface resiface - return resiface + forceModIface res + return res -- | Initial ram buffer to allocate for writing interface files. initBinMemSize :: Int @@ -236,14 +238,11 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_merged = merged, tcg_warns = warns, tcg_hpc = other_hpc_info, - tcg_th_splice_used = tc_splice_used, - tcg_dependent_files = dependent_files + tcg_th_splice_used = tc_splice_used } = do - let used_names = mkUsedNames tc_result let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) let home_unit = hsc_home_unit hsc_env let deps = mkDependencies home_unit @@ -252,48 +251,59 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (map mi_module pluginModules) let hpc_info = emptyHpcInfo other_hpc_info used_th <- readIORef tc_splice_used - dep_files <- (readIORef dependent_files) - (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) - let uc = initUsageConfig hsc_env - plugins = hsc_plugins hsc_env - fc = hsc_FC hsc_env - unit_env = hsc_unit_env hsc_env - -- Do NOT use semantic module here; this_mod in mkUsageInfo - -- is used solely to decide if we should record a dependency - -- or not. When we instantiate a signature, the semantic - -- module is something we want to record dependencies for, - -- but if you pass that in here, we'll decide it's the local - -- module and does not need to be recorded as a dependency. - -- See Note [Identity versus semantic module] - usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env this_mod (imp_mods imports) used_names - dep_files merged needed_links needed_pkgs + usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usage let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info - (imp_trust_own_pkg imports) safe_mode usages - docs mod_summary + (imp_trust_own_pkg imports) safe_mode self_recomp + docs mod_details mkFullIface hsc_env partial_iface Nothing Nothing NoStubs [] +mkRecompUsageInfo :: HscEnv -> TcGblEnv -> IO (Maybe [Usage]) +mkRecompUsageInfo hsc_env tc_result = do + let dflags = hsc_dflags hsc_env + if not (gopt Opt_WriteSelfRecompInfo dflags) + then return Nothing + else do + let used_names = mkUsedNames tc_result + dep_files <- (readIORef (tcg_dependent_files tc_result)) + (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) + let uc = initUsageConfig hsc_env + plugins = hsc_plugins hsc_env + fc = hsc_FC hsc_env + unit_env = hsc_unit_env hsc_env + + -- Do NOT use semantic module here; this_mod in mkUsageInfo + -- is used solely to decide if we should record a dependency + -- or not. When we instantiate a signature, the semantic + -- module is something we want to record dependencies for, + -- but if you pass that in here, we'll decide it's the local + -- module and does not need to be recorded as a dependency. + -- See Note [Identity versus semantic module] + usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env (tcg_mod tc_result) (imp_mods (tcg_imports tc_result)) used_names + dep_files (tcg_merged tc_result) needed_links needed_pkgs + return (Just usages) + mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Bool -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo -> Bool -> SafeHaskellMode - -> [Usage] + -> Maybe ModIfaceSelfRecomp -> Maybe Docs - -> ModSummary -> ModDetails -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode usages - docs mod_summary + hpc_info pkg_trust_req safe_mode self_recomp + docs ModDetails{ md_defaults = defaults, md_insts = insts, md_fam_insts = fam_insts, @@ -350,8 +360,8 @@ mkIface_ hsc_env then Nothing else Just semantic_mod) & set_mi_hsc_src hsc_src + & set_mi_self_recomp self_recomp & set_mi_deps deps - & set_mi_usages usages & set_mi_exports (mkIfaceExports exports) & set_mi_defaults (defaultsToIfaceDefaults defaults) @@ -376,7 +386,6 @@ mkIface_ hsc_env & set_mi_docs docs & set_mi_final_exts () & set_mi_ext_fields emptyExtensibleFields - & set_mi_src_hash (ms_hs_hash mod_summary) & set_mi_hi_bytes PartialIfaceBinHandle where ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -15,6 +15,7 @@ module GHC.Iface.Recomp , CompileReason(..) , recompileRequired , addFingerprints + , mkSelfRecomp ) where @@ -171,6 +172,7 @@ data RecompReason = UnitDepRemoved UnitId | ModulePackageChanged FastString | SourceFileChanged + | NoSelfRecompInfo | ThisUnitIdChanged | ImpurePlugin | PluginsChanged @@ -204,6 +206,7 @@ instance Outputable RecompReason where UnitDepRemoved uid -> ppr uid <+> text "removed" ModulePackageChanged s -> ftext s <+> text "package changed" SourceFileChanged -> text "Source file changed" + NoSelfRecompInfo -> text "Old interface lacks recompilation info" ThisUnitIdChanged -> text "-this-unit-id changed" ImpurePlugin -> text "Impure plugin forced recompilation" PluginsChanged -> text "Plugins changed" @@ -283,7 +286,7 @@ check_old_iface hsc_env mod_summary maybe_iface logger = hsc_logger hsc_env getIface = case maybe_iface of - Just _ -> do + Just {} -> do trace_if logger (text "We already have the old interface for" <+> ppr (ms_mod mod_summary)) return maybe_iface @@ -354,7 +357,9 @@ check_old_iface hsc_env mod_summary maybe_iface -- should check versions because some packages -- might have changed or gone away. Just iface -> - check_dyn_hi iface $ checkVersions hsc_env mod_summary iface + case mi_self_recomp_info iface of + Nothing -> return $ outOfDateItemBecause NoSelfRecompInfo Nothing + Just sr_info -> check_dyn_hi iface $ checkVersions hsc_env mod_summary iface sr_info -- | Check if a module is still the same 'version'. -- @@ -370,8 +375,9 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface + -> ModIfaceSelfRecomp -> IfG (MaybeValidated ModIface) -checkVersions hsc_env mod_summary iface +checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger (text "Considering whether compilation is required for" <+> ppr (mi_module iface) <> colon) @@ -380,23 +386,22 @@ checkVersions hsc_env mod_summary iface -- but we ALSO must make sure the instantiation matches up. See -- test case bkpcabal04! ; hsc_env <- getTopEnv - ; if mi_src_hash iface /= ms_hs_hash mod_summary + ; if mi_sr_src_hash self_recomp /= ms_hs_hash mod_summary then return $ outOfDateItemBecause SourceFileChanged Nothing else do { ; if not (isHomeModule home_unit (mi_module iface)) then return $ outOfDateItemBecause ThisUnitIdChanged Nothing else do { - ; recomp <- liftIO $ checkFlagHash hsc_env iface - `recompThen` checkOptimHash hsc_env iface - `recompThen` checkHpcHash hsc_env iface - `recompThen` checkMergedSignatures hsc_env mod_summary iface + ; recomp <- liftIO $ checkFlagHash hsc_env (mi_module iface) self_recomp + `recompThen` checkOptimHash hsc_env self_recomp + `recompThen` checkHpcHash hsc_env self_recomp + `recompThen` checkMergedSignatures hsc_env mod_summary self_recomp `recompThen` checkHsig logger home_unit mod_summary iface `recompThen` pure (checkHie dflags mod_summary) ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { ; recomp <- checkDependencies hsc_env mod_summary iface ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { - ; recomp <- checkPlugins (hsc_plugins hsc_env) iface + ; recomp <- checkPlugins (hsc_plugins hsc_env) self_recomp ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { - -- Source code unchanged and no errors yet... carry on -- -- First put the dependent-module info, read from the old @@ -411,7 +416,7 @@ checkVersions hsc_env mod_summary iface ; updateEps_ $ \eps -> eps { eps_is_boot = mkModDeps $ dep_boot_mods (mi_deps iface) } } ; recomp <- checkList [checkModUsage (hsc_FC hsc_env) u - | u <- mi_usages iface] + | u <- mi_sr_usages self_recomp] ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { ; return $ UpToDateItem iface }}}}}}} @@ -423,11 +428,11 @@ checkVersions hsc_env mod_summary iface -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIface -> IfG RecompileRequired -checkPlugins plugins iface = liftIO $ do +checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp - let old_fingerprint = mi_plugin_hash (mi_final_exts iface) + let old_fingerprint = mi_sr_plugin_hash self_recomp return $ pluginRecompileToRecompileRequired old_fingerprint new_fingerprint recomp recompPlugins :: Plugins -> IO PluginRecompile @@ -516,11 +521,11 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> ModIface -> IO RecompileRequired -checkFlagHash hsc_env iface = do +checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_flag_hash (mi_final_exts iface) - new_hash <- fingerprintDynFlags hsc_env (mi_module iface) putNameLiterally + let old_hash = mi_sr_flag_hash self_recomp + new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally case old_hash == new_hash of True -> up_to_date logger (text "Module flags unchanged") False -> out_of_date_hash logger FlagsChanged @@ -528,10 +533,10 @@ checkFlagHash hsc_env iface = do old_hash new_hash -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIface -> IO RecompileRequired +checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env - let old_hash = mi_opt_hash (mi_final_exts iface) + let old_hash = mi_sr_opt_hash iface new_hash <- fingerprintOptFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -544,10 +549,10 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIface -> IO RecompileRequired -checkHpcHash hsc_env iface = do +checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_hpc_hash (mi_final_exts iface) + let old_hash = mi_sr_hpc_hash self_recomp new_hash <- fingerprintHpcFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -561,11 +566,11 @@ checkHpcHash hsc_env iface = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIface -> IO RecompileRequired -checkMergedSignatures hsc_env mod_summary iface = do +checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env - let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_usages iface ] + let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_sr_usages self_recomp ] new_merged = case lookupUniqMap (requirementContext unit_state) (ms_mod_name mod_summary) of Nothing -> [] @@ -939,6 +944,28 @@ we use is: -} +-- | Compute the information needed for self-recompilation checking. This +-- information can be computed before the backend phase. +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp hsc_env this_mod src_hash usages = do + let dflags = hsc_dflags hsc_env + + flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + + opt_hash <- fingerprintOptFlags dflags putNameLiterally + + hpc_hash <- fingerprintHpcFlags dflags putNameLiterally + + plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + + return (ModIfaceSelfRecomp + { mi_sr_flag_hash = flag_hash + , mi_sr_hpc_hash = hpc_hash + , mi_sr_opt_hash = opt_hash + , mi_sr_plugin_hash = plugin_hash + , mi_sr_src_hash = src_hash + , mi_sr_usages = usages }) + -- | Add fingerprints for top-level declarations to a 'ModIface'. -- -- See Note [Fingerprinting IfaceDecls] @@ -1213,18 +1240,6 @@ addFingerprints hsc_env iface0 sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - -- the flag hash depends on: - -- - (some of) dflags - -- it returns two hashes, one that shouldn't change - -- the abi hash and one that should - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally - - opt_hash <- fingerprintOptFlags dflags putNameLiterally - - hpc_hash <- fingerprintHpcFlags dflags putNameLiterally - - plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) - -- the ABI hash depends on: -- - decls -- - export list @@ -1238,6 +1253,7 @@ addFingerprints hsc_env iface0 mi_warns iface0, mi_foreign iface0) + -- The interface hash depends on: -- - the ABI hash, plus -- - the source file hash, @@ -1246,21 +1262,17 @@ addFingerprints hsc_env iface0 -- - deps (home and external packages, dependent files) -- - hpc iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - mi_src_hash iface0, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_usages iface0, - sorted_deps, - mi_hpc iface0) + (mod_hash, + mi_src_hash iface0, + ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache + mi_usages iface0, + sorted_deps, + mi_hpc iface0) let final_iface_exts = ModIfaceBackend - { mi_iface_hash = iface_hash - , mi_mod_hash = mod_hash - , mi_flag_hash = flag_hash - , mi_opt_hash = opt_hash - , mi_hpc_hash = hpc_hash - , mi_plugin_hash = plugin_hash + { mi_mod_hash = mod_hash + , mi_iface_hash = iface_hash , mi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts @@ -1281,12 +1293,12 @@ addFingerprints hsc_env iface0 where this_mod = mi_module iface0 semantic_mod = mi_semantic_module iface0 - dflags = hsc_dflags hsc_env (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) ann_fn = mkIfaceAnnCache (mi_anns iface0) + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the -- current module). ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -0,0 +1,112 @@ +module GHC.Iface.Recomp.Types ( ModIfaceSelfRecomp(..) + ) where + +import GHC.Prelude +import GHC.Fingerprint +import GHC.Utils.Outputable +import GHC.Unit.Module.Deps + +import GHC.Utils.Binary + +import Control.DeepSeq + +{- +Note [Self recompilation information in interface files] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The flag -fwrite-if-self-recomp controls whether +interface files contain the information necessary to answer the +question: + + Is the interface file up-to-date, relative to: + * the source file it corresponds to, + * the flags passed to the GHC invocation to compile it, + * its dependencies (e.g. imported items, watched files added by addDependentFile, ...) + +If there is no self-recompilation information stored, then we always re-generate +the interface file from scratch. + +Why? Most packages are only built once either by a distribution or cabal +and then placed into an immutable store, after which we will never ask +this question. Therefore we can derive two benefits from omitting this +information. + +* Primary motivation: It vastly reduces the surface area for creating + non-deterministic interface files. See issue #10424 which motivated a + proper fix to that issue. Distributions have long contained versions + of GHC which just have broken self-recompilation checking (in order to + get deterministic interface files). + +* Secondary motivation: This reduces the size of interface files + slightly.. the `mi_usages` field can be quite big but probably this + isn't such a great benefit. + +* Third motivation: Conceptually clarity about which parts of an + interface file are used in order to **communicate** with subsequent + packages about the **interface** for a module. And which parts are + used to self-communicate during recompilation checking. + +The main tracking issue is #22188 but fixes issues such as #10424 in a +proper way. + +-} + +-- | The information for a module which is only used when deciding whether to recompile +-- itself. +-- +-- See Note [Self recompilation information in interface files] +data ModIfaceSelfRecomp = + ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint + -- ^ Hash of the .hs source, used for recompilation checking. + , mi_sr_usages :: [Usage] + -- ^ Usages; kept sorted so that it's easy to decide + -- whether to write a new iface file (changing usages + -- doesn't affect the hash of this module) + -- NOT STRICT! we read this field lazily from the interface file + -- It is *only* consulted by the recompilation checker + + , mi_sr_flag_hash :: !Fingerprint + -- ^ Hash of the important flags used when compiling the module, excluding + -- optimisation flags + , mi_sr_opt_hash :: !Fingerprint + -- ^ Hash of optimisation flags + , mi_sr_hpc_hash :: !Fingerprint + -- ^ Hash of hpc flags + , mi_sr_plugin_hash :: !Fingerprint + -- ^ Hash of plugins + } + + +instance Binary ModIfaceSelfRecomp where + put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do + put_ bh mi_sr_src_hash + lazyPut bh mi_sr_usages + put_ bh mi_sr_flag_hash + put_ bh mi_sr_opt_hash + put_ bh mi_sr_hpc_hash + put_ bh mi_sr_plugin_hash + + get bh = do + src_hash <- get bh + usages <- lazyGet bh + flag_hash <- get bh + opt_hash <- get bh + hpc_hash <- get bh + plugin_hash <- get bh + return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + +instance Outputable ModIfaceSelfRecomp where + ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) + = vcat [text "Self-Recomp" + , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash + , text "usages:" <+> ppr (length mi_sr_usages) + , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "opt hash:" <+> ppr mi_sr_opt_hash + , text "hpc hash:" <+> ppr mi_sr_hpc_hash + , text "plugin hash:" <+> ppr mi_sr_plugin_hash + ])] + +instance NFData ModIfaceSelfRecomp where + -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so + -- I left it as a shallow force. + rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file ===================================== compiler/GHC/Unit/Module/ModGuts.hs ===================================== @@ -53,7 +53,7 @@ data ModGuts mg_exports :: ![AvailInfo], -- ^ What it exports mg_deps :: !Dependencies, -- ^ What it depends on, directly or -- otherwise - mg_usages :: ![Usage], -- ^ What was used? Used for interfaces. + mg_usages :: !(Maybe [Usage]), -- ^ What was used? Used for interfaces. mg_used_th :: !Bool, -- ^ Did we run a TH splice? mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -15,7 +15,6 @@ module GHC.Unit.Module.ModIface , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -36,19 +35,16 @@ module GHC.Unit.Module.ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info ) , pattern ModIface - , restoreFromOldModIface - , addSourceFingerprint , set_mi_module , set_mi_sig_of , set_mi_hsc_src - , set_mi_src_hash + , set_mi_self_recomp , set_mi_hi_bytes , set_mi_deps - , set_mi_usages , set_mi_exports , set_mi_used_th , set_mi_fixities @@ -73,6 +69,8 @@ module GHC.Unit.Module.ModIface , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) + , ModIfaceSelfRecomp (..) + , withSelfRecomp , IfaceDeclExts , IfaceBackendExts , IfaceExport @@ -85,6 +83,12 @@ module GHC.Unit.Module.ModIface , mi_semantic_module , mi_free_holes , mi_mnwib + , mi_flag_hash + , mi_opt_hash + , mi_hpc_hash + , mi_plugin_hash + , mi_src_hash + , mi_usages , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -100,12 +104,14 @@ import GHC.Hs import GHC.Iface.Syntax import GHC.Iface.Ext.Fields +import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) + import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env @@ -150,19 +156,10 @@ type ModIface = ModIface_ 'ModIfaceFinal -- * Or computed just before writing the iface to disk. (Hashes) -- In order to fully instantiate it. data ModIfaceBackend = ModIfaceBackend - { mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_mod_hash :: !Fingerprint + { mi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_flag_hash :: !Fingerprint - -- ^ Hash of the important flags used when compiling the module, excluding - -- optimisation flags - , mi_opt_hash :: !Fingerprint - -- ^ Hash of optimisation flags - , mi_hpc_hash :: !Fingerprint - -- ^ Hash of hpc flags - , mi_plugin_hash :: !Fingerprint - -- ^ Hash of plugins + , mi_iface_hash :: !Fingerprint + -- ^ Hash of the whole interface , mi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans , mi_finsts :: !WhetherHasFamInst @@ -218,6 +215,15 @@ data IfaceBinHandle (phase :: ModIfacePhase) where -- (e.g., set to 'Nothing'). FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal + +withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp iface nk jk = + case mi_self_recomp_info iface of + Nothing -> nk + Just x -> jk x + + + -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, -- and can be written out to an interface file. The 'ModDetails is after @@ -245,16 +251,6 @@ data ModIface_ (phase :: ModIfacePhase) -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages_ :: [Usage], - -- ^ Usages; kept sorted so that it's easy to decide - -- whether to write a new iface file (changing usages - -- doesn't affect the hash of this module) - -- NOT STRICT! we read this field lazily from the interface file - -- It is *only* consulted by the recompilation checker - -- - -- The elements must be *deterministically* sorted to guarantee - -- deterministic interface files - mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier @@ -345,13 +341,15 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash_ :: !Fingerprint, - -- ^ Hash of the .hs source, used for recompilation checking. - mi_hi_bytes_ :: !(IfaceBinHandle phase) + mi_hi_bytes_ :: !(IfaceBinHandle phase), -- ^ A serialised in-memory buffer of this 'ModIface'. -- If this handle is given, we can avoid serialising the 'ModIface' -- when writing this 'ModIface' to disk, and write this buffer to disk instead. -- See Note [Sharing of ModIface]. + + mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] } -- Enough information to reconstruct the top level environment for a module @@ -397,6 +395,24 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} +mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ + +mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ + +mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ + +mi_src_hash :: ModIface_ phase -> Maybe Fingerprint +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ + +mi_usages :: ModIface_ phase -> Maybe [Usage] +mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ + +mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ + -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. mi_boot :: ModIface -> IsBootInterface @@ -454,9 +470,6 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance - -- because we are going to write it - -- out separately in the actual file mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then @@ -464,7 +477,6 @@ instance Binary ModIface where -- the byte array. -- See Note [Private fields in ModIface] mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_fixities_ = fixities, @@ -486,13 +498,10 @@ instance Binary ModIface where mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file + mi_self_recomp_info_ = self_recomp, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -501,16 +510,12 @@ instance Binary ModIface where put_ bh mod put_ bh sig_of put_ bh hsc_src - put_ bh iface_hash + put_ bh self_recomp put_ bh mod_hash - put_ bh flag_hash - put_ bh opt_hash - put_ bh hpc_hash - put_ bh plugin_hash + put_ bh iface_hash put_ bh orphan put_ bh hasFamInsts lazyPut bh deps - lazyPut bh usages put_ bh exports put_ bh exp_hash put_ bh used_th @@ -536,16 +541,12 @@ instance Binary ModIface where mod <- get bh sig_of <- get bh hsc_src <- get bh - iface_hash <- get bh + self_recomp_info <- get bh mod_hash <- get bh - flag_hash <- get bh - opt_hash <- get bh - hpc_hash <- get bh - plugin_hash <- get bh + iface_hash <- get bh orphan <- get bh hasFamInsts <- get bh deps <- lazyGet bh - usages <- {-# SCC "bin_usages" #-} lazyGet bh exports <- {-# SCC "bin_exports" #-} get bh exp_hash <- get bh used_th <- get bh @@ -570,15 +571,12 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = fingerprint0, -- placeholder because this is dealt - -- with specially when the file is read mi_hi_bytes_ = -- We can't populate this field here, as we are -- missing the 'mi_ext_fields_' field, which is -- handled in 'getIfaceWithExtFields'. FullIfaceBinHandle Strict.Nothing, mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_anns_ = anns, @@ -600,13 +598,10 @@ instance Binary ModIface where mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read + mi_self_recomp_info_ = self_recomp_info, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -625,10 +620,8 @@ emptyPartialModIface mod { mi_module_ = mod, mi_sig_of_ = Nothing, mi_hsc_src_ = HsSrcFile, - mi_src_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_usages_ = [], mi_exports_ = [], mi_used_th_ = False, mi_fixities_ = [], @@ -648,21 +641,19 @@ emptyPartialModIface mod mi_complete_matches_ = [], mi_docs_ = Nothing, mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields + mi_ext_fields_ = emptyExtensibleFields, + mi_self_recomp_info_ = Nothing } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) { mi_decls_ = [] + , mi_self_recomp_info_ = Nothing , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing , mi_final_exts_ = ModIfaceBackend - { mi_iface_hash = fingerprint0, - mi_mod_hash = fingerprint0, - mi_flag_hash = fingerprint0, - mi_opt_hash = fingerprint0, - mi_hpc_hash = fingerprint0, - mi_plugin_hash = fingerprint0, + { mi_mod_hash = fingerprint0, + mi_iface_hash = fingerprint0, mi_orphan = False, mi_finsts = False, mi_exp_hash = fingerprint0, @@ -692,18 +683,17 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_, mi_src_hash_ }) + , mi_ext_fields_ }) = rnf mi_module_ `seq` rnf mi_sig_of_ `seq` mi_hsc_src_ `seq` mi_hi_bytes_ `seq` mi_deps_ - `seq` mi_usages_ `seq` mi_exports_ `seq` rnf mi_used_th_ `seq` mi_fixities_ @@ -724,20 +714,14 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_docs_ `seq` mi_final_exts_ `seq` mi_ext_fields_ - `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_iface_hash, mi_mod_hash, mi_flag_hash, mi_opt_hash - , mi_hpc_hash, mi_plugin_hash, mi_orphan, mi_finsts, mi_exp_hash + rnf (ModIfaceBackend{ mi_mod_hash + , mi_orphan, mi_finsts, mi_exp_hash , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn , mi_hash_fn}) - = rnf mi_iface_hash - `seq` rnf mi_mod_hash - `seq` rnf mi_flag_hash - `seq` rnf mi_opt_hash - `seq` rnf mi_hpc_hash - `seq` rnf mi_plugin_hash + = rnf mi_mod_hash `seq` rnf mi_orphan `seq` rnf mi_finsts `seq` rnf mi_exp_hash @@ -803,27 +787,6 @@ completePartialModIface partial decls extra_decls final_exts = partial , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing } --- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array --- buffer 'mi_hi_bytes'. --- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. --- --- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. -addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase -addSourceFingerprint val iface = iface { mi_src_hash_ = val } - --- | Copy fields that aren't serialised to disk to the new 'ModIface_'. --- This includes especially hashes that are usually stored in the interface --- file header. --- --- We need this function after calling 'shareIface', to make sure the --- 'ModIface_' doesn't lose any information. This function does not discard --- the in-memory byte array buffer 'mi_hi_bytes'. -restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase -restoreFromOldModIface old new = new - { mi_hsc_src_ = mi_hsc_src_ old - , mi_src_hash_ = mi_src_hash_ old - } - set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } @@ -833,8 +796,8 @@ set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } -set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase -set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } +set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -842,9 +805,6 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } -set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase -set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } - set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } @@ -969,7 +929,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} -{-# INLINE mi_usages #-} {-# INLINE mi_exports #-} {-# INLINE mi_used_th #-} {-# INLINE mi_fixities #-} @@ -989,25 +948,23 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_docs #-} {-# INLINE mi_final_exts #-} {-# INLINE mi_ext_fields #-} -{-# INLINE mi_src_hash #-} {-# INLINE mi_hi_bytes #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + Module -> Maybe Module -> HscSource -> Dependencies -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface { mi_module , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -1028,14 +985,13 @@ pattern ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info } <- PrivateModIface { mi_module_ = mi_module , mi_sig_of_ = mi_sig_of , mi_hsc_src_ = mi_hsc_src , mi_deps_ = mi_deps - , mi_usages_ = mi_usages , mi_exports_ = mi_exports , mi_used_th_ = mi_used_th , mi_fixities_ = mi_fixities @@ -1056,6 +1012,6 @@ pattern ModIface , mi_docs_ = mi_docs , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields - , mi_src_hash_ = mi_src_hash , mi_hi_bytes_ = mi_hi_bytes + , mi_self_recomp_info_ = mi_self_recomp_info } ===================================== compiler/ghc.cabal.in ===================================== @@ -606,6 +606,7 @@ Library GHC.Iface.Recomp GHC.Iface.Recomp.Binary GHC.Iface.Recomp.Flags + GHC.Iface.Recomp.Types GHC.Iface.Rename GHC.Iface.Syntax GHC.Iface.Tidy ===================================== docs/users_guide/phases.rst ===================================== @@ -702,6 +702,24 @@ Options affecting code generation depend on the optimisation level. Any definitions which are already included in an interface file (via an unfolding for an exported identifier) are reused. +.. ghc-flag:: -fwrite-if-self-recomp + :shortdesc: Write information for self-recompilation checking in an interface file + :type: dynamic + :category: codegen + + :default: on + + Include information in an interface file which can be used in future to determine + whether we need to recompile a module or can reuse the existing interface. + + This is intended to be turned off in situations where you know you will never try + to recompile a module, such as when compiling a package for distribution. + The advantage is that by omitting unecessary information to do with dependencies + there is less chance of build paths leaking into the interface file and affecting + determinism. + + + .. ghc-flag:: -fobject-code :shortdesc: Generate object code ===================================== hadrian/doc/flavours.md ===================================== @@ -107,7 +107,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH <td>-O2</td> </tr> <tr> - <th>release (same as perf with -haddock)</td> + <th>release (same as perf with -haddock and +no_self_recomp)</td> <td></td> <td>-O<br>-H64m</td> <td>-O<br>-H64m</td> @@ -329,6 +329,10 @@ The supported transformers are listed below: <td><code>dump_stg</code></td> <td>Dump STG of all modules compiled by a stage1 compiler to a file</td> </tr> + <tr> + <td><code>no_self_recomp</code></td> + <td>Disable including self-recompilation information in interface files via <code>-fno-write-if-self-recomp</code>. If you are building a distribution you can enable this flag to produce more deterministic interface files.</td> + </tr> </table> ### Static ===================================== hadrian/src/Flavour.hs ===================================== @@ -16,6 +16,7 @@ module Flavour , disableProfiledLibs , enableLinting , enableHaddock + , disableSelfRecompInfo , enableHiCore , useNativeBignum , enableTextWithSIMDUTF @@ -67,6 +68,7 @@ flavourTransformers = M.fromList , "debug_stage1_ghc" =: debugGhc Stage1 , "lint" =: enableLinting , "haddock" =: enableHaddock + , "no_self_recomp" =: disableSelfRecompInfo , "hi_core" =: enableHiCore , "late_ccs" =: enableLateCCS , "boot_nonmoving_gc" =: enableBootNonmovingGc @@ -208,6 +210,17 @@ enableHaddock = [ arg "-haddock" ] +-- | Disable self recompilation information in interface files +disableSelfRecompInfo :: Flavour -> Flavour +disableSelfRecompInfo = + addArgs $ stage1 ? mconcat + [ builder (Ghc CompileHs) ? selfRecomp + ] + where + selfRecomp = mconcat + [ arg "-fno-write-if-self-recomp" + ] + -- | Build stage2 dependencies with options to emit Core into -- interface files which is sufficient to restart code generation. enableHiCore :: Flavour -> Flavour ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,8 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableHaddock performanceFlavour { name = "release" } +releaseFlavour = + -- 1. These interface files will be distributed and the source files never recompiled. + disableSelfRecompInfo + -- 2. Include documentation in the interface for tools such as haddock and HLS to use + $ enableHaddock performanceFlavour { name = "release" } ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -112,6 +112,7 @@ GHC.Hs.Utils GHC.Iface.Errors.Types GHC.Iface.Ext.Fields GHC.Iface.Recomp.Binary +GHC.Iface.Recomp.Types GHC.Iface.Syntax GHC.Iface.Type GHC.Parser.Annotation ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -118,6 +118,7 @@ GHC.HsToCore.Pmc.Solver.Types GHC.Iface.Errors.Types GHC.Iface.Ext.Fields GHC.Iface.Recomp.Binary +GHC.Iface.Recomp.Types GHC.Iface.Syntax GHC.Iface.Type GHC.Linker.Static.Utils ===================================== testsuite/tests/driver/self-recomp/Makefile ===================================== @@ -0,0 +1,38 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +TEST_HC_OPTS_NO_RTSOPTS = $(filter-out -rtsopts,$(TEST_HC_OPTS)) + +# ----------------------------------------------------------------------------- +# One-shot compilations, non-hierarchical modules + +# Check that modifying flags doesn't affect interface +SelfRecomp01: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface1 + rm SelfRecomp01.hi + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-if-self-recomp -Iidir -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface2 + diff iface1 iface2 + +# Check that the result of addDependentFile doesn't end up in interface +SelfRecomp02: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp02.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp02.hi > iface + [ -z $(grep iface SelfRecomp02.hs) ] + +# Check that modifying source doesn't affect interface +SelfRecomp03: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface1 + rm SelfRecomp03.hi + echo "" >> SelfRecomp03.hs + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface2 + diff iface1 iface2 + +# Check that if you don't have recompilation info then you always recompile. +SelfRecomp04: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-if-self-recomp -fhide-source-paths + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-if-self-recomp -fhide-source-paths ===================================== testsuite/tests/driver/self-recomp/SelfRecomp01.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp01 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp02.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +module SelfRecomp02 where + +import Language.Haskell.TH.Syntax + +main = $(addDependentFile "SelfRecomp02.hs" >> [| print () |]) ===================================== testsuite/tests/driver/self-recomp/SelfRecomp03.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp03 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.hs ===================================== @@ -0,0 +1 @@ +module SelfRecomp04 where ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.stdout ===================================== @@ -0,0 +1,2 @@ +[1 of 1] Compiling SelfRecomp04 +[1 of 1] Compiling SelfRecomp04 [Old interface lacks recompilation info] ===================================== testsuite/tests/driver/self-recomp/all.T ===================================== @@ -0,0 +1,4 @@ +test('SelfRecomp01', normal, makefile_test, ['SelfRecomp01']) +test('SelfRecomp02', normal, makefile_test, ['SelfRecomp02']) +test('SelfRecomp03', [copy_files], makefile_test, ['SelfRecomp03']) +test('SelfRecomp04', normal, makefile_test, ['SelfRecomp04']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/def66aef4d6b511532f5af92864f8724ff3e93ff...5b05c27bf186e66edc4fbf4a54943c8bd04f5024 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/def66aef4d6b511532f5af92864f8724ff3e93ff...5b05c27bf186e66edc4fbf4a54943c8bd04f5024 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/537f0223/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 12:22:03 2025 From: gitlab at gitlab.haskell.org (Ryan Scott (@RyanGlScott)) Date: Thu, 06 Mar 2025 07:22:03 -0500 Subject: [Git][ghc/ghc][wip/make-Wdata-kinds-tc-an-error] Remove -Wdata-kinds-tc warning, make DataKinds issues in typechecker become errors Message-ID: <67c9936b8675_20b3799f22c052987@gitlab.mail> Ryan Scott pushed to branch wip/make-Wdata-kinds-tc-an-error at Glasgow Haskell Compiler / GHC Commits: 6db8d605 by Ryan Scott at 2025-03-06T07:21:46-05:00 Remove -Wdata-kinds-tc warning, make DataKinds issues in typechecker become errors !11314 introduced the `-Wdata-kinds-tc` warning as part of a fix for #22141. This was a temporary stopgap measure to allow users who were accidentally relying on code which needed the `DataKinds` extension in order to typecheck without having to explicitly enable the extension. Now that some amount of time has passed, this patch removes `-Wdata-kinds-tc` and upgrades any `DataKinds`-related issues in the typechecker (which were previously warnings) into errors. - - - - - 29 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Validity.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/using-warnings.rst - − testsuite/tests/typecheck/should_compile/T22141a.stderr - − testsuite/tests/typecheck/should_compile/T22141b.stderr - − testsuite/tests/typecheck/should_compile/T22141c.stderr - − testsuite/tests/typecheck/should_compile/T22141d.stderr - − testsuite/tests/typecheck/should_compile/T22141e.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T20873c.hs - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs - testsuite/tests/typecheck/should_fail/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs - testsuite/tests/typecheck/should_fail/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs - testsuite/tests/typecheck/should_fail/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs - testsuite/tests/typecheck/should_fail/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs - testsuite/tests/typecheck/should_fail/T22141e.stderr - testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs - testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1073,7 +1073,6 @@ data WarningFlag = | Opt_WarnIncompleteRecordSelectors -- Since 9.10 | Opt_WarnBadlyStagedTypes -- Since 9.10 | Opt_WarnInconsistentFlags -- Since 9.8 - | Opt_WarnDataKindsTC -- Since 9.10 | Opt_WarnDefaultedExceptionContext -- Since 9.10 | Opt_WarnViewPatternSignatures -- Since 9.12 deriving (Eq, Ord, Show, Enum, Bounded) @@ -1189,7 +1188,6 @@ warnFlagNames wflag = case wflag of Opt_WarnIncompleteRecordSelectors -> "incomplete-record-selectors" :| [] Opt_WarnBadlyStagedTypes -> "badly-staged-types" :| [] Opt_WarnInconsistentFlags -> "inconsistent-flags" :| [] - Opt_WarnDataKindsTC -> "data-kinds-tc" :| [] Opt_WarnDefaultedExceptionContext -> "defaulted-exception-context" :| [] Opt_WarnViewPatternSignatures -> "view-pattern-signatures" :| [] @@ -1331,7 +1329,6 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnBadlyStagedTypes, Opt_WarnTypeEqualityRequiresOperators, Opt_WarnInconsistentFlags, - Opt_WarnDataKindsTC, Opt_WarnTypeEqualityOutOfScope, Opt_WarnViewPatternSignatures ] ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2355,7 +2355,6 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnImplicitRhsQuantification -> warnSpec x Opt_WarnIncompleteExportWarnings -> warnSpec x Opt_WarnIncompleteRecordSelectors -> warnSpec x - Opt_WarnDataKindsTC -> warnSpec x Opt_WarnDefaultedExceptionContext -> warnSpec x Opt_WarnViewPatternSignatures -> warnSpec x ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1715,21 +1715,15 @@ instance Diagnostic TcRnMessage where , inHsDocContext doc ] TcRnDataKindsError typeOrKind thing - -- See Note [Checking for DataKinds] (Wrinkle: Migration story for - -- DataKinds typechecker errors) in GHC.Tc.Validity for why we give - -- different diagnostic messages below. -> case thing of Left renamer_thing -> - mkSimpleDecorated $ - text "Illegal" <+> ppr_level <> colon <+> quotes (ppr renamer_thing) + mkSimpleDecorated $ msg renamer_thing Right typechecker_thing -> - mkSimpleDecorated $ vcat - [ text "An occurrence of" <+> quotes (ppr typechecker_thing) <+> - text "in a" <+> ppr_level <+> text "requires DataKinds." - , text "Future versions of GHC will turn this warning into an error." - ] + mkSimpleDecorated $ msg typechecker_thing where - ppr_level = text $ levelString typeOrKind + msg :: Outputable a => a -> SDoc + msg thing = text "Illegal" <+> text (levelString typeOrKind) <> + colon <+> quotes (ppr thing) TcRnTypeSynonymCycle decl_or_tcs -> mkSimpleDecorated $ @@ -2524,17 +2518,8 @@ instance Diagnostic TcRnMessage where -> ErrorWithoutFlag TcRnUnusedQuantifiedTypeVar{} -> WarningWithFlag Opt_WarnUnusedForalls - TcRnDataKindsError _ thing - -- DataKinds errors can arise from either the renamer (Left) or the - -- typechecker (Right). The latter category of DataKinds errors are a - -- fairly recent addition to GHC (introduced in GHC 9.10), and in order - -- to prevent these new errors from breaking users' code, we temporarily - -- downgrade these errors to warnings. See Note [Checking for DataKinds] - -- (Wrinkle: Migration story for DataKinds typechecker errors) - -- in GHC.Tc.Validity. - -> case thing of - Left _ -> ErrorWithoutFlag - Right _ -> WarningWithFlag Opt_WarnDataKindsTC + TcRnDataKindsError{} + -> ErrorWithoutFlag TcRnTypeSynonymCycle{} -> ErrorWithoutFlag TcRnZonkerMessage msg ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -2519,11 +2519,11 @@ data TcRnMessage where rename/should_fail/T22478e th/TH_Promoted1Tuple typecheck/should_compile/tcfail094 - typecheck/should_compile/T22141a - typecheck/should_compile/T22141b - typecheck/should_compile/T22141c - typecheck/should_compile/T22141d - typecheck/should_compile/T22141e + typecheck/should_fail/T22141a + typecheck/should_fail/T22141b + typecheck/should_fail/T22141c + typecheck/should_fail/T22141d + typecheck/should_fail/T22141e typecheck/should_compile/T22141f typecheck/should_compile/T22141g typecheck/should_fail/T20873c ===================================== compiler/GHC/Tc/Validity.hs ===================================== @@ -1000,18 +1000,11 @@ checkVdqOK ve tvbs ty = do -- | Check for a DataKinds violation in a kind context. -- See @Note [Checking for DataKinds]@. --- --- Note that emitting DataKinds errors from the typechecker is a fairly recent --- addition to GHC (introduced in GHC 9.10), and in order to prevent these new --- errors from breaking users' code, we temporarily downgrade these errors to --- warnings. (This is why we use 'diagnosticTcM' below.) See --- @Note [Checking for DataKinds] (Wrinkle: Migration story for DataKinds --- typechecker errors)@. checkDataKinds :: ValidityEnv -> Type -> TcM () checkDataKinds (ValidityEnv{ ve_ctxt = ctxt, ve_tidy_env = env }) ty = do data_kinds <- xoptM LangExt.DataKinds - diagnosticTcM - (not (data_kinds || typeLevelUserTypeCtxt ctxt)) $ + checkTcM + (data_kinds || typeLevelUserTypeCtxt ctxt) $ (env, TcRnDataKindsError KindLevel (Right (tidyType env ty))) {- Note [No constraints in kinds] @@ -1163,28 +1156,6 @@ different places in the code: synonym), so we also catch a subset of kind-level violations in the renamer to allow for earlier reporting of these errors. ------ --- Wrinkle: Migration story for DataKinds typechecker errors ------ - -As mentioned above, DataKinds is checked in two different places: the renamer -and the typechecker. The checks in the renamer have been around since DataKinds -was introduced. The checks in the typechecker, on the other hand, are a fairly -recent addition, having been introduced in GHC 9.10. As such, it is possible -that there are some programs in the wild that (1) do not enable DataKinds, and -(2) were accepted by a previous GHC version, but would now be rejected by the -new DataKinds checks in the typechecker. - -To prevent the new DataKinds checks in the typechecker from breaking users' -code, we temporarily allow programs to compile if they violate a DataKinds -check in the typechecker, but GHC will emit a warning if such a violation -occurs. Users can then silence the warning by enabling DataKinds in the module -where the affected code lives. It is fairly straightforward to distinguish -between DataKinds violations arising from the renamer versus the typechecker, -as TcRnDataKindsError (the error message type classifying all DataKinds errors) -stores an Either field that is Left when the error comes from the renamer and -Right when the error comes from the typechecker. - ************************************************************************ * * \subsection{Checking a theta or source type} ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -40,6 +40,21 @@ Language * Multiline strings are now accepted in foreign imports. (#25157) +* The ``-Wdata-kinds-tc`` warning has been removed, and the use of promoted + data types in kinds is now an error (rather than a warning) unless the + :extension:`DataKinds` extension is enabled. For example, the following code + will be rejected unless :extension:`DataKinds` is on: + + import Data.Kind (Type) + import GHC.TypeNats (Nat) + + -- Nat shouldn't be allowed here without DataKinds + data Vec :: Nat -> Type -> Type + + (The ``-Wdata-kinds-tc`` warning was introduced in GHC 9.10 as part of a fix + for an accidental oversight in which programs like the one above were + mistakenly accepted without the use of :extension:`DataKinds`.) + Compiler ~~~~~~~~ ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -82,7 +82,6 @@ as ``-Wno-...`` for every individual warning in the group. * :ghc-flag:`-Winconsistent-flags` * :ghc-flag:`-Wnoncanonical-monoid-instances` * :ghc-flag:`-Wnoncanonical-monad-instances` - * :ghc-flag:`-Wdata-kinds-tc` .. ghc-flag:: -W :shortdesc: enable normal warnings @@ -2535,26 +2534,6 @@ of ``-W(no-)*``. issued. Another example is :ghc-flag:`-dynamic` is ignored when :ghc-flag:`-dynamic-too` is passed. -.. ghc-flag:: -Wdata-kinds-tc - :shortdesc: warn when an illegal use of a type or kind without - :extension:`DataKinds` is caught by the typechecker - :type: dynamic - :reverse: -Wno-data-kinds-tc - - :since: 9.10.1 - - Introduced in GHC 9.10.1, this warns when an illegal use of a type or kind - (without having enabled the :extension:`DataKinds` extension) is caught in - the typechecker (hence the ``-tc`` suffix). These warnings complement the - existing :extension:`DataKinds` checks (that have existed since - :extension:`DataKinds` was first introduced), which result in errors - instead of warnings. - - This warning is scheduled to be changed to an error in a future GHC - version, at which point the :ghc-flag:`-Wdata-kinds-tc` flag will be - removed. Users can enable the :extension:`DataKinds` extension to avoid - issues (thus silencing the warning). - .. ghc-flag:: -Wdefaulted-exception-context :shortdesc: warn when an :base-ref:`Control.Exception.Context.ExceptionContext` implicit parameter is defaulted to ===================================== testsuite/tests/typecheck/should_compile/T22141a.stderr deleted ===================================== @@ -1,8 +0,0 @@ -T22141a.hs:8:1: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘Nat’ - In the data type declaration for ‘Vector’ - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/T22141b.stderr deleted ===================================== @@ -1,9 +0,0 @@ -T22141b.hs:10:1: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘Nat’ - In the expansion of type synonym ‘MyNat’ - In the data type declaration for ‘Vector’ - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/T22141c.stderr deleted ===================================== @@ -1,37 +0,0 @@ -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘(# *, * #)’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘T’ - In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘'[]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘'[GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘[GHC.Internal.Types.LiftedRep, - GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141c.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘Proxy T’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/T22141d.stderr deleted ===================================== @@ -1,37 +0,0 @@ -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘(# * | * #)’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘T’ - In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘'[]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘'[GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘[GHC.Internal.Types.LiftedRep, - GHC.Internal.Types.LiftedRep]’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141d.hs:10:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘Proxy T’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/T22141e.stderr deleted ===================================== @@ -1,22 +0,0 @@ -T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘42’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In the expansion of type synonym ‘T’ - In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘GHC.Internal.Bignum.Natural.Natural’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - -T22141e.hs:8:11: warning: [GHC-68567] [-Wdata-kinds-tc (in -Wdefault)] - • An occurrence of ‘Proxy T’ in a kind requires DataKinds. - Future versions of GHC will turn this warning into an error. - • In a standalone kind signature for ‘D’: Proxy T -> Type - Suggested fix: - Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) - ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -862,11 +862,6 @@ test('T21951a', normal, compile, ['-Wredundant-strictness-flags']) test('T21951b', normal, compile, ['-Wredundant-strictness-flags']) test('DataToTagSolving', normal, compile, ['']) test('T21550', normal, compile, ['']) -test('T22141a', normal, compile, ['']) -test('T22141b', normal, compile, ['']) -test('T22141c', normal, compile, ['']) -test('T22141d', normal, compile, ['']) -test('T22141e', [extra_files(['T22141e_Aux.hs'])], multimod_compile, ['T22141e.hs', '-v0']) test('T22141f', normal, compile, ['']) test('T22141g', normal, compile, ['']) test('T22310', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T20873c.hs ===================================== @@ -7,5 +7,8 @@ import Data.Kind ( Type ) type U a = Type -data Foo :: U Int where +-- This should be allowed without enabling DataKinds, This is because the return +-- kind only mentions Type, which is always permitted in kinds, and U, which is +-- simply a type synonym that expands to Type. +data Foo :: U Type where MkFoo :: Foo ===================================== testsuite/tests/typecheck/should_fail/T20873c.stderr ===================================== @@ -1,5 +1,5 @@ -T20873c.hs:10:1: error: [GHC-49378] - • Illegal kind signature ‘Foo :: U Int’ +T20873c.hs:13:1: error: [GHC-49378] + • Illegal kind signature ‘Foo :: U Type’ • In the data type declaration for ‘Foo’ Suggested fix: Perhaps you intended to use the ‘KindSignatures’ extension (implied by ‘TypeFamilies’ and ‘PolyKinds’) ===================================== testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141a.stderr ===================================== @@ -1,6 +1,7 @@ - T22141a.hs:8:1: error: [GHC-68567] - • Illegal kind: ‘GHC.Num.Natural.Natural’ + • Illegal kind: ‘GHC.Internal.Bignum.Natural.Natural’ • In the expansion of type synonym ‘Nat’ In the data type declaration for ‘Vector’ - Suggested fix: Perhaps you intended to use DataKinds + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) + ===================================== testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141b.stderr ===================================== @@ -1,7 +1,8 @@ - T22141b.hs:10:1: error: [GHC-68567] - • Illegal kind: ‘GHC.Num.Natural.Natural’ + • Illegal kind: ‘GHC.Internal.Bignum.Natural.Natural’ • In the expansion of type synonym ‘Nat’ In the expansion of type synonym ‘MyNat’ In the data type declaration for ‘Vector’ - Suggested fix: Perhaps you intended to use DataKinds + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) + ===================================== testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141c.stderr ===================================== @@ -1,4 +1,6 @@ +T22141c.hs:10:11: error: [GHC-68567] + • Illegal kind: ‘Proxy T’ + • In a standalone kind signature for ‘D’: Proxy T -> Type + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) -T22141c.hs:8:17: error: [GHC-68567] - Illegal kind: ‘(# Type, Type #)’ - Suggested fix: Perhaps you intended to use DataKinds ===================================== testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141d.stderr ===================================== @@ -1,4 +1,6 @@ +T22141d.hs:10:11: error: [GHC-68567] + • Illegal kind: ‘Proxy T’ + • In a standalone kind signature for ‘D’: Proxy T -> Type + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) -T22141d.hs:8:17: error: [GHC-68567] - Illegal kind: ‘(# Type | Type #)’ - Suggested fix: Perhaps you intended to use DataKinds ===================================== testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/T22141e.stderr ===================================== @@ -1,4 +1,6 @@ +T22141e.hs:8:11: error: [GHC-68567] + • Illegal kind: ‘Proxy T’ + • In a standalone kind signature for ‘D’: Proxy T -> Type + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) -T22141e.hs:7:17: error: [GHC-68567] - Illegal kind: ‘42’ - Suggested fix: Perhaps you intended to use DataKinds ===================================== testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs ===================================== ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -666,6 +666,11 @@ test('T21447', normal, compile_fail, ['']) test('T21530a', normal, compile_fail, ['']) test('T21530b', normal, compile_fail, ['']) test('Or4', normal, compile_fail, ['']) +test('T22141a', normal, compile_fail, ['']) +test('T22141b', normal, compile_fail, ['']) +test('T22141c', normal, compile_fail, ['']) +test('T22141d', normal, compile_fail, ['']) +test('T22141e', [extra_files(['T22141e_Aux.hs'])], multimod_compile_fail, ['T22141e.hs', '-v0']) test('T22570', normal, compile_fail, ['']) test('T22645', normal, compile_fail, ['']) test('T20666', normal, compile_fail, ['']) ===================================== testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE RequiredTypeArguments #-} module T23739_fail_case where ===================================== testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr ===================================== @@ -1,7 +1,6 @@ - -T23739_fail_case.hs:7:8: error: [GHC-01928] +T23739_fail_case.hs:8:8: error: [GHC-01928] • Illegal term-level use of the type variable ‘t’ - • bound at T23739_fail_case.hs:6:5 + • bound at T23739_fail_case.hs:7:5 • In the expression: t In the expression: case t of @@ -12,3 +11,4 @@ T23739_fail_case.hs:7:8: error: [GHC-01928] = case t of False -> "False" True -> "True" + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6db8d60540aa68807cf82e7237e425de97ef143f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6db8d60540aa68807cf82e7237e425de97ef143f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/95f09859/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 12:24:12 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 06 Mar 2025 07:24:12 -0500 Subject: [Git][ghc/ghc][wip/t25571] 3 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67c993ec9738f_20b3799f18fc532e0@gitlab.mail> Matthew Pickering pushed to branch wip/t25571 at Glasgow Haskell Compiler / GHC Commits: a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 21c971e0 by Matthew Pickering at 2025-03-06T11:43:23+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 35 changed files: - compiler/GHC.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fbe973e4aff63e953415337cba57aad42fb9fc75...21c971e03ab175dd416b74931d245ed92d4f9634 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fbe973e4aff63e953415337cba57aad42fb9fc75...21c971e03ab175dd416b74931d245ed92d4f9634 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/e7c6cb78/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 12:27:47 2025 From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo)) Date: Thu, 06 Mar 2025 07:27:47 -0500 Subject: [Git][ghc/ghc][wip/T25705-1] 2 commits: template-haskell: Add explicit exports lists to all remaining modules Message-ID: <67c994c3116ae_20b37994073c5387a@gitlab.mail> Teo Camarasu pushed to branch wip/T25705-1 at Glasgow Haskell Compiler / GHC Commits: 08b8ae6f by Teo Camarasu at 2025-03-06T12:27:36+00:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - 3c629d1f by Teo Camarasu at 2025-03-06T12:27:36+00:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks Resolves #25705 - - - - - 7 changed files: - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html Changes: ===================================== libraries/template-haskell/Language/Haskell/TH/Ppr.hs ===================================== @@ -1,9 +1,91 @@ {-# LANGUAGE Safe #-} --- | contains a prettyprinter for the --- Template Haskell datatypes -module Language.Haskell.TH.Ppr - ( module GHC.Boot.TH.Ppr ) - where +{- | contains a prettyprinter for the +Template Haskell datatypes +-} +module Language.Haskell.TH.Ppr ( + appPrec, + bar, + bytesToString, + commaSep, + commaSepApplied, + commaSepWith, + fromTANormal, + funPrec, + hashParens, + isStarT, + isSymOcc, + nestDepth, + noPrec, + opPrec, + parensIf, + pprBangType, + pprBndrVis, + pprBody, + pprClause, + pprCtxWith, + pprCxt, + pprExp, + pprFields, + pprFixity, + pprForall, + pprForall', + pprForallVis, + pprFunArgType, + pprGadtRHS, + pprGuarded, + pprInfixExp, + pprInfixT, + pprLit, + pprMatchPat, + pprMaybeExp, + pprNamespaceSpecifier, + pprParendType, + pprParendTypeArg, + pprPat, + pprPatSynSig, + pprPatSynType, + pprPrefixOcc, + pprRecFields, + pprStrictType, + pprString, + pprTyApp, + pprTyLit, + pprType, + pprVarBangType, + pprVarStrictType, + ppr_bndrs, + ppr_ctx_preds_with, + ppr_cxt_preds, + ppr_data, + ppr_dec, + ppr_deriv_clause, + ppr_deriv_strategy, + ppr_newtype, + ppr_overlap, + ppr_sig, + ppr_tf_head, + ppr_tySyn, + ppr_type_data, + ppr_typedef, + pprint, + qualPrec, + quoteParens, + semiSep, + semiSepWith, + sepWith, + showtextl, + sigPrec, + split, + unboxedSumBars, + unopPrec, + where_clause, + ForallVisFlag (..), + Ppr (..), + PprFlag (..), + Precedence, + TypeArg (..), +) +where import GHC.Boot.TH.Ppr ===================================== libraries/template-haskell/Language/Haskell/TH/PprLib.hs ===================================== @@ -1,8 +1,56 @@ {-# LANGUAGE Safe #-} -- | Monadic front-end to Text.PrettyPrint -module Language.Haskell.TH.PprLib - ( module GHC.Boot.TH.PprLib ) - where +module Language.Haskell.TH.PprLib ( + ($$), + ($+$), + (<+>), + (<>), + arrow, + braces, + brackets, + cat, + char, + colon, + comma, + dcolon, + double, + doubleQuotes, + empty, + equals, + fcat, + float, + fsep, + hang, + hcat, + hsep, + int, + integer, + isEmpty, + lbrace, + lbrack, + lparen, + nest, + parens, + pprName, + pprName', + ptext, + punctuate, + quotes, + rational, + rbrace, + rbrack, + rparen, + semi, + sep, + space, + text, + to_HPJ_Doc, + vcat, + Doc, + PprM, +) +where +import Prelude hiding ((<>)) import GHC.Boot.TH.PprLib ===================================== libraries/template-haskell/Language/Haskell/TH/Syntax.hs ===================================== @@ -1,22 +1,206 @@ {-# LANGUAGE MagicHash #-} -{-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TemplateHaskellQuotes #-} {-# LANGUAGE Trustworthy #-} -module Language.Haskell.TH.Syntax - ( module GHC.Boot.TH.Syntax - , makeRelativeToProject - , module GHC.Boot.TH.Lift - , addrToByteArrayName - , addrToByteArray - ) +{-# LANGUAGE UnboxedTuples #-} + +module Language.Haskell.TH.Syntax ( + Quote (..), + Exp (..), + Match (..), + Clause (..), + Q (..), + Pat (..), + Stmt (..), + Con (..), + Type (..), + Dec (..), + BangType, + VarBangType, + FieldExp, + FieldPat, + Name (..), + FunDep (..), + Pred, + RuleBndr (..), + TySynEqn (..), + InjectivityAnn (..), + Kind, + Overlap (..), + DerivClause (..), + DerivStrategy (..), + Code (..), + ModName (..), + addCorePlugin, + addDependentFile, + addForeignFile, + addForeignFilePath, + addForeignSource, + addModFinalizer, + addTempFile, + addTopDecls, + badIO, + bindCode, + bindCode_, + cmpEq, + compareBytes, + counter, + defaultFixity, + eqBytes, + extsEnabled, + getDoc, + getPackageRoot, + getQ, + get_cons_names, + hoistCode, + isExtEnabled, + isInstance, + joinCode, + liftCode, + location, + lookupName, + lookupTypeName, + lookupValueName, + manyName, + maxPrecedence, + memcmp, + mkNameG, + mkNameU, + mkOccName, + mkPkgName, + mk_tup_name, + mkName, + mkNameG_v, + mkNameG_d, + mkNameG_tc, + mkNameL, + mkNameS, + unTypeCode, + mkModName, + unsafeCodeCoerce, + mkNameQ, + mkNameG_fld, + modString, + nameBase, + nameModule, + namePackage, + nameSpace, + newDeclarationGroup, + newNameIO, + occString, + oneName, + pkgString, + putDoc, + putQ, + recover, + reify, + reifyAnnotations, + reifyConStrictness, + reifyFixity, + reifyInstances, + reifyModule, + reifyRoles, + reifyType, + report, + reportError, + reportWarning, + runIO, + sequenceQ, + runQ, + showName, + showName', + thenCmp, + tupleDataName, + tupleTypeName, + unTypeQ, + unboxedSumDataName, + unboxedSumTypeName, + unboxedTupleDataName, + unboxedTupleTypeName, + unsafeTExpCoerce, + ForeignSrcLang (..), + Extension (..), + AnnLookup (..), + AnnTarget (..), + Arity, + Bang (..), + BndrVis (..), + Body (..), + Bytes (..), + Callconv (..), + CharPos, + Cxt, + DecidedStrictness (..), + DocLoc (..), + FamilyResultSig (..), + Fixity (..), + FixityDirection (..), + Foreign (..), + Guard (..), + Info (..), + Inline (..), + InstanceDec, + Lit (..), + Loc (..), + Module (..), + ModuleInfo (..), + NameFlavour (..), + NameIs (..), + NameSpace (..), + NamespaceSpecifier (..), + OccName (..), + ParentName, + PatSynArgs (..), + PatSynDir (..), + PatSynType, + Phases (..), + PkgName (..), + Pragma (..), + Quasi (..), + Range (..), + Role (..), + RuleMatch (..), + Safety (..), + SourceStrictness (..), + SourceUnpackedness (..), + Specificity (..), + Strict, + StrictType, + SumAlt, + SumArity, + TExp (..), + TyLit (..), + TyVarBndr (..), + TypeFamilyHead (..), + Uniq, + Unlifted, + VarStrictType, + makeRelativeToProject, + liftString, + Lift (..), + dataToCodeQ, + dataToExpQ, + dataToPatQ, + dataToQa, + falseName, + justName, + leftName, + liftData, + liftDataTyped, + nonemptyName, + nothingName, + rightName, + trueName, + addrToByteArrayName, + addrToByteArray, +) where -import GHC.Boot.TH.Syntax -import GHC.Boot.TH.Lift -import System.FilePath import Data.Array.Byte +import GHC.Boot.TH.Lift +import GHC.Boot.TH.Syntax import GHC.Exts import GHC.ST +import System.FilePath -- This module completely re-exports 'GHC.Boot.TH.Syntax', -- and exports additionally functions that depend on filepath. @@ -41,4 +225,3 @@ addrToByteArray (I# len) addr = runST $ ST $ (# s', mb #) -> case copyAddrToByteArray# addr mb 0# len s' of s'' -> case unsafeFreezeByteArray# mb s'' of (# s''', ret #) -> (# s''', ByteArray ret #) - ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -53,6 +53,10 @@ Library build-depends: base >= 4.11 && < 4.22, + -- We don't directly depend on any of the modules from `ghc-internal` + -- But we need to depend on it to work around a Haddock bug. + -- See: https://gitlab.haskell.org/ghc/ghc/-/issues/25705 + ghc-internal == @ProjectVersionForLib at .*, ghc-boot-th == @ProjectVersionMunged@ other-modules: ===================================== utils/haddock/html-test/ref/QuasiExpr.html ===================================== @@ -335,9 +335,9 @@ >parseExprExp</a > :: <a href="#" title="Data.String" >String</a - > -> <a href="#" title="Language.Haskell.TH" + > -> <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a > <a href="#" class="selflink" >#</a ===================================== utils/haddock/html-test/ref/TH.html ===================================== @@ -55,9 +55,9 @@ ><p class="src" ><a id="v:decl" class="def" >decl</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > [<a href="#" title="Language.Haskell.TH" + > [<a href="#" title="Language.Haskell.TH.Syntax" >Dec</a >] <a href="#" class="selflink" >#</a ===================================== utils/haddock/html-test/ref/Threaded_TH.html ===================================== @@ -67,9 +67,9 @@ ><li class="src short" ><a href="#" >forkTH</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a ></li ></ul @@ -82,9 +82,9 @@ ><p class="src" ><a id="v:forkTH" class="def" >forkTH</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a > <a href="#" class="selflink" >#</a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57c25aca5f5371d5ff05a67d113e814c27b551f3...3c629d1f4dbb41d38c227ee80e0f35c9aaabd653 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57c25aca5f5371d5ff05a67d113e814c27b551f3...3c629d1f4dbb41d38c227ee80e0f35c9aaabd653 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/fed9e76d/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 15:12:51 2025 From: gitlab at gitlab.haskell.org (Oleg Grenrus (@phadej)) Date: Thu, 06 Mar 2025 10:12:51 -0500 Subject: [Git][ghc/ghc][wip/fix-whitespace] 71 commits: Deal correctly with Given CallStack constraints Message-ID: <67c9bb736e2b7_25debc16dac8523f1@gitlab.mail> Oleg Grenrus pushed to branch wip/fix-whitespace at Glasgow Haskell Compiler / GHC Commits: e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-â” |---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | â””-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a98415a3 by Oleg Grenrus at 2025-03-06T17:12:26+02:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 341 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/wasm/JSFFI.c - testsuite/driver/testlib.py - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/all.T - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8ed840b6653ad1121695a168ea6b89a142ee8369...a98415a37b5cbd47101e3f84c2162a2205ca1467 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8ed840b6653ad1121695a168ea6b89a142ee8369...a98415a37b5cbd47101e3f84c2162a2205ca1467 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/38fe9a43/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 16:25:49 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Thu, 06 Mar 2025 11:25:49 -0500 Subject: [Git][ghc/ghc][wip/testsuite-no-cusks] 6258 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <67c9cc8d2f511_26d1c864ff7859313@gitlab.mail> Vladislav Zavialov pushed to branch wip/testsuite-no-cusks at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by GergÅ‘ Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by GergÅ‘ Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by GergÅ‘ Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by GergÅ‘ Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by GergÅ‘ Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by GergÅ‘ Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by GergÅ‘ Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by GergÅ‘ Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by GergÅ‘ Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Åukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Åukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Åukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Åukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Åukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Åukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Åukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Åukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Åukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Åukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Åukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Åukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Åukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Åukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Åukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Åukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Åukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Åukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Åukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Åukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Åukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Åukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Åukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Åukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Åukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Åukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Åukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Åukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Åukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Åukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Åukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Åukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Åukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Åukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Åukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Åukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Åukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Åukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Åukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Åukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Åukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Åukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Åukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Åukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Åukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Åukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Åukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Åukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Åukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Åukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Åukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Åukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Åukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Åukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Åukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Åukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Åukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Åukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Åukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Åukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Åukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Åukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Åukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Åukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Åukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Åukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Åukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Åukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Åukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Åukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Åukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Åukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Åukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Åukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Åukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Åukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Åukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Åukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Åukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Åukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Åukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Åukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Åukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Åukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Åukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Åukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan AÄŸacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `"` as the `xml` lib did * we don't add extra ` ` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by MatthÃas Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki GarcÃa Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by MatthÃas Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by MatthÃas Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki GarcÃa Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default†langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by BartÅ‚omiej CieÅ›lar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: BartÅ‚omiej CieÅ›lar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by BartÅ‚omiej CieÅ›lar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: BartÅ‚omiej CieÅ›lar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by BartÅ‚omiej CieÅ›lar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: BartÅ‚omiej CieÅ›lar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - 42b05e9b by sheaf at 2023-07-22T12:36:00-04:00 RTS: declare setKeepCAFs symbol Commit 08ba8720 failed to declare the dependency of keepCAFsForGHCi on the symbol setKeepCAFs in the RTS, which led to undefined symbol errors on Windows, as exhibited by the testcase frontend001. Thanks to Moritz Angermann and Ryan Scott for the diagnosis and fix. Fixes #22961 - - - - - a72015d6 by sheaf at 2023-07-22T12:36:01-04:00 Mark plugins-external as broken on Windows This test is broken on Windows, so we explicitly mark it as such now that we stop skipping plugin tests on Windows. - - - - - cb9c93d7 by sheaf at 2023-07-22T12:36:01-04:00 Stop marking plugin tests as fragile on Windows Now that b2bb3e62 has landed we are in a better situation with regards to plugins on Windows, allowing us to unmark many plugin tests as fragile. Fixes #16405 - - - - - a7349217 by Krzysztof Gogolewski at 2023-07-22T12:36:37-04:00 Misc cleanup - Remove unused RDR names - Fix typos in comments - Deriving: simplify boxConTbl and remove unused litConTbl - chmod -x GHC/Exts.hs, this seems accidental - - - - - 33b6850a by Vladislav Zavialov at 2023-07-23T10:27:37-04:00 Visible forall in types of terms: Part 1 (#22326) This patch implements part 1 of GHC Proposal #281, introducing explicit `type` patterns and `type` arguments. Summary of the changes: 1. New extension flag: RequiredTypeArguments 2. New user-facing syntax: `type p` patterns (represented by EmbTyPat) `type e` expressions (represented by HsEmbTy) 3. Functions with required type arguments (visible forall) can now be defined and applied: idv :: forall a -> a -> a -- signature (relevant change: checkVdqOK in GHC/Tc/Validity.hs) idv (type a) (x :: a) = x -- definition (relevant change: tcPats in GHC/Tc/Gen/Pat.hs) x = idv (type Int) 42 -- usage (relevant change: tcInstFun in GHC/Tc/Gen/App.hs) 4. template-haskell support: TH.TypeE corresponds to HsEmbTy TH.TypeP corresponds to EmbTyPat 5. Test cases and a new User's Guide section Changes *not* included here are the t2t (term-to-type) transformation and term variable capture; those belong to part 2. - - - - - 73b5c7ce by sheaf at 2023-07-23T10:28:18-04:00 Add test for #22424 This is a simple Template Haskell test in which we refer to record selectors by their exact Names, in two different ways. Fixes #22424 - - - - - 83cbc672 by Ben Gamari at 2023-07-24T07:40:49+00:00 ghc-toolchain: Initial commit - - - - - 31dcd26c by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 ghc-toolchain: Toolchain Selection This commit integrates ghc-toolchain, the brand new way of configuring toolchains for GHC, with the Hadrian build system, with configure, and extends and improves the first iteration of ghc-toolchain. The general overview is * We introduce a program invoked `ghc-toolchain --triple=...` which, when run, produces a file with a `Target`. A `GHC.Toolchain.Target.Target` describes the properties of a target and the toolchain (executables and configured flags) to produce code for that target * Hadrian was modified to read Target files, and will both * Invoke the toolchain configured in the Target file as needed * Produce a `settings` file for GHC based on the Target file for that stage * `./configure` will invoke ghc-toolchain to generate target files, but it will also generate target files based on the flags configure itself configured (through `.in` files that are substituted) * By default, the Targets generated by configure are still (for now) the ones used by Hadrian * But we additionally validate the Target files generated by ghc-toolchain against the ones generated by configure, to get a head start on catching configuration bugs before we transition completely. * When we make that transition, we will want to drop a lot of the toolchain configuration logic from configure, but keep it otherwise. * For each compiler stage we should have 1 target file (up to a stage compiler we can't run in our machine) * We just have a HOST target file, which we use as the target for stage0 * And a TARGET target file, which we use for stage1 (and later stages, if not cross compiling) * Note there is no BUILD target file, because we only support cross compilation where BUILD=HOST * (for more details on cross-compilation see discussion on !9263) See also * Note [How we configure the bundled windows toolchain] * Note [ghc-toolchain consistency checking] * Note [ghc-toolchain overview] Ticket: #19877 MR: !9263 - - - - - a732b6d3 by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Add flag to enable/disable ghc-toolchain based configurations This flag is disabled by default, and we'll use the configure-generated-toolchains by default until we remove the toolchain configuration logic from configure. - - - - - 61eea240 by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Split ghc-toolchain executable to new packge In light of #23690, we split the ghc-toolchain executable out of the library package to be able to ship it in the bindist using Hadrian. Ideally, we eventually revert this commit. - - - - - 38e795ff by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Ship ghc-toolchain in the bindist Add the ghc-toolchain binary to the binary distribution we ship to users, and teach the bindist configure to use the existing ghc-toolchain. - - - - - 32cae784 by Matthew Craven at 2023-07-24T16:48:24-04:00 Kill off gen_bytearray_addr_access_ops.py The relevant primop descriptions are now generated directly by genprimopcode. This makes progress toward fixing #23490, but it is not a complete fix since there is more than one way in which cabal-reinstall (hadrian/build build-cabal) is broken. - - - - - 02e6a6ce by Matthew Pickering at 2023-07-24T16:49:00-04:00 compiler: Remove unused `containers.h` include Fixes #23712 - - - - - 822ef66b by Matthew Pickering at 2023-07-25T08:44:50-04:00 Fix pretty printing of WARNING pragmas There is still something quite unsavoury going on with WARNING pragma printing because the printing relies on the fact that for decl deprecations the SourceText of WarningTxt is empty. However, I let that lion sleep and just fixed things directly. Fixes #23465 - - - - - e7b38ede by Matthew Pickering at 2023-07-25T08:45:28-04:00 ci-images: Bump to commit which has 9.6 image The test-bootstrap job has been failing for 9.6 because we accidentally used a non-master commit. - - - - - bb408936 by Matthew Pickering at 2023-07-25T08:45:28-04:00 Update bootstrap plans for 9.6.2 and 9.4.5 - - - - - 355e1792 by Alan Zimmerman at 2023-07-26T10:17:32-04:00 EPA: Simplify GHC/Parser.y comb4/comb5 Use the HasLoc instance from Ast.hs to allow comb4/comb5 to work with anything with a SrcSpan Also get rid of some more now unnecessary reLoc calls. - - - - - 9393df83 by Gavin Zhao at 2023-07-26T10:18:16-04:00 compiler: make -ddump-asm work with wasm backend NCG Fixes #23503. Now the `-ddump-asm` flag is respected in the wasm backend NCG, so developers can directly view the generated ASM instead of needing to pass `-S` or `-keep-tmp-files` and manually find & open the assembly file. Ideally, we should be able to output the assembly files in smaller chunks like in other NCG backends. This would also make dumping assembly stats easier. However, this would require a large refactoring, so for short-term debugging purposes I think the current approach works fine. Signed-off-by: Gavin Zhao <git at gzgz.dev> - - - - - 79463036 by Krzysztof Gogolewski at 2023-07-26T10:18:54-04:00 llvm: Restore accidentally deleted code in 0fc5cb97 Fixes #23711 - - - - - 20db7e26 by Rodrigo Mesquita at 2023-07-26T10:19:33-04:00 configure: Default missing options to False when preparing ghc-toolchain Targets This commit fixes building ghc with 9.2 as the boostrap compiler. The ghc-toolchain patch assumed all _STAGE0 options were available, and forgot to account for this missing information in 9.2. Ghc 9.2 does not have in settings whether ar supports -l, hence can't report it with --info (unliked 9.4 upwards). The fix is to default the missing information (we default "ar supports -l" and other missing options to False) - - - - - fac9e84e by Naïm Favier at 2023-07-26T10:20:16-04:00 docs: Fix typo - - - - - 503fd647 by BartÅ‚omiej CieÅ›lar at 2023-07-26T17:23:10-04:00 This MR is an implementation of the proposal #516. It adds a warning -Wincomplete-record-selectors for usages of a record field access function (either a record selector or getField @"rec"), while trying to silence the warning whenever it can be sure that a constructor without the record field would not be invoked (which would otherwise cause the program to fail). For example: data T = T1 | T2 {x :: Bool} f a = x a -- this would throw an error g T1 = True g a = x a -- this would not throw an error h :: HasField "x" r Bool => r -> Bool h = getField @"x" j :: T -> Bool j = h -- this would throw an error because of the `HasField` -- constraint being solved See the tests DsIncompleteRecSel* and TcIncompleteRecSel for more examples of the warning. See Note [Detecting incomplete record selectors] in GHC.HsToCore.Expr for implementation details - - - - - af6fdf42 by Arnaud Spiwack at 2023-07-26T17:23:52-04:00 Fix user-facing label in MR template - - - - - 5d45b92a by Matthew Pickering at 2023-07-27T05:46:46-04:00 ci: Test bootstrapping configurations with full-ci and on marge batches There have been two incidents recently where bootstrapping has been broken by removing support for building with 9.2.*. The process for bumping the minimum required version starts with bumping the configure version and then other CI jobs such as the bootstrap jobs have to be updated. We must not silently bump the minimum required version. Now we are running a slimmed down validate pipeline it seems worthwile to test these bootstrap configurations in the full-ci pipeline. - - - - - 25d4fee7 by Matthew Pickering at 2023-07-27T05:46:46-04:00 bootstrap: Remove ghc-9_2_* plans We are anticipating shortly making it necessary to use ghc-9.4 to boot the compiler. - - - - - 2f66da16 by Matthew Pickering at 2023-07-27T05:46:46-04:00 Update bootstrap plans for ghc-platform and ghc-toolchain dependencies Fixes #23735 - - - - - c8c6eab1 by Matthew Pickering at 2023-07-27T05:46:46-04:00 bootstrap: Disable -selftest flag from bootstrap plans This saves on building one dependency (QuickCheck) which is unecessary for bootstrapping. - - - - - a80ca086 by Andrew Lelechenko at 2023-07-27T05:47:26-04:00 Link reference paper and package from System.Mem.{StableName,Weak} - - - - - a5319358 by David Knothe at 2023-07-28T13:13:10-04:00 Update Match Datatype EquationInfo currently contains a list of the equation's patterns together with a CoreExpr that is to be evaluated after a successful match on this equation. All the match-functions only operate on the first pattern of an equation - after successfully matching it, match is called recursively on the tail of the pattern list. We can express this more clearly and make the code a little more elegant by updating the datatype of EquationInfo as follows: data EquationInfo = EqnMatch { eqn_pat = Pat GhcTc, eqn_rest = EquationInfo } | EqnDone { eqn_rhs = MatchResult CoreExpr } An EquationInfo now explicitly exposes its first pattern which most functions operate on, and exposes the equation that remains after processing the first pattern. An EqnDone signifies an empty equation where the CoreExpr can now be evaluated. - - - - - 86ad1af9 by David Binder at 2023-07-28T13:13:53-04:00 Improve documentation for Data.Fixed - - - - - f8fa1d08 by Ben Gamari at 2023-07-28T13:14:31-04:00 ghc-prim: Use C11 atomics Previously `ghc-prim`'s atomic wrappers used the legacy `__sync_*` family of C builtins. Here we refactor these to rather use the appropriate C11 atomic equivalents, allowing us to be more explicit about the expected ordering semantics. - - - - - 0bfc8908 by Finley McIlwaine at 2023-07-28T18:46:26-04:00 Include -haddock in DynFlags fingerprint The -haddock flag determines whether or not the resulting .hi files contain haddock documentation strings. If the existing .hi files do not contain haddock documentation strings and the user requests them, we should recompile. - - - - - 40425c50 by Andreas Klebinger at 2023-07-28T18:47:02-04:00 Aarch64 NCG: Use encoded immediates for literals. Try to generate instr x2, <imm> instead of mov x1, lit instr x2, x1 When possible. This get's rid if quite a few redundant mov instructions. I believe this causes a metric decrease for LargeRecords as we reduce register pressure. ------------------------- Metric Decrease: LargeRecord ------------------------- - - - - - e9a0fa3f by Andrew Lelechenko at 2023-07-28T18:47:42-04:00 Bump filepath submodule to 1.4.100.4 Resolves #23741 Metric Decrease: MultiComponentModules MultiComponentModulesRecomp MultiLayerModules MultiLayerModulesRecomp T10421 T12234 T12425 T13035 T13701 T13719 T16875 T18304 T18698a T18698b T21839c T9198 TcPlugin_RewritePerf hard_hole_fits Metric decrease on Windows can be probably attributed to https://github.com/haskell/filepath/pull/183 - - - - - ee93edfd by Andrew Lelechenko at 2023-07-28T18:48:21-04:00 Add since pragmas to GHC.IO.Handle.FD - - - - - d0369802 by Simon Peyton Jones at 2023-07-30T09:24:48+01:00 Make the occurrence analyser smarter about join points This MR addresses #22404. There is a big Note Note [Occurrence analysis for join points] that explains it all. Significant changes * New field occ_join_points in OccEnv * The NonRec case of occAnalBind splits into two cases: one for existing join points (which does the special magic for Note [Occurrence analysis for join points], and one for other bindings. * mkOneOcc adds in info from occ_join_points. * All "bring into scope" activity is centralised in the new function `addInScope`. * I made a local data type LocalOcc for use inside the occurrence analyser It is like OccInfo, but lacks IAmDead and IAmALoopBreaker, which in turn makes computationns over it simpler and more efficient. * I found quite a bit of allocation in GHC.Core.Rules.getRules so I optimised it a bit. More minor changes * I found I was using (Maybe Arity) a lot, so I defined a new data type JoinPointHood and used it everwhere. This touches a lot of non-occ-anal files, but it makes everything more perspicuous. * Renamed data constructor WithUsageDetails to WUD, and WithTailUsageDetails to WTUD This also fixes #21128, on the way. --------- Compiler perf ----------- I spent quite a time on performance tuning, so even though it does more than before, the occurrence analyser runs slightly faster on average. Here are the compile-time allocation changes over 0.5% CoOpt_Read(normal) ghc/alloc 766,025,520 754,561,992 -1.5% CoOpt_Singletons(normal) ghc/alloc 759,436,840 762,925,512 +0.5% LargeRecord(normal) ghc/alloc 1,814,482,440 1,799,530,456 -0.8% PmSeriesT(normal) ghc/alloc 68,159,272 67,519,720 -0.9% T10858(normal) ghc/alloc 120,805,224 118,746,968 -1.7% T11374(normal) ghc/alloc 164,901,104 164,070,624 -0.5% T11545(normal) ghc/alloc 79,851,808 78,964,704 -1.1% T12150(optasm) ghc/alloc 73,903,664 71,237,544 -3.6% GOOD T12227(normal) ghc/alloc 333,663,200 331,625,864 -0.6% T12234(optasm) ghc/alloc 52,583,224 52,340,344 -0.5% T12425(optasm) ghc/alloc 81,943,216 81,566,720 -0.5% T13056(optasm) ghc/alloc 294,517,928 289,642,512 -1.7% T13253-spj(normal) ghc/alloc 118,271,264 59,859,040 -49.4% GOOD T15164(normal) ghc/alloc 1,102,630,352 1,091,841,296 -1.0% T15304(normal) ghc/alloc 1,196,084,000 1,166,733,000 -2.5% T15630(normal) ghc/alloc 148,729,632 147,261,064 -1.0% T15703(normal) ghc/alloc 379,366,664 377,600,008 -0.5% T16875(normal) ghc/alloc 32,907,120 32,670,976 -0.7% T17516(normal) ghc/alloc 1,658,001,888 1,627,863,848 -1.8% T17836(normal) ghc/alloc 395,329,400 393,080,248 -0.6% T18140(normal) ghc/alloc 71,968,824 73,243,040 +1.8% T18223(normal) ghc/alloc 456,852,568 453,059,088 -0.8% T18282(normal) ghc/alloc 129,105,576 131,397,064 +1.8% T18304(normal) ghc/alloc 71,311,712 70,722,720 -0.8% T18698a(normal) ghc/alloc 208,795,112 210,102,904 +0.6% T18698b(normal) ghc/alloc 230,320,736 232,697,976 +1.0% BAD T19695(normal) ghc/alloc 1,483,648,128 1,504,702,976 +1.4% T20049(normal) ghc/alloc 85,612,024 85,114,376 -0.6% T21839c(normal) ghc/alloc 415,080,992 410,906,216 -1.0% GOOD T4801(normal) ghc/alloc 247,590,920 250,726,272 +1.3% T6048(optasm) ghc/alloc 95,699,416 95,080,680 -0.6% T783(normal) ghc/alloc 335,323,384 332,988,120 -0.7% T9233(normal) ghc/alloc 709,641,224 685,947,008 -3.3% GOOD T9630(normal) ghc/alloc 965,635,712 948,356,120 -1.8% T9675(optasm) ghc/alloc 444,604,152 428,987,216 -3.5% GOOD T9961(normal) ghc/alloc 303,064,592 308,798,800 +1.9% BAD WWRec(normal) ghc/alloc 503,728,832 498,102,272 -1.1% geo. mean -1.0% minimum -49.4% maximum +1.9% In fact these figures seem to vary between platforms; generally worse on i386 for some reason. The Windows numbers vary by 1% espec in benchmarks where the total allocation is low. But the geom mean stays solidly negative, which is good. The "increase/decrease" list below covers all platforms. The big win on T13253-spj comes because it has a big nest of join points, each occurring twice in the next one. The new occ-anal takes only one iteration of the simplifier to do the inlining; the old one took four. Moreover, we get much smaller code with the new one: New: Result size of Tidy Core = {terms: 429, types: 84, coercions: 0, joins: 14/14} Old: Result size of Tidy Core = {terms: 2,437, types: 304, coercions: 0, joins: 10/10} --------- Runtime perf ----------- No significant changes in nofib results, except a 1% reduction in compiler allocation. Metric Decrease: CoOpt_Read T13253-spj T9233 T9630 T9675 T12150 T21839c LargeRecord MultiComponentModulesRecomp T10421 T13701 T10421 T13701 T12425 Metric Increase: T18140 T9961 T18282 T18698a T18698b T19695 - - - - - 42aa7fbd by Julian Ospald at 2023-07-30T17:22:01-04:00 Improve documentation around IOException and ioe_filename See: * https://github.com/haskell/core-libraries-committee/issues/189 * https://github.com/haskell/unix/pull/279 * https://github.com/haskell/unix/pull/289 - - - - - 33598ecb by Sylvain Henry at 2023-08-01T14:45:54-04:00 JS: implement getMonotonicTime (fix #23687) - - - - - d2bedffd by BartÅ‚omiej CieÅ›lar at 2023-08-01T14:46:40-04:00 Implementation of the Deprecated Instances proposal #575 This commit implements the ability to deprecate certain instances, which causes the compiler to emit the desired deprecation message whenever they are instantiated. For example: module A where class C t where instance {-# DEPRECATED "dont use" #-} C Int where module B where import A f :: C t => t f = undefined g :: Int g = f -- "dont use" emitted here The implementation is as follows: - In the parser, we parse deprecations/warnings attached to instances: instance {-# DEPRECATED "msg" #-} Show X deriving instance {-# WARNING "msg2" #-} Eq Y (Note that non-standalone deriving instance declarations do not support this mechanism.) - We store the resulting warning message in `ClsInstDecl` (respectively, `DerivDecl`). In `GHC.Tc.TyCl.Instance.tcClsInstDecl` (respectively, `GHC.Tc.Deriv.Utils.newDerivClsInst`), we pass on that information to `ClsInst` (and eventually store it in `IfaceClsInst` too). - Finally, when we solve a constraint using such an instance, in `GHC.Tc.Instance.Class.matchInstEnv`, we emit the appropriate warning that was stored in `ClsInst`. Note that we only emit a warning when the instance is used in a different module than it is defined, which keeps the behaviour in line with the deprecation of top-level identifiers. Signed-off-by: BartÅ‚omiej CieÅ›lar <bcieslar2001 at gmail.com> - - - - - d5a65af6 by Ben Gamari at 2023-08-01T14:47:18-04:00 compiler: Style fixes - - - - - 7218c80a by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Fix implicit cast This ensures that Task.h can be built with a C++ compiler. - - - - - d6d5aafc by Ben Gamari at 2023-08-01T14:47:19-04:00 testsuite: Fix warning in hs_try_putmvar001 - - - - - d9eddf7a by Ben Gamari at 2023-08-01T14:47:19-04:00 testsuite: Add AtomicModifyIORef test - - - - - f9eea4ba by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce NO_WARN macro This allows fine-grained ignoring of warnings. - - - - - 497b24ec by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Simplify atomicModifyMutVar2# implementation Previously we would perform a redundant load in the non-threaded RTS in atomicModifyMutVar2# implementation for the benefit of the non-moving GC's write barrier. Eliminate this. - - - - - 52ee082b by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce more principled fence operations - - - - - cd3c0377 by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce SET_INFO_RELAXED - - - - - 6df2352a by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Style fixes - - - - - 4ef6f319 by Ben Gamari at 2023-08-01T14:47:19-04:00 codeGen/tsan: Rework handling of spilling - - - - - f9ca7e27 by Ben Gamari at 2023-08-01T14:47:19-04:00 hadrian: More debug information - - - - - df4153ac by Ben Gamari at 2023-08-01T14:47:19-04:00 Improve TSAN documentation - - - - - fecae988 by Ben Gamari at 2023-08-01T14:47:19-04:00 hadrian: More selective TSAN instrumentation - - - - - 465a9a0b by Alan Zimmerman at 2023-08-01T14:47:56-04:00 EPA: Provide correct annotation span for ImportDecl Use the whole declaration, rather than just the span of the 'import' keyword. Metric Decrease: T9961 T5205 Metric Increase: T13035 - - - - - ae63d0fa by BartÅ‚omiej CieÅ›lar at 2023-08-01T14:48:40-04:00 Add cases to T23279: HasField for deprecated record fields This commit adds additional tests from ticket #23279 to ensure that we don't regress on reporting deprecated record fields in conjunction with HasField, either when using overloaded record dot syntax or directly through `getField`. Fixes #23279 - - - - - 00fb6e6b by Andreas Klebinger at 2023-08-01T14:49:17-04:00 AArch NCG: Pure refactor Combine some alternatives. Add some line breaks for overly long lines - - - - - 8f3b3b78 by Andreas Klebinger at 2023-08-01T14:49:54-04:00 Aarch ncg: Optimize immediate use for address calculations When the offset doesn't fit into the immediate we now just reuse the general getRegister' code path which is well optimized to compute the offset into a register instead of a special case for CmmRegOff. This means we generate a lot less code under certain conditions which is why performance metrics for these improve. ------------------------- Metric Decrease: T4801 T5321FD T5321Fun ------------------------- - - - - - 74a882dc by MorrowM at 2023-08-02T06:00:03-04:00 Add a RULE to make lookup fuse See https://github.com/haskell/core-libraries-committee/issues/175 Metric Increase: T18282 - - - - - cca74dab by Ben Gamari at 2023-08-02T06:00:39-04:00 hadrian: Ensure that way-flags are passed to CC Previously the way-specific compilation flags (e.g. `-DDEBUG`, `-DTHREADED_RTS`) would not be passed to the CC invocations. This meant that C dependency files would not correctly reflect dependencies predicated on the way, resulting in the rather painful #23554. Closes #23554. - - - - - 622b483c by Jaro Reinders at 2023-08-02T06:01:20-04:00 Native 32-bit Enum Int64/Word64 instances This commits adds more performant Enum Int64 and Enum Word64 instances for 32-bit platforms, replacing the Integer-based implementation. These instances are a copy of the Enum Int and Enum Word instances with minimal changes to manipulate Int64 and Word64 instead. On i386 this yields a 1.5x performance increase and for the JavaScript back end it even yields a 5.6x speedup. Metric Decrease: T18964 - - - - - c8bd7fa4 by Sylvain Henry at 2023-08-02T06:02:03-04:00 JS: fix typos in constants (#23650) - - - - - b9d5bfe9 by Josh Meredith at 2023-08-02T06:02:40-04:00 JavaScript: update MK_TUP macros to use current tuple constructors (#23659) - - - - - 28211215 by Matthew Pickering at 2023-08-02T06:03:19-04:00 ci: Pass -Werror when building hadrian in hadrian-ghc-in-ghci job Warnings when building Hadrian can end up cluttering the output of HLS, and we've had bug reports in the past about these warnings when building Hadrian. It would be nice to turn on -Werror on at least one build of Hadrian in CI to avoid a patch introducing warnings when building Hadrian. Fixes #23638 - - - - - aca20a5d by Ben Gamari at 2023-08-02T06:03:55-04:00 codeGen: Ensure that TSAN is aware of writeArray# write barriers By using a proper release store instead of a fence. - - - - - 453c0531 by Ben Gamari at 2023-08-02T06:03:55-04:00 codeGen: Ensure that array reads have necessary barriers This was the cause of #23541. - - - - - 93a0d089 by Arnaud Spiwack at 2023-08-02T06:04:37-04:00 Add test for #23550 - - - - - 6a2f4a20 by Arnaud Spiwack at 2023-08-02T06:04:37-04:00 Desugar non-recursive lets to non-recursive lets (take 2) This reverts commit 522bd584f71ddeda21efdf0917606ce3d81ec6cc. And takes care of the case that I missed in my previous attempt. Namely the case of an AbsBinds with no type variables and no dictionary variable. Ironically, the comment explaining why non-recursive lets were desugared to recursive lets were pointing specifically at this case as the reason. I just failed to understand that it was until Simon PJ pointed it out to me. See #23550 for more discussion. - - - - - ff81d53f by jade at 2023-08-02T06:05:20-04:00 Expand documentation of List & Data.List This commit aims to improve the documentation and examples of symbols exported from Data.List - - - - - fa4e5913 by Jade at 2023-08-02T06:06:03-04:00 Improve documentation of Semigroup & Monoid This commit aims to improve the documentation of various symbols exported from Data.Semigroup and Data.Monoid - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - e2c91bff by GergÅ‘ Érdi at 2023-08-03T02:55:46+01:00 Desugar bindings in the context of their evidence Closes #23172 - - - - - 481f4a46 by GergÅ‘ Érdi at 2023-08-03T07:48:43+01:00 Add flag to `-f{no-}specialise-incoherents` to enable/disable specialisation of incoherent instances Fixes #23287 - - - - - d751c583 by Profpatsch at 2023-08-04T12:24:26-04:00 base: Improve String & IsString documentation - - - - - 01db1117 by Ben Gamari at 2023-08-04T12:25:02-04:00 rts/win32: Ensure reliability of IO manager shutdown When the Win32 threaded IO manager shuts down, `ioManagerDie` sends an `IO_MANAGER_DIE` event to the IO manager thread using the `io_manager_event` event object. Finally, it will closes the event object, and invalidate `io_manager_event`. Previously, `readIOManagerEvent` would see that `io_manager_event` is invalid and return `0`, suggesting that everything is right with the world. This meant that if `ioManagerDie` invalidated the handle before the event manager was blocked on the event we would end up in a situation where the event manager would never realize it was asked to shut down. Fix this by ensuring that `readIOManagerEvent` instead returns `IO_MANAGER_DIE` when we detect that the event object has been invalidated by `ioManagerDie`. Fixes #23691. - - - - - fdef003a by Ryan Scott at 2023-08-04T12:25:39-04:00 Look through TH splices in splitHsApps This modifies `splitHsApps` (a key function used in typechecking function applications) to look through untyped TH splices and quasiquotes. Not doing so was the cause of #21077. This builds on !7821 by making `splitHsApps` match on `HsUntypedSpliceTop`, which contains the `ThModFinalizers` that must be run as part of invoking the TH splice. See the new `Note [Looking through Template Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`. Along the way, I needed to make the type of `splitHsApps.set` slightly more general to accommodate the fact that the location attached to a quasiquote is a `SrcAnn NoEpAnns` rather than a `SrcSpanAnnA`. Fixes #21077. - - - - - e77a0b41 by Ben Gamari at 2023-08-04T12:26:15-04:00 Bump deepseq submodule to 1.5. And bump bounds (cherry picked from commit 1228d3a4a08d30eaf0138a52d1be25b38339ef0b) - - - - - cebb5819 by Ben Gamari at 2023-08-04T12:26:15-04:00 configure: Bump minimal boot GHC version to 9.4 (cherry picked from commit d3ffdaf9137705894d15ccc3feff569d64163e8e) - - - - - 83766dbf by Ben Gamari at 2023-08-04T12:26:15-04:00 template-haskell: Bump version to 2.21.0.0 Bumps exceptions submodule. (cherry picked from commit bf57fc9aea1196f97f5adb72c8b56434ca4b87cb) - - - - - 1211112a by Ben Gamari at 2023-08-04T12:26:15-04:00 base: Bump version to 4.19 Updates all boot library submodules. (cherry picked from commit 433d99a3c24a55b14ec09099395e9b9641430143) - - - - - 3ab5efd9 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Normalise versions more aggressively In backpack hashes can contain `+` characters. (cherry picked from commit 024861af51aee807d800e01e122897166a65ea93) - - - - - d52be957 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Declare bkpcabal08 as fragile Due to spurious output changes described in #23648. (cherry picked from commit c046a2382420f2be2c4a657c56f8d95f914ea47b) - - - - - e75a58d1 by Ben Gamari at 2023-08-04T12:26:15-04:00 gitlab-ci: Only mark linker_unload_native as broken in static jobs This test passes on dynamically-linked Alpine. (cherry picked from commit f356a7e8ec8ec3d6b2b30fd175598b9b80065d87) - - - - - 8b176514 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Update base-exports - - - - - 4b647936 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite/interface-stability: normalise versions This eliminates spurious changes from version bumps. - - - - - 0eb54c05 by Ben Gamari at 2023-08-04T12:26:51-04:00 linker/PEi386: Don't sign-extend symbol section number Previously we incorrectly interpreted PE section numbers as signed values. However, this isn't the case; rather, it's an unsigned 16-bit number with a few special bit-patterns (0xffff and 0xfffe). This resulted in #22941 as the linker would conclude that the sections were invalid. Fixing this required quite a bit of refactoring. Closes #22941. - - - - - fd7ce39c by Ben Gamari at 2023-08-04T12:27:28-04:00 testsuite: Mark MulMayOflo_full as broken rather than skipping To ensure that we don't accidentally fix it. See #23742. - - - - - 824092f2 by Ben Gamari at 2023-08-04T12:27:28-04:00 nativeGen/AArch64: Fix sign extension in MulMayOflo Previously the 32-bit implementations of MulMayOflo would use the a non-sensical sign-extension mode. Rewrite these to reflect what gcc 11 produces. Also similarly rework the 16- and 8-bit cases. This now passes the MulMayOflo tests in ghc/test-primops> in all four widths, including the precision tests. Fixes #23721. - - - - - 1b15dbc4 by Jan HrÄek at 2023-08-04T12:28:08-04:00 Fix haddock markup in code example for coerce - - - - - 46fd8ced by Vladislav Zavialov at 2023-08-04T12:28:44-04:00 Fix (~) and (@) infix operators in TH splices (#23748) 8168b42a "Whitespace-sensitive bang patterns" allows GHC to accept the following infix operators: a ~ b = () a @ b = () But not if TH is used to generate those declarations: $([d| a ~ b = () a @ b = () |]) -- Test.hs:5:2: error: [GHC-55017] -- Illegal variable name: ‘~’ -- When splicing a TH declaration: (~_0) a_1 b_2 = GHC.Tuple.Prim.() This is easily fixed by modifying `reservedOps` in GHC.Utils.Lexeme - - - - - a1899d8f by Aaron Allen at 2023-08-04T12:29:24-04:00 [#23663] Show Flag Suggestions in GHCi Makes suggestions when using `:set` in GHCi with a misspelled flag. This mirrors how invalid flags are handled when passed to GHC directly. Logic for producing flag suggestions was moved to GHC.Driver.Sesssion so it can be shared. resolves #23663 - - - - - 03f2debd by Rodrigo Mesquita at 2023-08-04T12:30:00-04:00 Improve ghc-toolchain validation configure warning Fixes the layout of the ghc-toolchain validation warning produced by configure. - - - - - de25487d by Alan Zimmerman at 2023-08-04T12:30:36-04:00 EPA make getLocA a synonym for getHasLoc This is basically a no-op change, but allows us to make future changes that can rely on the HasLoc instances And I presume this means we can use more precise functions based on class resolution, so the Windows CI build reports Metric Decrease: T12234 T13035 - - - - - 3ac423b9 by Ben Gamari at 2023-08-04T12:31:13-04:00 ghc-platform: Add upper bound on base Hackage upload requires this. - - - - - 8ba20b21 by Matthew Craven at 2023-08-04T17:22:59-04:00 Adjust and clarify handling of primop effects Fixes #17900; fixes #20195. The existing "can_fail" and "has_side_effects" primop attributes that previously governed this were used in inconsistent and confusingly-documented ways, especially with regard to raising exceptions. This patch replaces them with a single "effect" attribute, which has four possible values: NoEffect, CanFail, ThrowsException, and ReadWriteEffect. These are described in Note [Classifying primop effects]. A substantial amount of related documentation has been re-drafted for clarity and accuracy. In the process of making this attribute format change for literally every primop, several existing mis-classifications were detected and corrected. One of these mis-classifications was tagToEnum#, which is now considered CanFail; this particular fix is known to cause a regression in performance for derived Enum instances. (See #23782.) Fixing this is left as future work. New primop attributes "cheap" and "work_free" were also added, and used in the corresponding parts of GHC.Core.Utils. In view of their actual meaning and uses, `primOpOkForSideEffects` and `exprOkForSideEffects` have been renamed to `primOpOkToDiscard` and `exprOkToDiscard`, respectively. Metric Increase: T21839c - - - - - 41bf2c09 by sheaf at 2023-08-04T17:23:42-04:00 Update inert_solved_dicts for ImplicitParams When adding an implicit parameter dictionary to the inert set, we must make sure that it replaces any previous implicit parameter dictionaries that overlap, in order to get the appropriate shadowing behaviour, as in let ?x = 1 in let ?x = 2 in ?x We were already doing this for inert_cans, but we weren't doing the same thing for inert_solved_dicts, which lead to the bug reported in #23761. The fix is thus to make sure that, when handling an implicit parameter dictionary in updInertDicts, we update **both** inert_cans and inert_solved_dicts to ensure a new implicit parameter dictionary correctly shadows old ones. Fixes #23761 - - - - - 43578d60 by Matthew Craven at 2023-08-05T01:05:36-04:00 Bump bytestring submodule to 0.11.5.1 - - - - - 91353622 by Ben Gamari at 2023-08-05T01:06:13-04:00 Initial commit of Note [Thunks, blackholes, and indirections] This Note attempts to summarize the treatment of thunks, thunk update, and indirections. This fell out of work on #23185. - - - - - 8d686854 by sheaf at 2023-08-05T01:06:54-04:00 Remove zonk in tcVTA This removes the zonk in GHC.Tc.Gen.App.tc_inst_forall_arg and its accompanying Note [Visible type application zonk]. Indeed, this zonk is no longer necessary, as we no longer maintain the invariant that types are well-kinded without zonking; only that typeKind does not crash; see Note [The Purely Kinded Type Invariant (PKTI)]. This commit removes this zonking step (as well as a secondary zonk), and replaces the aforementioned Note with the explanatory Note [Type application substitution], which justifies why the substitution performed in tc_inst_forall_arg remains valid without this zonking step. Fixes #23661 - - - - - 19dea673 by Ben Gamari at 2023-08-05T01:07:30-04:00 Bump nofib submodule Ensuring that nofib can be build using the same range of bootstrap compilers as GHC itself. - - - - - aa07402e by Luite Stegeman at 2023-08-05T23:15:55+09:00 JS: Improve compatibility with recent emsdk The JavaScript code in libraries/base/jsbits/base.js had some hardcoded offsets for fields in structs, because we expected the layout of the data structures to remain unchanged. Emsdk 3.1.42 changed the layout of the stat struct, breaking this assumption, and causing code in .hsc files accessing the stat struct to fail. This patch improves compatibility with recent emsdk by removing the assumption that data layouts stay unchanged: 1. offsets of fields in structs used by JavaScript code are now computed by the configure script, so both the .js and .hsc files will automatically use the new layout if anything changes. 2. the distrib/configure script checks that the emsdk version on a user's system is the same version that a bindist was booted with, to avoid data layout inconsistencies See #23641 - - - - - b938950d by Luite Stegeman at 2023-08-07T06:27:51-04:00 JS: Fix missing local variable declarations This fixes some missing local variable declarations that were found by running the testsuite in strict mode. Fixes #23775 - - - - - 6c0e2247 by sheaf at 2023-08-07T13:31:21-04:00 Update Haddock submodule to fix #23368 This submodule update adds the following three commits: bbf1c8ae - Check for puns 0550694e - Remove fake exports for (~), List, and Tuple<n> 5877bceb - Fix pretty-printing of Solo and MkSolo These commits fix the issues with Haddock HTML rendering reported in ticket #23368. Fixes #23368 - - - - - 5b5be3ea by Matthew Pickering at 2023-08-07T13:32:00-04:00 Revert "Bump bytestring submodule to 0.11.5.1" This reverts commit 43578d60bfc478e7277dcd892463cec305400025. Fixes #23789 - - - - - 01961be3 by Ben Gamari at 2023-08-08T02:47:14-04:00 configure: Derive library version from ghc-prim.cabal.in Since ghc-prim.cabal is now generated by Hadrian, we cannot depend upon it. Closes #23726. - - - - - 3b373838 by Ryan Scott at 2023-08-08T02:47:49-04:00 tcExpr: Push expected types for untyped TH splices inwards In !10911, I deleted a `tcExpr` case for `HsUntypedSplice` in favor of a much simpler case that simply delegates to `tcApp`. Although this passed the test suite at the time, this was actually an error, as the previous `tcExpr` case was critically pushing the expected type inwards. This actually matters for programs like the one in #23796, which GHC would not accept with type inference alone—we need full-blown type _checking_ to accept these. I have added back the previous `tcExpr` case for `HsUntypedSplice` and now explain why we have two different `HsUntypedSplice` cases (one in `tcExpr` and another in `splitHsApps`) in `Note [Looking through Template Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`. Fixes #23796. - - - - - 0ef1d8ae by sheaf at 2023-08-08T21:26:51-04:00 Compute all emitted diagnostic codes This commit introduces in GHC.Types.Error.Codes the function constructorCodes :: forall diag. (...) => Map DiagnosticCode String which computes a collection of all the diagnostic codes that correspond to a particular type. In particular, we can compute the collection of all diagnostic codes emitted by GHC using the invocation constructorCodes @GhcMessage We then make use of this functionality in the new "codes" test which checks consistency and coverage of GHC diagnostic codes. It performs three checks: - check 1: all non-outdated GhcDiagnosticCode equations are statically used. - check 2: all outdated GhcDiagnosticCode equations are statically unused. - check 3: all statically used diagnostic codes are covered by the testsuite (modulo accepted exceptions). - - - - - 4bc7b1e5 by Fraser Tweedale at 2023-08-08T21:27:32-04:00 numberToRangedRational: fix edge cases for exp ≈ (maxBound :: Int) Currently a negative exponent less than `minBound :: Int` results in Infinity, which is very surprising and obviously wrong. ``` λ> read "1e-9223372036854775808" :: Double 0.0 λ> read "1e-9223372036854775809" :: Double Infinity ``` There is a further edge case where the exponent can overflow when increased by the number of tens places in the integer part, or underflow when decreased by the number of leading zeros in the fractional part if the integer part is zero: ``` λ> read "10e9223372036854775807" :: Double 0.0 λ> read "0.01e-9223372036854775808" :: Double Infinity ``` To resolve both of these issues, perform all arithmetic and comparisons involving the exponent in type `Integer`. This approach also eliminates the need to explicitly check the exponent against `maxBound :: Int` and `minBound :: Int`, because the allowed range of the exponent (i.e. the result of `floatRange` for the target floating point type) is certainly within those bounds. This change implements CLC proposal 192: https://github.com/haskell/core-libraries-committee/issues/192 - - - - - 6eab07b2 by Alan Zimmerman at 2023-08-08T21:28:10-04:00 EPA: Remove Location from WarningTxt source This is not needed. - - - - - 1a98d673 by Sebastian Graf at 2023-08-09T16:24:29-04:00 Cleanup a TODO introduced in 1f94e0f7 The change must have slipped through review of !4412 - - - - - 2274abc8 by Sebastian Graf at 2023-08-09T16:24:29-04:00 More explicit strictness in GHC.Real - - - - - ce8aa54c by Sebastian Graf at 2023-08-09T16:24:30-04:00 exprIsTrivial: Factor out shared implementation The duplication between `exprIsTrivial` and `getIdFromTrivialExpr_maybe` has been bugging me for a long time. This patch introduces an inlinable worker function `trivial_expr_fold` acting as the single, shared decision procedure of triviality. It "returns" a Church-encoded `Maybe (Maybe Id)`, so when it is inlined, it fuses to similar code as before. (Better code, even, in the case of `getIdFromTrivialExpr` which presently allocates a `Just` constructor that cancels away after this patch.) - - - - - d004a36d by Sebastian Graf at 2023-08-09T16:24:30-04:00 Simplify: Simplification of arguments in a single function The Simplifier had a function `simplArg` that wasn't called in `rebuildCall`, which seems to be the main way to simplify args. Hence I consolidated the code path to call `simplArg`, too, renaming to `simplLazyArg`. - - - - - 8c73505e by Sebastian Graf at 2023-08-09T16:24:30-04:00 Core.Ppr: Omit case binder for empty case alternatives A minor improvement to pretty-printing - - - - - d8d993f1 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Disable tests RepPolyWrappedVar2 and RepPolyUnsafeCoerce1 in JS backend ... because those coerce between incompatible/unknown PrimReps. - - - - - f06e87e4 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Inlining literals into boring contexts is OK - - - - - 4a6b7c87 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Clarify floating of unsafeEqualityProofs (#23754) - - - - - b0f4752e by Sebastian Graf at 2023-08-09T16:24:30-04:00 Kill SetLevel.notWorthFloating.is_triv (#23270) We have had it since b84ba676034, when it operated on annotated expressions. Nowadays it operates on vanilla `CoreExpr` though, so we should just call `exprIsTrivial`; thus handling empty cases and string literals correctly. - - - - - 7e0c8b3b by Sebastian Graf at 2023-08-09T16:24:30-04:00 ANFise string literal arguments (#23270) This instates the invariant that a trivial CoreExpr translates to an atomic StgExpr. Nice. Annoyingly, in -O0 we sometimes generate ``` foo = case "blah"# of sat { __DEFAULT -> unpackCString# sat } ``` which makes it a bit harder to spot that we can emit a standard `stg_unpack_cstring` thunk. Fixes #23270. - - - - - 357f2738 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Deactivate -fcatch-nonexhaustive-cases in ghc-bignum (#23345) - - - - - 59202c80 by Sebastian Graf at 2023-08-09T16:24:30-04:00 CorePrep: Eliminate EmptyCase and unsafeEqualityProof in CoreToStg instead We eliminate EmptyCase by way of `coreToStg (Case e _ _ []) = coreToStg e` now. The main reason is that it plays far better in conjunction with eta expansion (as we aim to do for arguments in CorePrep, #23083), because we can discard any arguments, `(case e of {}) eta == case e of {}`, whereas in `(e |> co) eta` it's impossible to discard the argument. We do also give the same treatment to unsafeCoerce proofs and treat them as trivial iff their RHS is trivial. It is also both much simpler to describe than the previous mechanism of emitting an unsafe coercion and simpler to implement, removing quite a bit of commentary and `CorePrepProv`. In the ghc/alloc perf test `LargeRecord`, we introduce an additional Simplifier iteration due to #17910. E.g., FloatOut produces a binding ``` lvl_s6uK [Occ=Once1] :: GHC.Types.Int [LclId] lvl_s6uK = GHC.Types.I# 2# lvl_s6uL [Occ=Once1] :: GHC.Types.Any [LclId] lvl_s6uL = case Unsafe.Coerce.unsafeEqualityProof ... of { Unsafe.Coerce.UnsafeRefl v2_i6tr -> lvl_s6uK `cast` (... v2_i6tr ...) } ``` That occurs once and hence is pre-inlined unconditionally in the next Simplifier pass. It's non-trivial to find a way around that, but not really harmful otherwise. Hence we accept a 1.2% increase on some architectures. Metric Increase: LargeRecord - - - - - 00d31188 by Sebastian Graf at 2023-08-09T16:24:30-04:00 CorePrep: Eta expand arguments (#23083) Previously, we'd only eta expand let bindings and lambdas, now we'll also eta expand arguments such as in T23083: ```hs g f h = f (h `seq` (h $)) ``` Unless `-fpedantic-bottoms` is set, we'll now transform to ```hs g f h = f (\eta -> h eta) ``` in CorePrep. See the new `Note [Eta expansion of arguments in CorePrep]` for the details. We only do this optimisation with -O2 because we saw 2-3% ghc/alloc regressions in T4801 and T5321FD. Fixes #23083. - - - - - bf885d7a by Matthew Craven at 2023-08-09T16:25:07-04:00 Bump bytestring submodule to 0.11.5, again Fixes #23789. The bytestring commit used here is unreleased; a release can be made when necessary. - - - - - 7acbf0fd by Sven Tennie at 2023-08-10T19:17:11-04:00 Serialize CmmRetInfo in .rodata The handling of case was missing. - - - - - 0c3136f2 by Sven Tennie at 2023-08-10T19:17:11-04:00 Reference StgRetFun payload by its struct field address This is easier to grasp than relative pointer offsets. - - - - - f68ff313 by Sven Tennie at 2023-08-10T19:17:11-04:00 Better variable name: u -> frame The 'u' was likely introduced by copy'n'paste. - - - - - 0131bb7f by Sven Tennie at 2023-08-10T19:17:11-04:00 Make checkSTACK() public Such that it can also be used in tests. - - - - - 7b6e1e53 by Sven Tennie at 2023-08-10T19:17:11-04:00 Publish stack related fields in DerivedConstants.h These will be used in ghc-heap to decode these parts of the stack. - - - - - 907ed054 by Sven Tennie at 2023-08-10T19:17:11-04:00 ghc-heap: Decode StgStack and its stack frames Previously, ghc-heap could only decode heap closures. The approach is explained in detail in note [Decoding the stack]. - - - - - 6beb6ac2 by Sven Tennie at 2023-08-10T19:17:11-04:00 Remove RetFunType from RetFun stack frame representation It's a technical detail. The single usage is replaced by a predicate. - - - - - 006bb4f3 by Sven Tennie at 2023-08-10T19:17:11-04:00 Better parameter name The call-site uses the term "offset", too. - - - - - d4c2c1af by Sven Tennie at 2023-08-10T19:17:11-04:00 Make closure boxing pure There seems to be no need to do something complicated. However, the strictness of the closure pointer matters, otherwise a thunk gets decoded. - - - - - 8d8426c9 by Sven Tennie at 2023-08-10T19:17:11-04:00 Document entertainGC in test It wasn't obvious why it's there and what its role is. Also, increase the "entertainment level" a bit. I checked in STG and Cmm dumps that this really generates closures (and is not e.g. constant folded away.) - - - - - cc52c358 by Finley McIlwaine at 2023-08-10T19:17:47-04:00 Add -dipe-stats flag This is useful for seeing which info tables have information. - - - - - 261c4acb by Finley McIlwaine at 2023-08-10T19:17:47-04:00 Add -finfo-table-map-with-fallback -finfo-table-map-with-stack The -fno-info-table-map-with-stack flag omits STACK info tables from the info table map, and the -fno-info-table-map-with-fallback flag omits info tables with defaulted source locations from the map. In a test on the Agda codebase the build results were about 7% smaller when both of those types of tables were omitted. Adds a test that verifies that passing each combination of these flags results in the correct output for -dipe-stats, which is disabled for the js backend since profiling is not implemented. This commit also refactors a lot of the logic around extracting info tables from the Cmm results and building the info table map. This commit also fixes some issues in the users guide rst source to fix warnings that were noticed while debugging the documentation for these flags. Fixes #23702 - - - - - d7047e0d by Jaro Reinders at 2023-08-14T04:41:42-04:00 Add changelog entry for specialised Enum Int64/Word64 instances - - - - - 52f5e8fb by cydparser at 2023-08-14T04:42:20-04:00 Fix -ddump-to-file and -ddump-timings interaction (#20316) - - - - - 1274c5d6 by cydparser at 2023-08-14T04:42:20-04:00 Update release notes (#20316) - - - - - 8e699b23 by Matthew Pickering at 2023-08-14T10:44:47-04:00 base: Add changelog entry for CLC #188 This proposal modified the implementations of copyBytes, moveBytes and fillBytes (as detailed in the proposal) https://github.com/haskell/core-libraries-committee/issues/188 - - - - - 026f040a by Matthew Pickering at 2023-08-14T10:45:23-04:00 packaging: Build manpage in separate directory to other documentation We were installing two copies of the manpage: * One useless one in the `share/doc` folder, because we copy the doc/ folder into share/ * The one we deliberately installed into `share/man` etc The solution is to build the manpage into the `manpage` directory when building the bindist, and then just install it separately. Fixes #23707 - - - - - 524c60c8 by BartÅ‚omiej CieÅ›lar at 2023-08-14T13:46:33-04:00 Report deprecated fields bound by record wildcards when used This commit ensures that we emit the appropriate warnings when a deprecated record field bound by a record wildcard is used. For example: module A where data Foo = Foo {x :: Int, y :: Bool, z :: Char} {-# DEPRECATED x "Don't use x" #-} {-# WARNING y "Don't use y" #-} module B where import A foo (Foo {..}) = x This will cause us to emit a "Don't use x" warning, with location the location of the record wildcard. Note that we don't warn about `y`, because it is unused in the RHS of `foo`. Fixes #23382 - - - - - d6130065 by Matthew Pickering at 2023-08-14T13:47:11-04:00 Add zstd suffix to jobs which rely on zstd This was causing some confusion as the job was named simply "x86_64-linux-deb10-validate", which implies a standard configuration rather than any dependency on libzstd. - - - - - e24e44fc by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: Always run project-version job This is needed for the downstream test-primops pipeline to workout what the version of a bindist produced by a pipeline is. - - - - - f17b9d62 by Matthew Pickering at 2023-08-14T13:47:11-04:00 gen_ci: Rework how jobs-metadata.json is generated * We now represent a job group a triple of Maybes, which makes it easier to work out when jobs are enabled/disabled on certain pipelines. ``` data JobGroup a = StandardTriple { v :: Maybe (NamedJob a) , n :: Maybe (NamedJob a) , r :: Maybe (NamedJob a) } ``` * `jobs-metadata.json` generation is reworked using the following algorithm. - For each pipeline type, find all the platforms we are doing builds for. - Select one build per platform - Zip together the results This way we can choose different pipelines for validate/nightly/release which makes the metadata also useful for validate pipelines. This feature is used by the test-primops downstream CI in order to select the right bindist for testing validate pipelines. This makes it easier to inspect which jobs are going to be enabled on a particular pipeline. - - - - - f9a5563d by Matthew Pickering at 2023-08-14T13:47:11-04:00 gen_ci: Rules rework In particular we now distinguish between whether we are dealing with a Nightly/Release pipeline (which labels don't matter for) and a validate pipeline where labels do matter. The overall goal here is to allow a disjunction of labels for validate pipelines, for example, > Run a job if we have the full-ci label or test-primops label Therefore the "ValidateOnly" rules are treated as a set of disjunctions rather than conjunctions like before. What this means in particular is that if we want to ONLY run a job if a label is set, for example, "FreeBSD" label then we have to override the whole label set. Fixes #23772 - - - - - d54b0c1d by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: set -e for lint-ci-config scripts - - - - - 994a9b35 by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: Fix job metadata generation - - - - - e194ed2b by Ben Gamari at 2023-08-15T00:58:09-04:00 users-guide: Note that GHC2021 doesn't include ExplicitNamespaces As noted in #23801. - - - - - d814bda9 by Ben Gamari at 2023-08-15T05:43:53-04:00 users-guide: Support both distutils and packaging As noted in #23818, some old distributions (e.g. Debian 9) only include `distutils` while newer distributions only include `packaging`. Fixes #23818. - - - - - 1726db3f by Ben Gamari at 2023-08-15T05:43:53-04:00 users-guide: Ensure extlinks is compatible with Sphinx <4 The semantics of the `extlinks` attribute annoyingly changed in Sphinx 4. Reflect this in our configuration. See #22690. Fixes #23807. - - - - - 173338cf by Matthew Pickering at 2023-08-15T22:00:24-04:00 ci: Run full-ci on master and release branches Fixes #23737 - - - - - bdab6898 by Andrew Lelechenko at 2023-08-15T22:01:03-04:00 Add @since pragmas for Data.Ord.clamp and GHC.Float.clamp - - - - - 662d351b by Matthew Pickering at 2023-08-16T09:35:04-04:00 ghc-toolchain: Match CPP args with configure script At the moment we need ghc-toolchain to precisely match the output as provided by the normal configure script. The normal configure script (FP_HSCPP_CMD_WITH_ARGS) branches on whether we are using clang or gcc so we match that logic exactly in ghc-toolchain. The old implementation (which checks if certain flags are supported) is better but for now we have to match to catch any potential errors in the configuration. Ticket: #23720 - - - - - 09c6759e by Matthew Pickering at 2023-08-16T09:35:04-04:00 configure: Fix `-Wl,--no-as-needed` check The check was failing because the args supplied by $$1 were quoted which failed because then the C compiler thought they were an input file. Fixes #23720 - - - - - 2129678b by Matthew Pickering at 2023-08-16T09:35:04-04:00 configure: Add flag which turns ghc-toolchain check into error We want to catch these errors in CI, but first we need to a flag which turns this check into an error. - - - - - 6e2aa8e0 by Matthew Pickering at 2023-08-16T09:35:04-04:00 ci: Enable --enable-strict-ghc-toolchain-check for all CI jobs This will cause any CI job to fail if we have a mismatch between what ghc-toolchain reports and what ./configure natively reports. Fixing these kinds of issues is highest priority for 9.10 release. - - - - - 12d39e24 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 Pass user-specified options to ghc-toolchain The current user interface to configuring target toolchains is `./configure`. In !9263 we added a new tool to configure target toolchains called `ghc-toolchain`, but the blessed way of creating these toolchains is still through configure. However, we were not passing the user-specified options given with the `./configure` invocation to the ghc-toolchain tool. This commit remedies that by storing the user options and environment variables in USER_* variables, which then get passed to GHC-toolchain. The exception to the rule is the windows bundled toolchain, which overrides the USER_* variables with whatever flags the windows bundled toolchain requires to work. We consider the bundled toolchain to be effectively the user specifying options, since the actual user delegated that configuration work. Closes #23678 - - - - - f7b3c3a0 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 ghc-toolchain: Parse javascript and ghcjs as a Arch and OS - - - - - 8a0ae4ee by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 ghc-toolchain: Fix ranlib option - - - - - 31e9ec96 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 Check Link Works with -Werror - - - - - bc1998b3 by Matthew Pickering at 2023-08-16T09:35:04-04:00 Only check for no_compact_unwind support on darwin While writing ghc-toolchain we noticed that the FP_PROG_LD_NO_COMPACT_UNWIND check is subtly wrong. Specifically, we pass -Wl,-no_compact_unwind to cc. However, ld.gold interprets this as -n o_compact_unwind, which is a valid argument. Fixes #23676 - - - - - 0283f36e by Matthew Pickering at 2023-08-16T09:35:04-04:00 Add some javascript special cases to ghc-toolchain On javascript there isn't a choice of toolchain but some of the configure checks were not accurately providing the correct answer. 1. The linker was reported as gnu LD because the --version output mentioned gnu LD. 2. The --target flag makes no sense on javascript but it was just ignored by the linker, so we add a special case to stop ghc-toolchain thinking that emcc supports --target when used as a linker. - - - - - a48ec5f8 by Matthew Pickering at 2023-08-16T09:35:04-04:00 check for emcc in gnu_LD check - - - - - 50df2e69 by Matthew Pickering at 2023-08-16T09:35:04-04:00 Add ldOverrideWhitelist to only default to ldOverride on windows/linux On some platforms - ie darwin, javascript etc we really do not want to allow the user to use any linker other than the default one as this leads to all kinds of bugs. Therefore it is a bit more prudant to add a whitelist which specifies on which platforms it might be possible to use a different linker. - - - - - a669a39c by Matthew Pickering at 2023-08-16T09:35:04-04:00 Fix plaform glob in FPTOOLS_SET_C_LD_FLAGS A normal triple may look like x86_64-unknown-linux but when cross-compiling you get $target set to a quad such as.. aarch64-unknown-linux-gnu Which should also match this check. - - - - - c52b6769 by Matthew Pickering at 2023-08-16T09:35:04-04:00 ghc-toolchain: Pass ld-override onto ghc-toolchain - - - - - 039b484f by Matthew Pickering at 2023-08-16T09:35:04-04:00 ld override: Make whitelist override user given option - - - - - d2b63cbc by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: Add format mode to normalise differences before diffing. The "format" mode takes an "--input" and "--ouput" target file and formats it. This is intended to be useful on windows where the configure/ghc-toolchain target files can't be diffed very easily because the path separators are different. - - - - - f2b39e4a by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: Bump ci-images commit to get new ghc-wasm-meta We needed to remove -Wno-unused-command-line-argument from the arguments passed in order for the configure check to report correctly. See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10976#note_516335 - - - - - 92103830 by Matthew Pickering at 2023-08-16T09:35:05-04:00 configure: MergeObjsCmd - distinguish between empty string and unset variable If `MergeObjsCmd` is explicitly set to the empty string then we should assume that MergeObjs is just not supported. This is especially important for windows where we set MergeObjsCmd to "" in m4/fp_setup_windows_toolchain.m4. - - - - - 3500bb2c by Matthew Pickering at 2023-08-16T09:35:05-04:00 configure: Add proper check to see if object merging works - - - - - 08c9a014 by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: If MergeObjsCmd is not set, replace setting with Nothing If the user explicitly chooses to not set a MergeObjsCmd then it is correct to use Nothing for tgtMergeObjs field in the Target file. - - - - - c9071d94 by Matthew Pickering at 2023-08-16T09:35:05-04:00 HsCppArgs: Augment the HsCppOptions This is important when we pass -I when setting up the windows toolchain. - - - - - 294a6d80 by Matthew Pickering at 2023-08-16T09:35:05-04:00 Set USER_CPP_ARGS when setting up windows toolchain - - - - - bde4b5d4 by Rodrigo Mesquita at 2023-08-16T09:35:05-04:00 Improve handling of Cc as a fallback - - - - - f4c1c3a3 by Rodrigo Mesquita at 2023-08-16T09:35:05-04:00 ghc-toolchain: Configure Cpp and HsCpp correctly when user specifies flags In ghc-toolchain, we were only /not/ configuring required flags when the user specified any flags at all for the of the HsCpp and Cpp tools. Otherwise, the linker takes into consideration the user specified flags to determine whether to search for a better linker implementation, but already configured the remaining GHC and platform-specific flags regardless of the user options. Other Tools consider the user options as a baseline for further configuration (see `findProgram`), so #23689 is not applicable. Closes #23689 - - - - - bfe4ffac by Matthew Pickering at 2023-08-16T09:35:05-04:00 CPP_ARGS: Put new options after user specified options This matches up with the behaviour of ghc-toolchain, so that the output of both matches. - - - - - a6828173 by GergÅ‘ Érdi at 2023-08-16T09:35:41-04:00 If a defaulting plugin made progress, re-zonk wanteds before built-in defaulting Fixes #23821. - - - - - e2b38115 by Sylvain Henry at 2023-08-17T07:54:06-04:00 JS: implement openat(AT_FDCWD...) (#23697) Use `openSync` to implement `openat(AT_FDCWD...)`. - - - - - a975c663 by sheaf at 2023-08-17T07:54:47-04:00 Use unsatisfiable for missing methods w/ defaults When a class instance has an Unsatisfiable constraint in its context and the user has not explicitly provided an implementation of a method, we now always provide a RHS of the form `unsatisfiable @msg`, even if the method has a default definition available. This ensures that, when deferring type errors, users get the appropriate error message instead of a possible runtime loop, if class default methods were defined recursively. Fixes #23816 - - - - - 45ca51e5 by Ben Gamari at 2023-08-17T15:16:41-04:00 ghc-internal: Initial commit of the skeleton - - - - - 88bbf8c5 by Ben Gamari at 2023-08-17T15:16:41-04:00 ghc-experimental: Initial commit - - - - - 664468c0 by Ben Gamari at 2023-08-17T15:17:17-04:00 testsuite/cloneStackLib: Fix incorrect format specifiers - - - - - eaa835bb by Ben Gamari at 2023-08-17T15:17:17-04:00 rts/ipe: Fix const-correctness of IpeBufferListNode Both info tables and the string table should be `const` - - - - - 78f6f6fd by Ben Gamari at 2023-08-17T15:17:17-04:00 nonmoving: Drop dead debugging utilities These are largely superceded by support in the ghc-utils GDB extension. - - - - - 3f6e8f42 by Ben Gamari at 2023-08-17T15:17:17-04:00 nonmoving: Refactor management of mark thread Here we refactor that treatment of the worker thread used by the nonmoving GC for concurrent marking, avoiding creating a new thread with every major GC cycle. As well, the new scheme is considerably easier to reason about, consolidating all state in one place, accessed via a small set of accessors with clear semantics. - - - - - 88c32b7d by Ben Gamari at 2023-08-17T15:17:17-04:00 testsuite: Skip T23221 in nonmoving GC ways This test is very dependent upon GC behavior. - - - - - 381cfaed by Ben Gamari at 2023-08-17T15:17:17-04:00 ghc-heap: Don't expose stack dirty and marking fields These are GC metadata and are not relevant to the end-user. Moreover, they are unstable which makes ghc-heap harder to test than necessary. - - - - - 16828ca5 by Luite Stegeman at 2023-08-21T18:42:53-04:00 bump process submodule to include macOS fix and JS support - - - - - b4d5f6ed by Matthew Pickering at 2023-08-21T18:43:29-04:00 ci: Add support for triggering test-primops pipelines This commit adds 4 ways to trigger testing with test-primops. 1. Applying the ~test-primops label to a validate pipeline. 2. A manually triggered job on a validate pipeline 3. A nightly pipeline job 4. A release pipeline job Fixes #23695 - - - - - 32c50daa by Matthew Pickering at 2023-08-21T18:43:29-04:00 Add test-primops label support The test-primops CI job requires some additional builds in the validation pipeline, so we make sure to enable these jobs when test-primops label is set. - - - - - 73ca8340 by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "Aarch ncg: Optimize immediate use for address calculations" This reverts commit 8f3b3b78a8cce3bd463ed175ee933c2aabffc631. See #23793 - - - - - 5546ad9e by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "AArch NCG: Pure refactor" This reverts commit 00fb6e6b06598752414a0b9a92840fb6ca61338d. See #23793 - - - - - 02dfcdc2 by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "Aarch64 NCG: Use encoded immediates for literals." This reverts commit 40425c5021a9d8eb5e1c1046e2d5fa0a2918f96c. See #23793 ------------------------- Metric Increase: T4801 T5321FD T5321Fun ------------------------- - - - - - 7be4a272 by Matthew Pickering at 2023-08-22T08:55:20+01:00 ci: Remove manually triggered test-ci job This doesn't work on slimmed down pipelines as the needed jobs don't exist. If you want to run test-primops then apply the label. - - - - - 76a4d11b by Jaro Reinders at 2023-08-22T08:08:13-04:00 Remove Ptr example from roles docs - - - - - 069729d3 by Bryan Richter at 2023-08-22T08:08:49-04:00 Guard against duplicate pipelines in forks - - - - - f861423b by Rune K. Svendsen at 2023-08-22T08:09:35-04:00 dump-decls: fix "Ambiguous module name"-error Fixes errors of the following kind, which happen when dump-decls is run on a package that contains a module name that clashes with that of another package. ``` dump-decls: <no location info>: error: Ambiguous module name `System.Console.ANSI.Types': it was found in multiple packages: ansi-terminal-0.11.4 ansi-terminal-types-0.11.5 ``` - - - - - edd8bc43 by Krzysztof Gogolewski at 2023-08-22T12:31:20-04:00 Fix MultiWayIf linearity checking (#23814) Co-authored-by: Thomas BAGREL <thomas.bagrel at tweag.io> - - - - - 4ba088d1 by konsumlamm at 2023-08-22T12:32:02-04:00 Update `Control.Concurrent.*` documentation - - - - - 015886ec by ARATA Mizuki at 2023-08-22T15:13:13-04:00 Support 128-bit SIMD on AArch64 via LLVM backend - - - - - 52a6d868 by Krzysztof Gogolewski at 2023-08-22T15:13:51-04:00 Testsuite cleanup - Remove misleading help text in perf_notes, ways are not metrics - Remove no_print_summary - this was used for Phabricator - In linters tests, run 'git ls-files' just once. Previously, it was called on each has_ls_files() - Add ghc-prim.cabal to gitignore, noticed in #23726 - Remove ghc-prim.cabal, it was accidentally committed in 524c60c8cd - - - - - ab40aa52 by Alan Zimmerman at 2023-08-22T15:14:28-04:00 EPA: Use Introduce [DeclTag] in AnnSortKey The AnnSortKey is used to keep track of the order of declarations for printing when the container has split them apart. This applies to HsValBinds and ClassDecl, ClsInstDecl. When making modifications to the list of declarations, the new order must be captured for when it must be printed. For each list of declarations (binds and sigs for a HsValBind) we can just store the list in order. To recreate the list when printing, we must merge them, and this is what the AnnSortKey records. It used to be indexed by SrcSpan, we now simply index by a marker as to which list to take the next item from. - - - - - e7db36c1 by sheaf at 2023-08-23T08:41:28-04:00 Don't attempt pattern synonym error recovery This commit gets rid of the pattern synonym error recovery mechanism (recoverPSB). The rationale is that the fake pattern synonym binding that the recovery mechanism introduced could lead to undesirable knock-on errors, and it isn't really feasible to conjure up a satisfactory binding as pattern synonyms can be used both in expressions and patterns. See Note [Pattern synonym error recovery] in GHC.Tc.TyCl.PatSyn. It isn't such a big deal to eagerly fail compilation on a pattern synonym that doesn't typecheck anyway. Fixes #23467 - - - - - 6ccd9d65 by Ben Gamari at 2023-08-23T08:42:05-04:00 base: Don't use Data.ByteString.Internals.memcpy This function is now deprecated from `bytestring`. Use `Foreign.Marshal.Utils.copyBytes` instead. Fixes #23880. - - - - - 0bfa0031 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Uniformly pass buildOptions to all builders in runBuilder In Builder.hs, runBuilderWith mostly ignores the buildOptions in BuildInfo. This leads to hard to diagnose bugs as any build options you pass with runBuilderWithCmdOptions are ignored for many builders. Solution: Uniformly pass buildOptions to the invocation of cmd. Fixes #23845 - - - - - 9cac8f11 by Matthew Pickering at 2023-08-23T13:43:48-04:00 Abstract windows toolchain setup This commit splits up the windows toolchain setup logic into two functions. * FP_INSTALL_WINDOWS_TOOLCHAIN - deals with downloading the toolchain if it isn't already downloaded * FP_SETUP_WINDOWS_TOOLCHAIN - sets the environment variables to point to the correct place FP_SETUP_WINDOWS_TOOLCHAIN is abstracted from the location of the mingw toolchain and also the eventual location where we will install the toolchain in the installed bindist. This is the first step towards #23608 - - - - - 6c043187 by Matthew Pickering at 2023-08-23T13:43:48-04:00 Generate build.mk for bindists The config.mk.in script was relying on some variables which were supposed to be set by build.mk but therefore never were when used to install a bindist. Specifically * BUILD_PROF_LIBS to determine whether we had profiled libraries or not * DYNAMIC_GHC_PROGRAMS to determine whether we had shared libraries or not Not only were these never set but also not really accurate because you could have shared libaries but still statically linked ghc executable. In addition variables like GhcLibWays were just never used, so those have been deleted from the script. Now instead we generate a build.mk file which just directly specifies which RtsWays we have supplied in the bindist and whether we have DYNAMIC_GHC_PROGRAMS. - - - - - fe23629b by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Add reloc-binary-dist-* targets This adds a command line option to build a "relocatable" bindist. The bindist is created by first creating a normal bindist and then installing it using the `RelocatableBuild=YES` option. This creates a bindist without any wrapper scripts pointing to the libdir. The motivation for this feature is that we want to ship relocatable bindists on windows and this method is more uniform than the ad-hoc method which lead to bugs such as #23608 and #23476 The relocatable bindist can be built with the "reloc-binary-dist" target and supports the same suffixes as the normal "binary-dist" command to specify the compression style. - - - - - 41cbaf44 by Matthew Pickering at 2023-08-23T13:43:48-04:00 packaging: Fix installation scripts on windows/RelocatableBuild case This includes quite a lot of small fixes which fix the installation makefile to work on windows properly. This also required fixing the RelocatableBuild variable which seemed to have been broken for a long while. Sam helped me a lot writing this patch by providing a windows machine to test the changes. Without him it would have taken ages to tweak everything. Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 03474456 by Matthew Pickering at 2023-08-23T13:43:48-04:00 ci: Build relocatable bindist on windows We now build the relocatable bindist target on windows, which means we test and distribute the new method of creating a relocatable bindist. - - - - - d0b48113 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Add error when trying to build binary-dist target on windows The binary dist produced by `binary-dist` target doesn't work on windows because of the wrapper script the makefile installs. In order to not surprise any packagers we just give an error if someone tries to build the old binary-dist target rather than the reloc-binary-dist target. - - - - - 7cbf9361 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Remove query' logic to use tooldir - - - - - 03fad42e by Matthew Pickering at 2023-08-23T13:43:48-04:00 configure: Set WindresCmd directly and removed unused variables For some reason there was an indirection via the Windres variable before setting WindresCmd. That indirection led to #23855. I then also noticed that these other variables were just not used anywhere when trying to work out what the correct condition was for this bit of the configure script. - - - - - c82770f5 by sheaf at 2023-08-23T13:43:48-04:00 Apply shellcheck suggestion to SUBST_TOOLDIR - - - - - 896e35e5 by sheaf at 2023-08-23T13:44:34-04:00 Compute hints from TcSolverReportMsg This commit changes how hints are handled in conjunction with constraint solver report messages. Instead of storing `[GhcHint]` in the TcRnSolverReport error constructor, we compute the hints depending on the underlying TcSolverReportMsg. This disentangles the logic and makes it easier to add new hints for certain errors. - - - - - a05cdaf0 by Alexander Esgen at 2023-08-23T13:45:16-04:00 users-guide: remove note about fatal Haddock parse failures - - - - - 4908d798 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Introduce Data.Enum - - - - - f59707c7 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num.Integer - - - - - b1054053 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num - - - - - 6baa481d by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num.Natural - - - - - 2ac15233 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Float - - - - - f3c489de by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Real - - - - - 94f59eaa by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Eliminate module reexport in GHC.Exception The metric increase here isn't strictly due to this commit but it's a rather small, incidental change. Metric Increase: T8095 T13386 Metric Decrease: T8095 T13386 T18304 - - - - - be1fc7df by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add disclaimers in internal modules To warn users that these modules are internal and their interfaces may change with little warning. As proposed in Core Libraries Committee #146 [CLC146]. [CLC146]: https://github.com/haskell/core-libraries-committee/issues/146 - - - - - 0326f3f4 by sheaf at 2023-08-23T17:37:29-04:00 Bump Cabal submodule We need to bump the Cabal submodule to include commit ec75950 which fixes an issue with a dodgy import Rep(..) which relied on GHC bug #23570 - - - - - 0504cd08 by Facundo DomÃnguez at 2023-08-23T17:38:11-04:00 Fix typos in the documentation of Data.OldList.permutations - - - - - 1420b8cb by Antoine Leblanc at 2023-08-24T16:18:17-04:00 Be more eager in TyCon boot validity checking This commit performs boot-file consistency checking for TyCons into checkValidTyCl. This ensures that we eagerly catch any mismatches, which prevents the compiler from seeing these inconsistencies and panicking as a result. See Note [TyCon boot consistency checking] in GHC.Tc.TyCl. Fixes #16127 - - - - - d99c816f by Finley McIlwaine at 2023-08-24T16:18:55-04:00 Refactor estimation of stack info table provenance This commit greatly refactors the way we compute estimated provenance for stack info tables. Previously, this process was done using an entirely separate traversal of the whole Cmm code stream to build the map from info tables to source locations. The separate traversal is now fused with the Cmm code generation pipeline in GHC.Driver.Main. This results in very significant code generation speed ups when -finfo-table-map is enabled. In testing, this patch reduces code generation times by almost 30% with -finfo-table-map and -O0, and 60% with -finfo-table-map and -O1 or -O2 . Fixes #23103 - - - - - d3e0124c by Finley McIlwaine at 2023-08-24T16:18:55-04:00 Add a test checking overhead of -finfo-table-map We want to make sure we don't end up with poor codegen performance resulting from -finfo-table-map again as in #23103. This test adds a performance test tracking total allocations while compiling ExactPrint with -finfo-table-map. - - - - - fcfc1777 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Add export list to GHC.Llvm.MetaData - - - - - 5880fff6 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Allow LlvmLits in MetaExprs This omission appears to be an oversight. - - - - - 86ce92a2 by Ben Gamari at 2023-08-25T10:58:16-04:00 compiler: Move platform feature predicates to GHC.Driver.DynFlags These are useful in `GHC.Driver.Config.*`. - - - - - a6a38742 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Introduce infrastructure for module flag metadata - - - - - e9af2cf3 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Don't pass stack alignment via command line As of https://reviews.llvm.org/D103048 LLVM no longer supports the `-stack-alignment=...` flag. Instead this information is passed via a module flag metadata node. This requires dropping support for LLVM 11 and 12. Fixes #23870 - - - - - a936f244 by Alan Zimmerman at 2023-08-25T10:58:56-04:00 EPA: Keep track of "in" token for WarningTxt category A warning can now be written with a category, e.g. {-# WARNInG in "x-c" e "d" #-} Keep track of the location of the 'in' keyword and string, as well as the original SourceText of the label, in case it uses character escapes. - - - - - 3df8a653 by Matthew Pickering at 2023-08-25T17:42:18-04:00 Remove redundant import in InfoTableProv The copyBytes function is provided by the import of Foreign. Fixes #23889 - - - - - d6f807ec by Ben Gamari at 2023-08-25T17:42:54-04:00 gitlab/issue-template: Mention report-a-bug - - - - - 50b9f75d by Artin Ghasivand at 2023-08-26T20:02:50+03:30 Added StandaloneKindSignature examples to replace CUSKs ones - - - - - 2f6309a4 by Vladislav Zavialov at 2023-08-27T03:47:37-04:00 Remove outdated CPP in compiler/* and template-haskell/* The boot compiler was bumped to 9.4 in cebb5819b43. There is no point supporting older GHC versions with CPP. - - - - - 5248fdf7 by Zubin Duggal at 2023-08-28T15:01:09+05:30 testsuite: Add regression test for #23861 Simon says this was fixed by commit 8d68685468d0b6e922332a3ee8c7541efbe46137 Author: sheaf <sam.derbyshire at gmail.com> Date: Fri Aug 4 15:28:45 2023 +0200 Remove zonk in tcVTA - - - - - b6903f4d by Zubin Duggal at 2023-08-28T12:33:58-04:00 testsuite: Add regression test for #23864 Simon says this was fixed by commit 59202c800f2c97c16906120ab2561f6e1556e4af Author: Sebastian Graf <sebastian.graf at kit.edu> Date: Fri Mar 31 17:35:22 2023 +0200 CorePrep: Eliminate EmptyCase and unsafeEqualityProof in CoreToStg instead We eliminate EmptyCase by way of `coreToStg (Case e _ _ []) = coreToStg e` now. The main reason is that it plays far better in conjunction with eta expansion (as we aim to do for arguments in CorePrep, #23083), because we can discard any arguments, `(case e of {}) eta == case e of {}`, whereas in `(e |> co) eta` it's impossible to discard the argument. - - - - - 9eecdf33 by sheaf at 2023-08-28T18:54:06+00:00 Remove ScopedTypeVariables => TypeAbstractions This commit implements [amendment 604](https://github.com/ghc-proposals/ghc-proposals/pull/604/) to [GHC proposal 448](https://github.com/ghc-proposals/ghc-proposals/pull/448) by removing the implication of language extensions ScopedTypeVariables => TypeAbstractions To limit breakage, we now allow type arguments in constructor patterns when both ScopedTypeVariables and TypeApplications are enabled, but we emit a warning notifying the user that this is deprecated behaviour that will go away starting in GHC 9.12. Fixes #23776 - - - - - fadd5b4d by sheaf at 2023-08-28T18:54:06+00:00 .stderr: ScopedTypeVariables =/> TypeAbstractions This commit accepts testsuite changes for the changes in the previous commit, which mean that TypeAbstractions is no longer implied by ScopedTypeVariables. - - - - - 4f5fb500 by Greg Steuck at 2023-08-29T07:55:13-04:00 Repair `codes` test on OpenBSD by explicitly requesting extended RE - - - - - 6bbde581 by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Add test for #23540 `T23540.hs` makes use of `explainEv` from `HieQueries.hs`, so `explainEv` has been moved to `TestUtils.hs`. - - - - - 257bb3bd by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Add test for #23120 - - - - - 4f192947 by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Make some evidence uses reachable by toHie Resolves #23540, #23120 This adds spans to certain expressions in the typechecker and renamer, and lets 'toHie' make use of those spans. Therefore the relevant evidence uses for the following syntax will now show up under the expected nodes in 'HieAst's: - Overloaded literals ('IsString', 'Num', 'Fractional') - Natural patterns and N+k patterns ('Eq', 'Ord', and instances from the overloaded literals being matched on) - Arithmetic sequences ('Enum') - Monadic bind statements ('Monad') - Monadic body statements ('Monad', 'Alternative') - ApplicativeDo ('Applicative', 'Functor') - Overloaded lists ('IsList') Also see Note [Source locations for implicit function calls] In the process of handling overloaded lists I added an extra 'SrcSpan' field to 'VAExpansion' - this allows us to more accurately reconstruct the locations from the renamer in 'rebuildHsApps'. This also happens to fix #23120. See the additions to Note [Looking through HsExpanded] - - - - - fe9fcf9d by Sylvain Henry at 2023-08-29T12:07:50-04:00 ghc-heap: rename C file (fix #23898) - - - - - b60d6576 by Krzysztof Gogolewski at 2023-08-29T12:08:29-04:00 Misc cleanup - Builtin.PrimOps: ReturnsAlg was used only for unboxed tuples. Rename to ReturnsTuple. - Builtin.Utils: use SDoc for a panic message. The comment about <<details unavailable>> was obsoleted by e8d356773b56. - TagCheck: fix wrong logic. It was zipping a list 'args' with its version 'args_cmm' after filtering. - Core.Type: remove an outdated 1999 comment about unlifted polymorphic types - hadrian: remove leftover debugging print - - - - - 3054fd6d by Krzysztof Gogolewski at 2023-08-29T12:09:08-04:00 Add a regression test for #23903 The bug has been fixed by commit bad2f8b8aa8424. - - - - - 21584b12 by Ben Gamari at 2023-08-29T19:52:02-04:00 README: Refer to ghc-hq repository for contributor and governance information - - - - - e542d590 by sheaf at 2023-08-29T19:52:40-04:00 Export setInertSet from GHC.Tc.Solver.Monad We used to export getTcSInerts and setTcSInerts from GHC.Tc.Solver.Monad. These got renamed to getInertSet/setInertSet in e1590ddc. That commit also removed the export of setInertSet, but that function is useful for the GHC API. - - - - - 694ec5b1 by sheaf at 2023-08-30T10:18:32-04:00 Don't bundle children for non-parent Avails We used to bundle all children of the parent Avail with things that aren't the parent, e.g. with class C a where type T a meth :: .. we would bundle the whole Avail (C, T, meth) with all of C, T and meth, instead of only with C. Avoiding this fixes #23570 - - - - - d926380d by Krzysztof Gogolewski at 2023-08-30T10:19:08-04:00 Fix typos - - - - - d07080d2 by Josh Meredith at 2023-08-30T19:42:32-04:00 JS: Implement missing C functions `rename`, `realpath`, and `getcwd` (#23806) - - - - - e2940272 by David Binder at 2023-08-30T19:43:08-04:00 Bump submodules of hpc and hpc-bin to version 0.7.0.0 hpc 0.7.0.0 dropped SafeHaskell safety guarantees in order to simplify compatibility with newer versions of the directory package which dropped all SafeHaskell guarantees. - - - - - 5d56d05c by David Binder at 2023-08-30T19:43:08-04:00 Bump hpc bound in ghc.cabal.in - - - - - 99fff496 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 ghc classes documentation: rm redundant comment - - - - - fe021bab by Dominik Schrempf at 2023-08-31T00:04:46-04:00 prelude documentation: various nits - - - - - 48c84547 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 integer documentation: minor corrections - - - - - 20cd12f4 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 real documentation: nits - - - - - dd39bdc0 by sheaf at 2023-08-31T00:05:27-04:00 Add a test for #21765 This issue (of reporting a constraint as being redundant even though removing it causes typechecking to fail) was fixed in aed1974e. This commit simply adds a regression test. Fixes #21765 - - - - - f1ec3628 by Andrew Lelechenko at 2023-08-31T23:53:30-04:00 Export foldl' from Prelude and bump submodules See https://github.com/haskell/core-libraries-committee/issues/167 for discussion Metric Decrease: T8095 T13386 Metric Increase: T13386 T8095 T8095 ghc/alloc decreased on x86_64, but increased on aarch64. T13386 ghc/alloc decreased on x86_64-windows, but increased on other platforms. Neither has anything to do with `foldl'`, so I conclude that both are flaky. - - - - - 3181b97d by GergÅ‘ Érdi at 2023-08-31T23:54:06-04:00 Allow cross-tyvar defaulting proposals from plugins Fixes #23832. - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - e4af506e by Sebastian Graf at 2023-09-01T14:29:12-04:00 Clarify Note [GlobalId/LocalId] after CorePrep (#23797) Fixes #23797. - - - - - ac29787c by Sylvain Henry at 2023-09-01T14:30:02-04:00 Fix warning with UNPACK on sum type (#23921) - - - - - 9765ac7b by Zubin Duggal at 2023-09-05T00:37:45-04:00 hadrian: track python dependencies in doc rules - - - - - 1578215f by sheaf at 2023-09-05T00:38:26-04:00 Bump Haddock to fix #23616 This commit updates the Haddock submodule to include the fix to #23616. Fixes #23616 - - - - - 5a2fe35a by David Binder at 2023-09-05T00:39:07-04:00 Fix example in GHC user guide in SafeHaskell section The example given in the SafeHaskell section uses an implementation of Monad which no longer works. This MR removes the non-canonical return instance and adds the necessary instances of Functor and Applicative. - - - - - 291d81ae by Matthew Pickering at 2023-09-05T14:03:10-04:00 driver: Check transitive closure of haskell package dependencies when deciding whether to relink We were previously just checking whether direct package dependencies had been modified. This caused issues when compiling without optimisations as we wouldn't relink the direct dependency if one of its dependenices changed. Fixes #23724 - - - - - 35da0775 by Krzysztof Gogolewski at 2023-09-05T14:03:47-04:00 Re-export GHC.Utils.Panic.Plain from GHC.Utils.Panic Fixes #23930 - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 3930d793 by Jaro Reinders at 2023-09-06T18:42:55-04:00 Make STG rewriter produce updatable closures - - - - - 0104221a by Krzysztof Gogolewski at 2023-09-06T18:43:32-04:00 configure: update message to use hadrian (#22616) - - - - - b34f8586 by Alan Zimmerman at 2023-09-07T10:58:38-04:00 EPA: Incorrect locations for UserTyVar with '@' In T13343.hs, the location for the @ is not within the span of the surrounding UserTyVar. type Bad @v = (forall (v1 :: RuntimeRep) (a1 :: TYPE v). a1) :: TYPE v Widen it so it is captured. Closes #23887 - - - - - 8046f020 by Finley McIlwaine at 2023-09-07T10:59:15-04:00 Bump haddock submodule to fix #23920 Removes the fake export of `FUN` from Prelude. Fixes #23920. Bumps haddock submodule. - - - - - e0aa8c6e by Krzysztof Gogolewski at 2023-09-07T11:00:03-04:00 Fix wrong role in mkSelCo_maybe In the Lint failure in #23938, we start with a coercion Refl :: T a ~R T a, and call mkSelCo (SelTyCon 1 nominal) Refl. The function incorrectly returned Refl :: a ~R a. The returned role should be nominal, according to the SelCo rule: co : (T s1..sn) ~r0 (T t1..tn) r = tyConRole tc r0 i ---------------------------------- SelCo (SelTyCon i r) : si ~r ti In this test case, r is nominal while r0 is representational. - - - - - 1d92f2df by GergÅ‘ Érdi at 2023-09-08T04:04:30-04:00 If we have multiple defaulting plugins, then we should zonk in between them after any defaulting has taken place, to avoid a defaulting plugin seeing a metavariable that has already been filled. Fixes #23821. - - - - - eaee4d29 by GergÅ‘ Érdi at 2023-09-08T04:04:30-04:00 Improvements to the documentation of defaulting plugins Based on @simonpj's draft and comments in !11117 - - - - - ede3df27 by Alan Zimmerman at 2023-09-08T04:05:06-04:00 EPA: Incorrect span for LWarnDec GhcPs The code (from T23465.hs) {-# WARNInG in "x-c" e "d" #-} e = e gives an incorrect span for the LWarnDecl GhcPs Closes #23892 It also fixes the Test23465/Test23464 mixup - - - - - a0ccef7a by Krzysztof Gogolewski at 2023-09-08T04:05:42-04:00 Valid hole fits: don't suggest unsafeCoerce (#17940) - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 88b942c4 by Oleg Grenrus at 2023-09-08T19:58:42-04:00 Add warning for badly staged types. Resolves #23829. The stage violation results in out-of-bound names in splices. Technically this is an error, but someone might rely on this!? Internal changes: - we now track stages for TyVars. - thLevel (RunSplice _) = 0, instead of panic, as reifyInstances does in fact rename its argument type, and it can contain variables. - - - - - 9861f787 by Ben Gamari at 2023-09-08T19:59:19-04:00 rts: Fix invalid symbol type I suspect this code is dead since we haven't observed this failing despite the obviously incorrect macro name. - - - - - 03ed6a9a by Ben Gamari at 2023-09-08T19:59:19-04:00 testsuite: Add simple test exercising C11 atomics in GHCi See #22012. - - - - - 1aa5733a by Ben Gamari at 2023-09-08T19:59:19-04:00 rts/RtsSymbols: Add AArch64 outline atomic operations Fixes #22012 by adding the symbols described in https://github.com/llvm/llvm-project/blob/main/llvm/docs/Atomics.rst#libcalls-atomic. Ultimately this would be better addressed by #22011, but this is a first step in the right direction and fixes the immediate symptom. Note that we dropped the `__arch64_cas16` operations as these provided by all platforms's compilers. Also, we don't link directly against the libgcc/compiler-rt definitions but rather provide our own wrappers to work around broken toolchains (e.g. https://bugs.gentoo.org/868018). Generated via https://gitlab.haskell.org/ghc/ghc/-/snippets/5733. - - - - - 8f7d3041 by Matthew Pickering at 2023-09-08T19:59:55-04:00 ci: Build debian12 and fedora38 bindists This adds builds for the latest releases for fedora and debian We build these bindists in nightly and release pipelines. - - - - - a1f0d55c by Felix Leitz at 2023-09-08T20:00:37-04:00 Fix documentation around extension implication for MultiParamTypeClasses/ConstrainedClassMethods. - - - - - 98166389 by Teo Camarasu at 2023-09-12T04:30:54-04:00 docs: move -xn flag beside --nonmoving-gc It makes sense to have these beside each other as they are aliases. - - - - - f367835c by Teo Camarasu at 2023-09-12T04:30:55-04:00 nonmoving: introduce a family of dense allocators Supplement the existing power 2 sized nonmoving allocators with a family of dense allocators up to a configurable threshold. This should reduce waste from rounding up block sizes while keeping the amount of allocator sizes manageable. This patch: - Adds a new configuration option `--nonmoving-dense-allocator-count` to control the amount of these new dense allocators. - Adds some constants to `NonmovingAllocator` in order to keep marking fast with the new allocators. Resolves #23340 - - - - - 2b07bf2e by Teo Camarasu at 2023-09-12T04:30:55-04:00 Add changelog entry for #23340 - - - - - f96fe681 by sheaf at 2023-09-12T04:31:44-04:00 Use printGhciException in run{Stmt, Decls} When evaluating statements in GHCi, we need to use printGhciException instead of the printException function that GHC provides in order to get the appropriate error messages that are customised for ghci use. - - - - - d09b932b by psilospore at 2023-09-12T04:31:44-04:00 T23686: Suggest how to enable Language Extension when in ghci Fixes #23686 - - - - - da30f0be by Matthew Craven at 2023-09-12T04:32:24-04:00 Unarise: Split Rubbish literals in function args Fixes #23914. Also adds a check to STG lint that these args are properly unary or nullary after unarisation - - - - - 261b6747 by Matthew Pickering at 2023-09-12T04:33:04-04:00 darwin: Bump MAXOSX_DEPLOYMENT_TARGET to 10.13 This bumps the minumum supported version to 10.13 (High Sierra) which is 6 years old at this point. Fixes #22938 - - - - - f418f919 by Mario Blažević at 2023-09-12T04:33:45-04:00 Fix TH pretty-printing of nested GADTs, issue #23937 This commit fixes `Language.Haskell.TH.Ppr.pprint` so that it correctly pretty-prints GADTs declarations contained within data family instances. Fixes #23937 - - - - - d7a64753 by John Ericson at 2023-09-12T04:34:20-04:00 Put hadrian non-bootstrap plans through `jq` This makes it possible to review changes with conventional diffing tools. This is picking up where ad8cfed4195b1bbfc15b841f010e75e71f63157d left off. - - - - - ff0a709a by Sylvain Henry at 2023-09-12T08:46:28-04:00 JS: fix some tests - Tests using Setup programs need to pass --with-hc-pkg - Several other fixes See https://gitlab.haskell.org/ghc/ghc/-/wikis/javascript-backend/bug_triage for the current status - - - - - fc86f0e7 by Krzysztof Gogolewski at 2023-09-12T08:47:04-04:00 Fix in-scope set assertion failure (#23918) Patch by Simon - - - - - 21a906c2 by Matthew Pickering at 2023-09-12T17:21:04+02:00 Add -Winconsistent-flags warning The warning fires when inconsistent command line flags are passed. For example: * -dynamic-too and -dynamic * -dynamic-too on windows * -O and --interactive * etc This is on by default and allows users to control whether the warning is displayed and whether it should be an error or not. Fixes #22572 - - - - - dfc4f426 by Krzysztof Gogolewski at 2023-09-12T20:31:35-04:00 Avoid serializing BCOs with the internal interpreter Refs #23919 - - - - - 9217950b by Finley McIlwaine at 2023-09-13T08:06:03-04:00 Fix numa auto configure - - - - - 98e7c1cf by Simon Peyton Jones at 2023-09-13T08:06:40-04:00 Add -fno-cse to T15426 and T18964 This -fno-cse change is to avoid these performance tests depending on flukey CSE stuff. Each contains several independent tests, and we don't want them to interact. See #23925. By killing CSE we expect a 400% increase in T15426, and 100% in T18964. Metric Increase: T15426 T18964 - - - - - 236a134e by Simon Peyton Jones at 2023-09-13T08:06:40-04:00 Tiny refactor canEtaReduceToArity was only called internally, and always with two arguments equal to zero. This patch just specialises the function, and renames it to cantEtaReduceFun. No change in behaviour. - - - - - 56b403c9 by Ben Gamari at 2023-09-13T19:21:36-04:00 spec-constr: Lift argument limit for SPEC-marked functions When the user adds a SPEC argument to a function, they are informing us that they expect the function to be specialised. However, previously this instruction could be preempted by the specialised-argument limit (sc_max_args). Fix this. This fixes #14003. - - - - - 6840012e by Simon Peyton Jones at 2023-09-13T19:22:13-04:00 Fix eta reduction Issue #23922 showed that GHC was bogusly eta-reducing a join point. We should never eta-reduce (\x -> j x) to j, if j is a join point. It is extremly difficult to trigger this bug. It took me 45 mins of trying to make a small tests case, here immortalised as T23922a. - - - - - e5c00092 by Andreas Klebinger at 2023-09-14T08:57:43-04:00 Profiling: Properly escape characters when using `-pj`. There are some ways in which unusual characters like quotes or others can make it into cost centre names. So properly escape these. Fixes #23924 - - - - - ec490578 by Ellie Hermaszewska at 2023-09-14T08:58:24-04:00 Use clearer example variable names for bool eliminator - - - - - 5126a2fe by Sylvain Henry at 2023-09-15T11:18:02-04:00 Add missing int64/word64-to-double/float rules (#23907) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/203 - - - - - 566ef411 by Mario Blažević at 2023-09-15T11:18:43-04:00 Fix and test TH pretty-printing of type operator role declarations This commit fixes and tests `Language.Haskell.TH.Ppr.pprint` so that it correctly pretty-prints `type role` declarations for operator names. Fixes #23954 - - - - - 8e05c54a by Simon Peyton Jones at 2023-09-16T01:42:33-04:00 Use correct FunTyFlag in adjustJoinPointType As the Lint error in #23952 showed, the function adjustJoinPointType was failing to adjust the FunTyFlag when adjusting the type. I don't think this caused the seg-fault reported in the ticket, but it is definitely. This patch fixes it. It is tricky to come up a small test case; Krzysztof came up with this one, but it only triggers a failure in GHC 9.6. - - - - - 778c84b6 by Pierre Le Marre at 2023-09-16T01:43:15-04:00 Update to Unicode 15.1.0 See: https://www.unicode.org/versions/Unicode15.1.0/ - - - - - f9d79a6c by Alan Zimmerman at 2023-09-18T00:00:14-04:00 EPA: track unicode version for unrestrictedFunTyCon Closes #23885 Updates haddock submodule - - - - - 9374f116 by Andrew Lelechenko at 2023-09-18T00:00:54-04:00 Bump parsec submodule to allow text-2.1 and bytestring-0.12 - - - - - 7ca0240e by Ben Gamari at 2023-09-18T15:16:48-04:00 base: Advertise linear time of readFloat As noted in #23538, `readFloat` has runtime that scales nonlinearly in the size of its input. Consequently, its use on untrusted input can be exploited as a denial-of-service vector. Point this out and suggest use of `read` instead. See #23538. - - - - - f3f58f13 by Simon Peyton Jones at 2023-09-18T15:17:24-04:00 Remove dead code GHC.CoreToStg.Prep.canFloat This function never fires, so we can delete it: #23965. - - - - - ccab5b15 by Ben Gamari at 2023-09-18T15:18:02-04:00 base/changelog: Move fix for #23907 to 9.8.1 section Since the fix was backported to 9.8.1 - - - - - 51b57d65 by Matthew Pickering at 2023-09-19T08:44:31-04:00 Add aarch64 alpine bindist This is dynamically linked and makes creating statically linked executables more straightforward. Fixes #23482 - - - - - 02c87213 by Matthew Pickering at 2023-09-19T08:44:31-04:00 Add aarch64-deb11 bindist This adds a debian 11 release job for aarch64. Fixes #22005 - - - - - 8b61dfd6 by Alexis King at 2023-09-19T08:45:13-04:00 Don’t store the async exception masking state in CATCH frames - - - - - 86d2971e by doyougnu at 2023-09-19T19:08:19-04:00 compiler,ghci: error codes link to HF error index closes: #23259 - adds -fprint-error-index-links={auto|always|never} flag - - - - - 5f826c18 by sheaf at 2023-09-19T19:09:03-04:00 Pass quantified tyvars in tcDefaultAssocDecl This commit passes the correct set of quantified type variables written by the user in associated type default declarations for validity checking. This ensures that validity checking of associated type defaults mirrors that of standalone type family instances. Fixes #23768 (see testcase T23734 in subsequent commit) - - - - - aba18424 by sheaf at 2023-09-19T19:09:03-04:00 Avoid panic in mkGADTVars This commit avoids panicking in mkGADTVars when we encounter a type variable as in #23784 that is bound by a user-written forall but not actually used. Fixes #23784 - - - - - a525a92a by sheaf at 2023-09-19T19:09:03-04:00 Adjust reporting of unused tyvars in data FamInsts This commit adjusts the validity checking of data family instances to improve the reporting of unused type variables. See Note [Out of scope tvs in data family instances] in GHC.Tc.Validity. The problem was that, in a situation such as data family D :: Type data instance forall (d :: Type). D = MkD the RHS passed to 'checkFamPatBinders' would be the TyCon app R:D d which mentions the type variable 'd' quantified in the user-written forall. Thus, when computing the set of unused type variables in the RHS of the data family instance, we would find that 'd' is used, and report a strange error message that would say that 'd' is not bound on the LHS. To fix this, we special-case the data-family instance case, manually extracting all the type variables that appear in the arguments of all the data constructores of the data family instance. Fixes #23778 - - - - - 28dd52ee by sheaf at 2023-09-19T19:09:03-04:00 Unused tyvars in FamInst: only report user tyvars This commit changes how we perform some validity checking for coercion axioms to mirror how we handle default declarations for associated type families. This allows us to keep track of whether type variables in type and data family instances were user-written or not, in order to only report the user-written ones in "unused type variable" error messages. Consider for example: {-# LANGUAGE PolyKinds #-} type family F type instance forall a. F = () In this case, we get two quantified type variables, (k :: Type) and (a :: k); the second being user-written, but the first is introduced by the typechecker. We should only report 'a' as being unused, as the user has no idea what 'k' is. Fixes #23734 - - - - - 1eed645c by sheaf at 2023-09-19T19:09:03-04:00 Validity: refactor treatment of data families This commit refactors the reporting of unused type variables in type and data family instances to be more principled. This avoids ad-hoc logic in the treatment of data family instances. - - - - - 35bc506b by John Ericson at 2023-09-19T19:09:40-04:00 Remove `ghc-cabal` It is dead code since the Make build system was removed. I tried to go over every match of `git grep -i ghc-cabal` to find other stray bits. Some of those might be workarounds that can be further removed. - - - - - 665ca116 by John Paul Adrian Glaubitz at 2023-09-19T19:10:39-04:00 Re-add unregisterised build support for sparc and sparc64 Closes #23959 - - - - - 142f8740 by Matthew Pickering at 2023-09-19T19:11:16-04:00 Bump ci-images to use updated version of Alex Fixes #23977 - - - - - fa977034 by John Ericson at 2023-09-21T12:55:25-04:00 Use Cabal 3.10 for Hadrian We need the newer version for `CABAL_FLAG_*` env vars for #17191. - - - - - a5d22cab by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: `need` any `configure` script we will call When the script is changed, we should reconfigure. - - - - - db882b57 by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: Make it easier to debug Cabal configure Right now, output is squashed. This make per-package configure scripts extremely hard to maintain, because we get vague "library is missing" errors when the actually probably is usually completely unrelated except for also involving the C/C++ toolchain. (I can always pass `-VVV` to Hadrian locally, but these errors are subtle and I often cannot reproduce them locally!) `--disable-option-checking` was added back in 75c6e0684dda585c37b4ac254cd7a13537a59a91 but seems to be a bit overkill; if other flags are passed that are not recognized behind the two from Cabal mentioned in the former comment, we *do* want to know about it. - - - - - 7ed65f5a by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: Increase verbosity of certain cabal commands This is a hack to get around the cabal function we're calling *decreasing* the verbosity it passes to another function, which is the stuff we often actually care about. Sigh. Keeping this a separate commit so if this makes things too verbose it is easy to revert. - - - - - a4fde569 by John Ericson at 2023-09-21T12:55:25-04:00 rts: Move most external symbols logic to the configure script This is much more terse because we are programmatically handling the leading underscore. `findPtr` however is still handled in the Cabal file because we need a newer Cabal to pass flags to the configure script automatically. Co-Authored-By: Ben Gamari <ben at well-typed.com> - - - - - 56cc85fb by Andrew Lelechenko at 2023-09-21T12:56:21-04:00 Bump Cabal submodule to allow text-2.1 and bytestring-0.12 - - - - - 0cd6148c by Matthew Pickering at 2023-09-21T12:56:21-04:00 hadrian: Generate Distribution/Fields/Lexer.x before creating a source-dist - - - - - b10ba6a3 by Andrew Lelechenko at 2023-09-21T12:56:21-04:00 Bump hadrian's index-state to upgrade alex at least to 3.2.7.3 - - - - - 11ecc37b by Luite Stegeman at 2023-09-21T12:57:03-04:00 JS: correct file size and times Programs produced by the JavaScript backend were returning incorrect file sizes and modification times, causing cabal related tests to fail. This fixes the problem and adds an additional test that verifies basic file information operations. fixes #23980 - - - - - b35fd2cd by Ben Gamari at 2023-09-21T12:57:39-04:00 gitlab-ci: Drop libiserv from upload_ghc_libs libiserv has been merged into the ghci package. - - - - - 37ad04e8 by Ben Gamari at 2023-09-21T12:58:15-04:00 testsuite: Fix Windows line endings - - - - - 5795b365 by Ben Gamari at 2023-09-21T12:58:15-04:00 testsuite: Use makefile_test - - - - - 15118740 by Ben Gamari at 2023-09-21T12:58:55-04:00 system-cxx-std-lib: Add license and description - - - - - 0208f1d5 by Ben Gamari at 2023-09-21T12:59:33-04:00 gitlab/issue-templates: Rename bug.md -> default.md So that it is visible by default. - - - - - 23cc3f21 by Andrew Lelechenko at 2023-09-21T20:18:11+01:00 Bump submodule text to 2.1 - - - - - b8e4fe23 by Andrew Lelechenko at 2023-09-22T20:05:05-04:00 Bump submodule unix to 2.8.2.1 - - - - - 54b2016e by John Ericson at 2023-09-23T11:40:41-04:00 Move lib{numa,dw} defines to RTS configure Clean up the m4 to handle the auto case always and be more consistent. Also simplify the CPP --- we should always have both headers if we are using libnuma. "side effects" (AC_DEFINE, and AC_SUBST) are removed from the macros to better separate searching from actions taken based on search results. This might seem overkill now, but will make shuffling logic between configure scripts easier later. The macro comments are converted from `dnl` to `#` following the recomendation in https://www.gnu.org/software/autoconf/manual/autoconf-2.71/html_node/Macro-Definitions.html - - - - - d51b601b by John Ericson at 2023-09-23T11:40:50-04:00 Shuffle libzstd configuring between scripts Like the prior commit for libdw and libnuma, `AC_DEFINE` to RTS configure, `AC_SUBST` goes to the top-level configure script, and the documentation of the m4 macro is improved. - - - - - d1425af0 by John Ericson at 2023-09-23T11:41:03-04:00 Move `FP_ARM_OUTLINE_ATOMICS` to RTS configure It is just `AC_DEFINE` it belongs there instead. - - - - - 18de37e4 by John Ericson at 2023-09-23T11:41:03-04:00 Move mmap in the runtime linker check to the RTS configure `AC_DEFINE` should go there instead. - - - - - 74132c2b by Andrew Lelechenko at 2023-09-25T21:56:54-04:00 Elaborate comment on GHC_NO_UNICODE - - - - - de142aa2 by Ben Gamari at 2023-09-26T15:25:03-04:00 gitlab-ci: Mark T22012 as broken on CentOS 7 Due to #23979. - - - - - 6a896ce8 by Teo Camarasu at 2023-09-26T15:25:39-04:00 hadrian: better error for failing to find file's dependencies Resolves #24004 - - - - - d697a6c2 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Refactor uses of `partitionEithers . map` This patch changes occurences of the idiom `partitionEithers (map f xs)` by the simpler form `partitionWith f xs` where `partitionWith` is the utility function defined in `GHC.Utils.Misc`. Resolves: #23953 - - - - - 8a2968b7 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Refactor uses of `partitionEithers <$> mapM f xs` This patch changes occurences of the idiom `partitionEithers <$> mapM f xs` by the simpler form `partitionWithM f xs` where `partitionWithM` is a utility function newly added to `GHC.Utils.Misc`. - - - - - 6a27eb97 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Mark `GHC.Utils.Misc.partitionWithM` as inlineable This patch adds an `INLINEABLE` pragma for `partitionWithM` to ensure that the right-hand side of the definition of this function remains available for specialisation at call sites. - - - - - f1e5245a by David Binder at 2023-09-27T01:19:00-04:00 Add RTS option to supress tix file - - - - - 1f43124f by David Binder at 2023-09-27T01:19:00-04:00 Add expected output to testsuite in test interface-stability/base-exports - - - - - b9d2c354 by David Binder at 2023-09-27T01:19:00-04:00 Expose HpcFlags and getHpcFlags from GHC.RTS.Flags - - - - - 345675c6 by David Binder at 2023-09-27T01:19:00-04:00 Fix expected output of interface-stability test - - - - - 146e1c39 by David Binder at 2023-09-27T01:19:00-04:00 Implement getHpcFlags - - - - - 61ba8e20 by David Binder at 2023-09-27T01:19:00-04:00 Add section in user guide - - - - - ea05f890 by David Binder at 2023-09-27T01:19:01-04:00 Rename --emit-tix-file to --write-tix-file - - - - - cabce2ce by David Binder at 2023-09-27T01:19:01-04:00 Update the golden files for interface stability - - - - - 1dbdb9d0 by Krzysztof Gogolewski at 2023-09-27T01:19:37-04:00 Refactor: introduce stgArgRep The function 'stgArgType' returns the type in STG. But this violates the abstraction: in STG we're supposed to operate on PrimReps. This introduces stgArgRep ty = typePrimRep (stgArgType ty) stgArgRep1 ty = typePrimRep1 (stgArgType ty) stgArgRep_maybe ty = typePrimRep_maybe (stgArgType ty) stgArgType is still directly used for unboxed tuples (should be fixable), FFI and in ticky. - - - - - b02f8042 by Mario Blažević at 2023-09-27T17:33:28-04:00 Fix TH pretty-printer's parenthesization This PR Fixes `Language.Haskell.TH.Ppr.pprint` so it correctly emits parentheses where needed. Fixes #23962, #23968, #23971, and #23986 - - - - - 79104334 by Krzysztof Gogolewski at 2023-09-27T17:34:04-04:00 Add a testcase for #17564 The code in the ticket relied on the behaviour of Derived constraints. Derived constraints were removed in GHC 9.4 and now the code works as expected. - - - - - d7a80143 by sheaf at 2023-09-28T03:25:53-04:00 lint-codes: add new modes of operation This commit adds two new modes of operation to the lint-codes utility: list - list all statically used diagnostic codes outdated - list all outdated diagnostic codes The previous behaviour is now: test - test consistency and coverage of diagnostic codes - - - - - 477d223c by sheaf at 2023-09-28T03:25:53-04:00 lint codes: avoid using git-grep We manually traverse through the filesystem to find the diagnostic codes embedded in .stdout and .stderr files, to avoid any issues with old versions of grep. Fixes #23843 - - - - - a38ae69a by sheaf at 2023-09-28T03:25:53-04:00 lint-codes: add Hadrian targets This commit adds new Hadrian targets: codes, codes:used - list all used diagnostic codes codes:outdated - list outdated diagnostic codes This allows users to easily query GHC for used and outdated diagnostic codes, e.g. hadrian/build -j --flavour=<..> codes will list all used diagnostic codes in the command line by running the lint-codes utility in the "list codes" mode of operation. The diagnostic code consistency and coverage test is still run as usual, through the testsuite: hadrian/build test --only="codes" - - - - - 9cdd629b by Ben Gamari at 2023-09-28T03:26:29-04:00 hadrian: Install LICENSE files in bindists Fixes #23548. - - - - - b8ebf876 by Matthew Craven at 2023-09-28T03:27:05-04:00 Fix visibility when eta-reducing a type lambda Fixes #24014. - - - - - d3874407 by Torsten Schmits at 2023-09-30T16:08:10-04:00 Fix several mistakes around free variables in iface breakpoints Fixes #23612 , #23607, #23998 and #23666. MR: !11026 The fingerprinting logic in `Iface.Recomp` failed lookups when processing decls containing breakpoints for two reasons: * IfaceBreakpoint created binders for free variables instead of expressions * When collecting free names for the dependency analysis for fingerprinting, breakpoint FVs were skipped - - - - - ef5342cd by Simon Peyton Jones at 2023-09-30T16:08:48-04:00 Refactor to combine HsLam and HsLamCase This MR is pure refactoring (#23916): * Combine `HsLam` and `HsLamCase` * Combine `HsCmdLam` and `HsCmdLamCase` This just arranges to treat uniformly \x -> e \case pi -> ei \cases pis -> ie In the exising code base the first is treated differently to the latter two. No change in behaviour. More specifics: * Combine `HsLam` and `HsLamCase` (constructors of `Language.Haskell.Syntax.Expr.HsExpr`) into one data construtor covering * Lambda * `\case` * `\cases` * The new `HsLam` has an argument of type `HsLamVariant` to distinguish the three cases. * Similarly, combine `HsCmdLam` and `HsCmdLamCase` (constructors of `Language.Haskell.Syntax.Expr.HsCmd` ) into one. * Similarly, combine `mkHsLamPV` and `mkHsLamCasePV` (methods of class `DisambECP`) into one. (Thank you Alan Zimmerman.) * Similarly, combine `LambdaExpr` and `LamCaseAlt` (constructors of `Language.Haskell.Syntax.Expr.HsMatchContext`) into one: `LamAlt` with a `HsLamVariant` argument. * Similarly, combine `KappaExpr` and `ArrowLamCaseAlt` (constructors of `Language.Haskell.Syntax.Expr.HsArrowMatchContext`) into one: `ArrowLamAlt` with a `HsLamVariant` argument. * Similarly, combine `PsErrLambdaInPat` and `PsErrLambdaCaseInPat` (constructors of `GHC.Parser.Errors.Ppr.PsError`) into one. * Similarly, combine `PsErrLambdaInPat` and `PsErrLambdaCaseInPat` (constructors of `GHC.Parser.Errors.Ppr.PsError`) into one. * In the same `PsError` data type, combine `PsErrLambdaCmdInFunAppCmd` and `PsErrLambdaCaseCmdInFunAppCmd` into one. * In the same `PsError` data tpye, combine `PsErrLambdaInFunAppExpr` and `PsErrLambdaCaseInFunAppExpr` into one. p* Smilarly combine `ExpectedFunTyLam` and `ExpectedFunTyLamCase` (constructors of `GHC.Tc.Types.Origin.ExpectedFunTyOrigin`) into one. Phew! - - - - - b048bea0 by Andreas Klebinger at 2023-09-30T16:09:24-04:00 Arm: Make ppr methods easier to use by not requiring NCGConfig - - - - - 2adc0508 by Andreas Klebinger at 2023-09-30T16:09:24-04:00 AArch64: Fix broken conditional jumps for offsets >= 1MB Rewrite conditional jump instructions with offsets >= 1MB to use unconditional jumps to avoid overflowing the immediate. Fixes #23746 - - - - - 1424f790 by Alan Zimmerman at 2023-09-30T16:10:00-04:00 EPA: Replace Monoid with NoAnn We currently use the Monoid class as a constraint on Exact Print Annotation functions, so we can use mempty. But this leads to requiring Semigroup instances too, which do not always make sense. Instead, introduce a class NoAnn, with a function noAnn analogous to mempty. Closes #20372 Updates haddock submodule - - - - - c1a3ecde by Ben Gamari at 2023-09-30T16:10:36-04:00 users-guide: Refactor handling of :base-ref: et al. - - - - - bc204783 by Richard Eisenberg at 2023-10-02T14:50:52+02:00 Simplify and correct nasty case in coercion opt This fixes #21062. No test case, because triggering this code seems challenging. - - - - - 9c9ca67e by Andrew Lelechenko at 2023-10-04T05:42:28-04:00 Bump bytestring submodule to 0.12.0.2 - - - - - 4e46dc2b by Andrew Lelechenko at 2023-10-04T05:42:28-04:00 Inline bucket_match - - - - - f6b2751f by Ben Gamari at 2023-10-04T05:43:05-04:00 configure: Fix #21712 again This is a bit of a shot in the dark to fix #24033, which appears to be another instance of #21712. For some reason the ld-override logic *still* appears to be active on Darwin targets (or at least one). Consequently, on misconfigured systems we may choose a non-`ld64` linker. It's a bit unclear exactly what happened in #24033 but ultimately the check added for #21712 was not quite right, checking for the `ghc_host_os` (the value of which depends upon the bootstrap compiler) instead of the target platform. Fix this. Fixes #24033. - - - - - 2f0a101d by Krzysztof Gogolewski at 2023-10-04T05:43:42-04:00 Add a regression test for #24029 - - - - - 8cee3fd7 by sheaf at 2023-10-04T05:44:22-04:00 Fix non-symbolic children lookup of fixity decl The fix for #23664 did not correctly account for non-symbolic names when looking up children of a given parent. This one-line fix changes that. Fixes #24037 - - - - - a4785b33 by Cheng Shao at 2023-10-04T05:44:59-04:00 rts: fix incorrect ticket reference - - - - - e037f459 by Ben Gamari at 2023-10-04T05:45:35-04:00 users-guide: Fix discussion of -Wpartial-fields * fix a few typos * add a new example showing when the warning fires * clarify the existing example * point out -Wincomplete-record-selects Fixes #24049. - - - - - 8ff3134e by Matthew Pickering at 2023-10-05T05:34:58-04:00 Revert "Pass preprocessor options to C compiler when building foreign C files (#16737)" This reverts commit 1c18d3b41f897f34a93669edaebe6069f319f9e2. `-optP` should pass options to the preprocessor, that might be a very different program to the C compiler, so passing the options to the C compiler is likely to result in `-optP` being useless. Fixes #17185 and #21291 - - - - - 8f6010b9 by Ben Gamari at 2023-10-05T05:35:36-04:00 rts/nonmoving: Fix on LLP64 platforms Previously `NONMOVING_SEGMENT_MASK` and friends were defined with the `UL` size suffix. However, this is wrong on LLP64 platforms like Windows, where `long` is 32-bits. Fixes #23003. Fixes #24042. - - - - - f20d02f8 by Andreas Klebinger at 2023-10-05T05:36:14-04:00 Fix isAArch64Bitmask for 32bit immediates. Fixes #23802 - - - - - 63afb701 by Bryan Richter at 2023-10-05T05:36:49-04:00 Work around perf note fetch failure Addresses #24055. - - - - - 242102f4 by Krzysztof Gogolewski at 2023-10-05T05:37:26-04:00 Add a test for #21348 - - - - - 7d390bce by Rewbert at 2023-10-05T05:38:08-04:00 Fixes #24046 - - - - - 69abb171 by Finley McIlwaine at 2023-10-06T14:06:28-07:00 Ensure unconstrained instance dictionaries get IPE info In the `StgRhsCon` case of `GHC.Stg.Debug.collectStgRhs`, we were not coming up with an initial source span based on the span of the binder, which was causing instance dictionaries without dynamic superclass constraints to not have source locations in their IPE info. Now they do. Resolves #24005 - - - - - 390443b7 by Andreas Klebinger at 2023-10-07T10:00:20-04:00 rts: Split up rts/include/stg/MachRegs.h by arch - - - - - 3685942f by Bryan Richter at 2023-10-07T10:00:56-04:00 Actually set hackage index state Or at least, use a version of the cabal command that *claims* to set the index state. Time will tell. - - - - - 46a0e5be by Bryan Richter at 2023-10-07T10:00:56-04:00 Update hackage index state - - - - - d4b037de by Bryan Richter at 2023-10-07T10:00:56-04:00 Ensure hadrian uses CI's hackage index state - - - - - e206be64 by Andrew Lelechenko at 2023-10-08T15:06:14-04:00 Do not use O_NONBLOCK on regular files or block devices CLC proposal https://github.com/haskell/core-libraries-committee/issues/166 - - - - - a06197c4 by David Binder at 2023-10-08T15:06:55-04:00 Update hpc-bin submodule to 0.69 - - - - - ed6785b6 by David Binder at 2023-10-08T15:06:55-04:00 Update Hadrian with correct path to happy file for hpc-bin - - - - - 94066d58 by Alan Zimmerman at 2023-10-09T21:35:53-04:00 EPA: Introduce HasAnnotation class The class is defined as class HasAnnotation e where noAnnSrcSpan :: SrcSpan -> e This generalises noAnnSrcSpan, and allows noLocA :: (HasAnnotation e) => a -> GenLocated e a noLocA = L (noAnnSrcSpan noSrcSpan) - - - - - 8792a1bc by Ben Gamari at 2023-10-09T21:36:29-04:00 Bump unix submodule to v2.8.3.0 - - - - - e96c51cb by Andreas Klebinger at 2023-10-10T16:44:27+01:00 Add a flag -fkeep-auto-rules to optionally keep auto-generated rules around. The motivation for the flag is given in #21917. - - - - - 3ed58cef by Matthew Pickering at 2023-10-10T19:01:22-04:00 hadrian: Add ghcToolchain to tool args list This allows you to load ghc-toolchain and ghc-toolchain-bin into HLS. - - - - - 476c02d4 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Normalise triple via config.sub We were not normalising the target triple anymore like we did with the old make build system. Fixes #23856 - - - - - 303dd237 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add missing vendor normalisation This is copied from m4/ghc_convert_vendor.m4 Towards #23868 - - - - - 838026c9 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add loongarch64 to parseArch Towards #23868 - - - - - 1a5bc0b5 by Matthew Pickering at 2023-10-10T19:01:22-04:00 Add same LD hack to ghc-toolchain In the ./configure script, if you pass the `LD` variable then this has the effect of stopping use searching for a linker and hence passing `-fuse-ld=...`. We want to emulate this logic in ghc-toolchain, if a use explicilty specifies `LD` variable then don't add `-fuse-ld=..` with the goal of making ./configure and ghc-toolchain agree on which flags to use when using the C compiler as a linker. This is quite unsavoury as we don't bake the choice of LD into the configuration anywhere but what's important for now is making ghc-toolchain and ./configure agree as much as possible. See #23857 for more discussion - - - - - 42d50b5a by Ben Gamari at 2023-10-10T19:01:22-04:00 ghc-toolchain: Check for C99 support with -std=c99 Previously we failed to try enabling C99 support with `-std=c99`, as `autoconf` attempts. This broke on older compilers (e.g. CentOS 7) which don't enable C99 by default. Fixes #23879. - - - - - da2961af by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add endianess check using __BYTE_ORDER__ macro In very old toolchains the BYTE_ORDER macro is not set but thankfully the __BYTE_ORDER__ macro can be used instead. - - - - - d8da73cd by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: AC_PATH_TARGET_TOOL for LD We want to make sure that LD is set to an absolute path in order to be consistent with the `LD=$(command -v ld)` call. The AC_PATH_TARGET_TOOL macro uses the absolute path rather than AC_CHECK_TARGET_TOOL which might use a relative path. - - - - - 171f93cc by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Check whether we need -std=gnu99 for CPP as well In ./configure the C99 flag is passed to the C compiler when used as a C preprocessor. So we also check the same thing in ghc-toolchain. - - - - - 89a0918d by Matthew Pickering at 2023-10-10T19:01:22-04:00 Check for --target linker flag separately to C compiler There are situations where the C compiler doesn't accept `--target` but when used as a linker it does (but doesn't do anything most likely) In particular with old gcc toolchains, the C compiler doesn't support --target but when used as a linker it does. - - - - - 37218329 by Matthew Pickering at 2023-10-10T19:01:22-04:00 Use Cc to compile test file in nopie check We were attempting to use the C compiler, as a linker, to compile a file in the nopie check, but that won't work in general as the flags we pass to the linker might not be compatible with the ones we pass when using the C compiler. - - - - - 9b2dfd21 by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: Error when ghc-toolchain fails to compile This is a small QOL change as if you are working on ghc-toolchain and it fails to compile then configure will continue and can give you outdated results. - - - - - 1f0de49a by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: Check whether -no-pie works when the C compiler is used as a linker `-no-pie` is a flag we pass when using the C compiler as a linker (see pieCCLDOpts in GHC.Driver.Session) so we should test whether the C compiler used as a linker supports the flag, rather than just the C compiler. - - - - - 62cd2579 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Remove javascript special case for --target detection emcc when used as a linker seems to ignore the --target flag, and for consistency with configure which now tests for --target, we remove this special case. - - - - - 0720fde7 by Ben Gamari at 2023-10-10T19:01:22-04:00 toolchain: Don't pass --target to emscripten toolchain As noted in `Note [Don't pass --target to emscripten toolchain]`, emscripten's `emcc` is rather inconsistent with respect to its treatment of the `--target` flag. Avoid this by special-casing this toolchain in the `configure` script and `ghc-toolchain`. Fixes on aspect of #23744. - - - - - 6354e1da by Matthew Pickering at 2023-10-10T19:01:22-04:00 hadrian: Don't pass `--gcc-options` as a --configure-arg to cabal configure Stop passing -gcc-options which mixed together linker flags and non-linker flags. There's no guarantee the C compiler will accept both of these in each mode. - - - - - c00a4bd6 by Ben Gamari at 2023-10-10T19:01:22-04:00 configure: Probe stage0 link flags For consistency with later stages and CC. - - - - - 1f11e7c4 by Sebastian Graf at 2023-10-10T19:01:58-04:00 Stricter Binary.get in GHC.Types.Unit (#23964) I noticed some thunking while looking at Core. This change has very modest, but throughout positive ghc/alloc effect: ``` hard_hole_fits(normal) ghc/alloc 283,057,664 281,620,872 -0.5% geo. mean -0.1% minimum -0.5% maximum +0.0% ``` Fixes #23964. - - - - - a4f1a181 by Bryan Richter at 2023-10-10T19:02:37-04:00 rel_eng/upload.sh cleanups - - - - - 80705335 by doyougnu at 2023-10-10T19:03:18-04:00 ci: add javascript label rule This adds a rule which triggers the javascript job when the "javascript" label is assigned to an MR. - - - - - a2c0fff6 by Matthew Craven at 2023-10-10T19:03:54-04:00 Make 'wWarningFlagsDeps' include every WarningFlag Fixes #24071. - - - - - d055f099 by Jan HrÄek at 2023-10-10T19:04:33-04:00 Fix pretty printing of overlap pragmas in TH splices (fixes #24074) - - - - - 0746b868 by Andreas Klebinger at 2023-10-10T19:05:09-04:00 Aarch64 NCG: Use encoded immediates for literals. Try to generate instr x2, <imm> instead of mov x1, lit instr x2, x1 When possible. This get's rid if quite a few redundant mov instructions. I believe this causes a metric decrease for LargeRecords as we reduce register pressure. ------------------------- Metric Decrease: LargeRecord ------------------------- - - - - - 739f4e6f by Andreas Klebinger at 2023-10-10T19:05:09-04:00 AArch NCG: Refactor getRegister' Remove some special cases which can be handled just as well by the generic case. This increases code re-use while also fixing #23749. Since some of the special case wasn't upholding Note [Signed arithmetic on AArch64]. - - - - - 1b213d33 by Andreas Klebinger at 2023-10-10T19:05:09-04:00 Aarch ncg: Optimize immediate use for address calculations When the offset doesn't fit into the immediate we now just reuse the general getRegister' code path which is well optimized to compute the offset into a register instead of a special case for CmmRegOff. This means we generate a lot less code under certain conditions which is why performance metrics for these improve. ------------------------- Metric Decrease: T4801 T5321FD T5321Fun ------------------------- - - - - - b7df0732 by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over mem management checks These are for heap allocation, a strictly RTS concern. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. The RTS configure one has a new ``` AC_CHECK_SIZEOF([void *]) ``` that the top-level configure version didn't have, so that `ac_cv_sizeof_void_p` is defined. Once more code is moved over in latter commits, that can go away. Progress towards #17191 - - - - - 41130a65 by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over `__thread` check This used by (@bgamari thinks) the `GCThread` abstraction in the RTS. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - cc5ec2bd by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over misc function checks These are for general use in the RTS. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - 809e7c2d by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over `eventfd` check This check is for the RTS part of the event manager and has a corresponding part in `base`. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - 58f3babf by John Ericson at 2023-10-11T16:02:48-04:00 Split `FP_CHECK_PTHREADS` and move part to RTS configure `NEED_PTHREAD_LIB` is unused since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build system), and so is no longer defined. Progress towards #17191 - - - - - e99cf237 by Moritz Angermann at 2023-10-11T16:03:24-04:00 nativeGen: section flags for .text$foo only Commit 3ece9856d157c85511d59f9f862ab351bbd9b38b, was supposed to fix #22834 in !9810. It does however add "xr" indiscriminatly to .text sections even if splitSections is disabled. This leads to the assembler saying: ghc_1.s:7849:0: error: Warning: Ignoring changed section attributes for .text | 7849 | .section .text,"xr" | ^ - - - - - f383a242 by Sylvain Henry at 2023-10-11T16:04:04-04:00 Modularity: pass TempDir instead of DynFlags (#17957) - - - - - 34fc28b0 by John Ericson at 2023-10-12T06:48:28-04:00 Test that functions from `mingwex` are available Ryan wrote these two minimizations, but they never got added to the test suite. See #23309, #23378 Co-Authored-By: Ben Gamari <bgamari.foss at gmail.com> Co-Authored-By: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - bdb54a0e by John Ericson at 2023-10-12T06:48:28-04:00 Do not check for the `mingwex` library in `/configure` See the recent discussion in !10360 --- Cabal will itself check for the library for the packages that need it, and while the autoconf check additionally does some other things like define a `HAS_LIBMINGWEX` C Preprocessor macro, those other things are also unused and unneeded. Progress towards #17191, which aims to get rid of `/configure` entirely. - - - - - 43e814e1 by Ben Gamari at 2023-10-12T06:49:40-04:00 base: Introduce move modules into src The only non-move changes here are whitespace changes to pass the `whitespace` test and a few testsuite adaptations. - - - - - df81536f by Moritz Angermann at 2023-10-12T06:50:16-04:00 [PEi386 linker] Bounds check and null-deref guard We should resonably be able to expect that we won't exceed the number of sections if we assume to be dealing with legal object files. We can however not guarantee that we get some negative values, and while we try to special case most, we should exclude negative indexing into the sections array. We also need to ensure that we do not try to derefences targetSection, if it is NULL, due to the switch statement. - - - - - c74c4f00 by John Ericson at 2023-10-12T10:31:13-04:00 Move apple compat check to RTS configure - - - - - c80778ea by John Ericson at 2023-10-12T10:31:13-04:00 Move clock/timer fun checks to RTS configure Actual library check (which will set the Cabal flag) is left in the top-level configure for now. Progress towards #17191 - - - - - 7f9f2686 by John Ericson at 2023-10-12T10:31:13-04:00 Move visibility and "musttail" annotation checks to the RTS configure All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - ffb3efe6 by John Ericson at 2023-10-12T10:31:13-04:00 Move leading underscore checks to RTS configure `CabalLeadingUnderscore` is done via Hadrian already, so we can stop `AC_SUBST`ing it completely. - - - - - 25fa4b02 by John Ericson at 2023-10-12T10:31:13-04:00 Move alloca, fork, const, and big endian checks to RTS configure All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. - - - - - 5170f42a by John Ericson at 2023-10-12T10:31:13-04:00 Move libdl check to RTS configure - - - - - ea7a1447 by John Ericson at 2023-10-12T10:31:13-04:00 Adjust `FP_FIND_LIBFFI` Just set vars, and `AC_SUBST` in top-level configure. Don't define `HAVE_SYSTEM_LIBFFI` because nothing is using it. It hasn't be in used since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build system). - - - - - f399812c by John Ericson at 2023-10-12T10:31:13-04:00 Split BFD support to RTS configure The flag is still in the top-level configure, but the other checks (which define various macros --- important) are in the RTS configure. - - - - - f64f44e9 by John Ericson at 2023-10-12T10:31:13-04:00 Split libm check between top level and RTS - - - - - dafc4709 by Moritz Angermann at 2023-10-12T10:31:49-04:00 CgUtils.fixStgRegStmt respect register width This change ensure that the reg + offset computation is always of the same size. Before this we could end up with a 64bit register, and then add a 32bit offset (on 32bit platforms). This not only would fail type sanity checking, but also incorrectly truncate 64bit values into 32bit values silently on 32bit architectures. - - - - - 9e6ef7ba by Matthew Pickering at 2023-10-12T20:35:00-04:00 hadrian: Decrease verbosity of cabal commands In Normal, most tools do not produce output to stdout unless there are error conditions. Reverts 7ed65f5a1bc8e040e318ccff395f53a9bbfd8217 - - - - - 08fc27af by John Ericson at 2023-10-12T20:35:36-04:00 Do not substitute `@...@` for stage-specific values in cabal files `rts` and `ghc-prim` now no longer have a `*.cabal.in` to set Cabal flag defaults; instead manual choices are passed to configure in the usual way. The old way was fundamentally broken, because it meant we were baking these Cabal files for a specific stage. Now we only do stage-agnostic @...@ substitution in cabal files (the GHC version), and so all stage-specific configuration is properly confined to `_build` and the right stage dir. Also `include-ghc-prim` is a flag that no longer exists for `ghc-prim` (it was removed in 835d8ddbbfb11796ea8a03d1806b7cee38ba17a6) so I got rid of it. Co-Authored-By: Matthew Pickering <matthewtpickering at gmail.com> - - - - - a0ac8785 by Sebastian Graf at 2023-10-14T19:17:12-04:00 Fix restarts in .ghcid Using the whole of `hadrian/` restarted in a loop for me. - - - - - fea9ecdb by Sebastian Graf at 2023-10-14T19:17:12-04:00 CorePrep: Refactor FloatingBind (#23442) A drastically improved architecture for local floating in CorePrep that decouples the decision of whether a float is going to be let- or case-bound from how far it can float (out of strict contexts, out of lazy contexts, to top-level). There are a couple of new Notes describing the effort: * `Note [Floating in CorePrep]` for the overview * `Note [BindInfo and FloatInfo]` for the new classification of floats * `Note [Floats and FloatDecision]` for how FloatInfo is used to inform floating decisions This is necessary ground work for proper treatment of Strict fields and unlifted values at top-level. Fixes #23442. NoFib results (omitted = 0.0%): ``` -------------------------------------------------------------------------------- Program Allocs Instrs -------------------------------------------------------------------------------- pretty 0.0% -1.6% scc 0.0% -1.7% -------------------------------------------------------------------------------- Min 0.0% -1.7% Max 0.0% -0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 32523713 by Matthew Pickering at 2023-10-14T19:17:49-04:00 hadrian: Move ghcBinDeps into ghcLibDeps This completes a5227080b57cb51ac34d4c9de1accdf6360b818b, the `ghc-usage.txt` and `ghci-usage.txt` file are also used by the `ghc` library so need to make sure they are present in the libdir even if we are not going to build `ghc-bin`. This also fixes things for cross compilers because the stage2 cross-compiler requires the ghc-usage.txt file, but we are using the stage2 lib folder but not building stage3:exe:ghc-bin so ghc-usage.txt was not being generated. - - - - - ec3c4488 by sheaf at 2023-10-14T19:18:29-04:00 Combine GREs when combining in mkImportOccEnv In `GHC.Rename.Names.mkImportOccEnv`, we sometimes discard one import item in favour of another, as explained in Note [Dealing with imports] in `GHC.Rename.Names`. However, this can cause us to lose track of important parent information. Consider for example #24084: module M1 where { class C a where { type T a } } module M2 ( module M1 ) where { import M1 } module M3 where { import M2 ( C, T ); instance C () where T () = () } When processing the import list of `M3`, we start off (for reasons that are not relevant right now) with two `Avail`s attached to `T`, namely `C(C, T)` and `T(T)`. We combine them in the `combine` function of `mkImportOccEnv`; as described in Note [Dealing with imports] we discard `C(C, T)` in favour of `T(T)`. However, in doing so, we **must not** discard the information want that `C` is the parent of `T`. Indeed, losing track of this information can cause errors when importing, as we could get an error of the form ‘T’ is not a (visible) associated type of class ‘C’ We fix this by combining the two GREs for `T` using `plusGRE`. Fixes #24084 - - - - - 257c2807 by Ilias Tsitsimpis at 2023-10-14T19:19:07-04:00 hadrian: Pass -DNOSMP to C compiler when needed Hadrian passes the -DNOSMP flag to GHC when the target doesn't support SMP, but doesn't pass it to CC as well, leading to the following compilation error on mips64el: | Run Cc (FindCDependencies CDep) Stage1: rts/sm/NonMovingScav.c => _build/stage1/rts/build/c/sm/NonMovingScav.o.d Command line: /usr/bin/mips64el-linux-gnuabi64-gcc -E -MM -MG -MF _build/stage1/rts/build/c/hooks/FlagDefaults.thr_debug_p_o.d -MT _build/stage1/rts/build/c/hooks/FlagDefaults.o -Irts/include -I_build/stage1/rts/build -I_build/stage1/rts/build/include -Irts/include -x c rts/hooks/FlagDefaults.c -Wall -Wextra -Wstrict-prototypes -Wmissing-prototypes -Wmissing-declarations -Winline -Wpointer-arith -Wmissing-noreturn -Wnested-externs -Wredundant-decls -Wundef -fno-strict-aliasing -DTHREADED_RTS -DDEBUG -fomit-frame-pointer -O2 -g -Irts -I_build/stage1/rts/build -DDEBUG -fno-omit-frame-pointer -g3 -O0 ===> Command failed with error code: 1 In file included from rts/include/Stg.h:348, from rts/include/Rts.h:38, from rts/hooks/FlagDefaults.c:8: rts/include/stg/SMP.h:416:2: error: #error memory barriers unimplemented on this architecture 416 | #error memory barriers unimplemented on this architecture | ^~~~~ rts/include/stg/SMP.h:440:2: error: #error memory barriers unimplemented on this architecture 440 | #error memory barriers unimplemented on this architecture | ^~~~~ rts/include/stg/SMP.h:464:2: error: #error memory barriers unimplemented on this architecture 464 | #error memory barriers unimplemented on this architecture | ^~~~~ The old make system correctly passed this flag to both GHC and CC [1]. Fix this error by passing -DNOSMP to CC as well. [1] https://gitlab.haskell.org/ghc/ghc/-/blob/00920f176b0235d5bb52a8e054d89a664f8938fe/rts/ghc.mk#L407 Closes #24082 - - - - - 13d3c613 by John Ericson at 2023-10-14T19:19:42-04:00 Users Guide: Drop dead code for Haddock refs to `parallel` I noticed while working on !11451 that `@LIBRARY_parallel_UNIT_ID@` was not substituted. It is dead code -- there is no `parallel-ref` usages and it doesn't look like there ever was (going back to 3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b), so let's delete it. - - - - - fe067577 by Sylvain Henry at 2023-10-18T19:40:25-04:00 Avoid out-of-bound array access in bigNatIsPowerOf2 (fix #24066) bigNatIndex# in the `where` clause wasn't guarded by "bigNatIsZero a". - - - - - cc1625b1 by Sylvain Henry at 2023-10-18T19:40:25-04:00 Bignum: fix right shift of negative BigNat with native backend - - - - - cbe4400d by Sylvain Henry at 2023-10-18T19:40:25-04:00 Rts: expose rtsOutOfBoundsAccess symbol - - - - - 72c7380c by Sylvain Henry at 2023-10-18T19:40:25-04:00 Hadrian: enable `-fcheck-prim-bounds` in validate flavour This allows T24066 to fail when the bug is present. Otherwise the out-of-bound access isn't detected as it happens in ghc-bignum which wasn't compiled with the bounds check. - - - - - f9436990 by John Ericson at 2023-10-18T19:41:01-04:00 Make Hadrian solely responsible for substituting `docs/users_guide/ghc_config.py.in` Fixes #24091 Progress on #23966 Issue #24091 reports that `@ProjectVersion@` is no longer being substituted in the GHC user's guide. I assume this is a recent issue, but I am not sure how it's worked since c1a3ecde720b3bddc2c8616daaa06ee324e602ab; it looks like both Hadrian and configure are trying to substitute the same `.in` file! Now only Hadrian does. That is better anyways; already something that issue #23966 requested. It seems like we were missing some dependencies in Hadrian. (I really, really hate that this is possible!) Hopefully it is fixed now. - - - - - b12df0bb by John Ericson at 2023-10-18T19:41:37-04:00 `ghcversion.h`: No need to cope with undefined `ProjectPatchLevel*` Since 4e6c80197f1cc46dfdef0300de46847c7cfbdcb0, these are guaranteed to be defined. (Guaranteed including a test in the testsuite.) - - - - - 0295375a by John Ericson at 2023-10-18T19:41:37-04:00 Generate `ghcversion.h` from a `.in` file Now that there are no conditional sections (see the previous commit), we can just a do simple substitution rather than pasting it together line by line. Progress on #23966 - - - - - 740a1b85 by Krzysztof Gogolewski at 2023-10-19T11:37:20-04:00 Add a regression test for #24064 - - - - - 921fbf2f by Hécate Moonlight at 2023-10-19T11:37:59-04:00 CLC Proposal #182: Export List from Data.List Proposal link: https://github.com/haskell/core-libraries-committee/issues/182 - - - - - 4f02d3c1 by Sylvain Henry at 2023-10-20T04:01:32-04:00 rts: fix small argument passing on big-endian arch (fix #23387) - - - - - b86243b4 by Sylvain Henry at 2023-10-20T04:02:13-04:00 Interpreter: fix literal alignment on big-endian architectures (fix #19261) Literals weren't correctly aligned on big-endian, despite what the comment said. - - - - - a4b2ec47 by Sylvain Henry at 2023-10-20T04:02:54-04:00 Testsuite: recomp011 and recomp015 are fixed on powerpc These tests have been fixed but not tested and re-enabled on big-endian powerpc (see comments in #11260 and #11323) - - - - - fded7dd4 by Sebastian Graf at 2023-10-20T04:03:30-04:00 CorePrep: Allow floating dictionary applications in -O0 into a Rec (#24102) - - - - - 02efc181 by John Ericson at 2023-10-22T02:48:55-04:00 Move function checks to RTS configure Some of these functions are used in `base` too, but we can copy the checks over to its configure if that's an issue. - - - - - 5f4bccab by John Ericson at 2023-10-22T02:48:55-04:00 Move over a number of C-style checks to RTS configure - - - - - 5cf04f58 by John Ericson at 2023-10-22T02:48:55-04:00 Move/Copy more `AC_DEFINE` to RTS config Only exception is the LLVM version macros, which are used for GHC itself. - - - - - b8ce5dfe by John Ericson at 2023-10-22T02:48:55-04:00 Define `TABLES_NEXT_TO_CODE` in the RTS configure We create a new cabal flag to facilitate this. - - - - - 4a40271e by John Ericson at 2023-10-22T02:48:55-04:00 Configure scripts: `checkOS`: Make a bit more robust `mingw64` and `mingw32` are now both accepted for `OSMinGW32`. This allows us to cope with configs/triples that we haven't normalized extra being what GNU `config.sub` does. - - - - - 16bec0a0 by John Ericson at 2023-10-22T02:48:55-04:00 Generate `ghcplatform.h` from RTS configure We create a new cabal flag to facilitate this. - - - - - 7dfcab2f by John Ericson at 2023-10-22T02:48:55-04:00 Get rid of all mention of `mk/config.h` The RTS configure script is now solely responsible for managing its headers; the top level configure script does not help. - - - - - c1e3719c by Cheng Shao at 2023-10-22T02:49:33-04:00 rts: drop stale mentions of MIN_UPD_SIZE We used to have MIN_UPD_SIZE macro that describes the minimum reserved size for thunks, so that the thunk can be overwritten in place as indirections or blackholes. However, this macro has not been actually defined or used anywhere since a long time ago; StgThunkHeader already reserves a padding word for this purpose. Hence this patch which drops stale mentions of MIN_UPD_SIZE. - - - - - d24b0d85 by Andrew Lelechenko at 2023-10-22T02:50:11-04:00 base changelog: move non-backported entries from 4.19 section to 4.20 Neither !10933 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Text.Read.Lex.html#numberToRangedRational) nor !10189 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Data.List.NonEmpty.html#unzip) were backported to `base-4.19.0.0`. Moving them to `base-4.20.0.0` section. Also minor stylistic changes to other entries, bringing them to a uniform form. - - - - - de78b32a by Alan Zimmerman at 2023-10-23T09:09:41-04:00 EPA Some tweaks to annotations - Fix span for GRHS - Move TrailingAnns from last match to FunBind - Fix GADT 'where' clause span - Capture full range for a CaseAlt Match - - - - - d5a8780d by Simon Hengel at 2023-10-23T09:10:23-04:00 Update primitives.rst - - - - - 4d075924 by Josh Meredith at 2023-10-24T23:04:12+11:00 JS/userguide: add explanation of writing jsbits - - - - - 07ab5cc1 by Cheng Shao at 2023-10-24T15:40:32-04:00 testsuite: increase timeout of ghc-api tests for wasm32 ghc-api tests for wasm32 are more likely to timeout due to the large wasm module sizes, especially when testing with wasm native tail calls, given wasmtime's handling of tail call opcodes are suboptimal at the moment. It makes sense to increase timeout specifically for these tests on wasm32. This doesn't affect other targets, and for wasm32 we don't increase timeout for all tests, so not to risk letting major performance regressions slip through the testsuite. - - - - - 0d6acca5 by Greg Steuck at 2023-10-26T08:44:23-04:00 Explicitly require RLIMIT_AS before use in OSMem.c This is done elsewhere in the source tree. It also suddenly is required on OpenBSD. - - - - - 9408b086 by Sylvain Henry at 2023-10-26T08:45:03-04:00 Modularity: modularize external linker Decouple runLink from DynFlags to allow calling runLink more easily. This is preliminary work for calling Emscripten's linker (emcc) from our JavaScript linker. - - - - - e0f35030 by doyougnu at 2023-10-27T08:41:12-04:00 js: add JStg IR, remove unsaturated constructor - Major step towards #22736 and adding the optimizer in #22261 - - - - - 35587eba by Simon Peyton Jones at 2023-10-27T08:41:48-04:00 Fix a bug in tail calls with ticks See #24078 for the diagnosis. The change affects only the Tick case of occurrence analysis. It's a bit hard to test, so no regression test (yet anyway). - - - - - 9bc5cb92 by Matthew Craven at 2023-10-28T07:06:17-04:00 Teach tag-inference about SeqOp/seq# Fixes the STG/tag-inference analogue of #15226. Co-Authored-By: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - 34f06334 by Moritz Angermann at 2023-10-28T07:06:53-04:00 [PEi386] Mask SYM_TYPE_DUP_DISCARD in makeSymbolExtra 48e391952c17ff7eab10b0b1456e3f2a2af28a9b introduced `SYM_TYPE_DUP_DISCARD` to the bitfield. The linker however, failed to mask the `SYM_TYPE_DUP_DISCARD` value. Thus `== SYM_TYPE_CODE` comparisons easily failed. This lead to us relocating DATA lookups (GOT) into E8 (call) and E9 (jump) instructions. - - - - - 5b51b2a2 by Mario Blažević at 2023-10-28T07:07:33-04:00 Fix and test for issue #24111, TH.Ppr output of pattern synonyms - - - - - 723bc352 by Alan Zimmerman at 2023-10-30T20:36:41-04:00 EPA: print doc comments as normal comments And ignore the ones allocated in haddock processing. It does not guarantee that every original haddock-like comment appears in the output, as it discards ones that have no legal attachment point. closes #23459 - - - - - 21b76843 by Simon Peyton Jones at 2023-10-30T20:37:17-04:00 Fix non-termination bug in equality solver constraint left-to-right then right to left, forever. Easily fixed. - - - - - 270867ac by Sebastian Graf at 2023-10-30T20:37:52-04:00 ghc-toolchain: build with `-package-env=-` (#24131) Otherwise globally installed libraries (via `cabal install --lib`) break the build. Fixes #24131. - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - 7a90020f by Krzysztof Gogolewski at 2023-10-31T20:03:37-04:00 docs: fix ScopedTypeVariables example (#24101) The previous example didn't compile. Furthermore, it wasn't demonstrating the point properly. I have changed it to an example which shows that 'a' in the signature must be the same 'a' as in the instance head. - - - - - 49f69f50 by Krzysztof Gogolewski at 2023-10-31T20:04:13-04:00 Fix pretty-printing of type family dependencies "where" should be after the injectivity annotation. - - - - - 73c191c0 by Ben Gamari at 2023-10-31T20:04:49-04:00 gitlab-ci: Bump LLVM bootstrap jobs to Debian 12 As the Debian 10 images have too old an LLVM. Addresses #24056. - - - - - 5b0392e0 by Matthew Pickering at 2023-10-31T20:04:49-04:00 ci: Run aarch64 llvm backend job with "LLVM backend" label This brings it into line with the x86 LLVM backend job. - - - - - 9f9c9227 by Ryan Scott at 2023-11-01T09:19:12-04:00 More robust checking for DataKinds As observed in #22141, GHC was not doing its due diligence in catching code that should require `DataKinds` in order to use. Most notably, it was allowing the use of arbitrary data types in kind contexts without `DataKinds`, e.g., ```hs data Vector :: Nat -> Type -> Type where ``` This patch revamps how GHC tracks `DataKinds`. The full specification is written out in the `DataKinds` section of the GHC User's Guide, and the implementation thereof is described in `Note [Checking for DataKinds]` in `GHC.Tc.Validity`. In brief: * We catch _type_-level `DataKinds` violations in the renamer. See `checkDataKinds` in `GHC.Rename.HsType` and `check_data_kinds` in `GHC.Rename.Pat`. * We catch _kind_-level `DataKinds` violations in the typechecker, as this allows us to catch things that appear beneath type synonyms. (We do *not* want to do this in type-level contexts, as it is perfectly fine for a type synonym to mention something that requires DataKinds while still using the type synonym in a module that doesn't enable DataKinds.) See `checkValidType` in `GHC.Tc.Validity`. * There is now a single `TcRnDataKindsError` that classifies all manner of `DataKinds` violations, both in the renamer and the typechecker. The `NoDataKindsDC` error has been removed, as it has been subsumed by `TcRnDataKindsError`. * I have added `CONSTRAINT` is `isKindTyCon`, which is what checks for illicit uses of data types at the kind level without `DataKinds`. Previously, `isKindTyCon` checked for `Constraint` but not `CONSTRAINT`. This is inconsistent, given that both `Type` and `TYPE` were checked by `isKindTyCon`. Moreover, it thwarted the implementation of the `DataKinds` check in `checkValidType`, since we would expand `Constraint` (which was OK without `DataKinds`) to `CONSTRAINT` (which was _not_ OK without `DataKinds`) and reject it. Now both are allowed. * I have added a flurry of additional test cases that test various corners of `DataKinds` checking. Fixes #22141. - - - - - 575d7690 by Sylvain Henry at 2023-11-01T09:19:53-04:00 JS: fix FFI "wrapper" and "dynamic" Fix codegen and helper functions for "wrapper" and "dynamic" foreign imports. Fix tests: - ffi006 - ffi011 - T2469 - T4038 Related to #22363 - - - - - 81fb8885 by Alan Zimmerman at 2023-11-01T22:23:56-04:00 EPA: Use full range for Anchor This change requires a series of related changes, which must all land at the same time, otherwise all the EPA tests break. * Use the current Anchor end as prior end Use the original anchor location end as the source of truth for calculating print deltas. This allows original spacing to apply in most cases, only changed AST items need initial delta positions. * Add DArrow to TrailingAnn * EPA Introduce HasTrailing in ExactPrint Use [TrailingAnn] in enterAnn and remove it from ExactPrint (LocatedN RdrName) * In HsDo, put TrailingAnns at top of LastStmt * EPA: do not convert comments to deltas when balancing. * EPA: deal with fallout from getMonoBind * EPA fix captureLineSpacing * EPA print any comments in the span before exiting it * EPA: Add comments to AnchorOperation * EPA: remove AnnEofComment, it is no longer used Updates Haddock submodule - - - - - 03e82511 by Rodrigo Mesquita at 2023-11-01T22:24:32-04:00 Fix in docs regarding SSymbol, SNat, SChar (#24119) - - - - - 362cc693 by Matthew Pickering at 2023-11-01T22:25:08-04:00 hadrian: Update bootstrap plans (9.4.6, 9.4.7, 9.6.2, 9.6.3, 9.8.1) Updating the bootstrap plans with more recent GHC versions. - - - - - 00b9b8d3 by Matthew Pickering at 2023-11-01T22:25:08-04:00 ci: Add 9.8.1 bootstrap testing job - - - - - ef3d20f8 by Matthew Pickering at 2023-11-01T22:25:08-04:00 Compatibility with 9.8.1 as boot compiler This fixes several compatability issues when using 9.8.1 as the boot compiler. * An incorrect version guard on the stack decoding logic in ghc-heap * Some ghc-prim bounds need relaxing * ghc is no longer wired in, so we have to remove the -this-unit-id ghc call. Fixes #24077 - - - - - 6755d833 by Jaro Reinders at 2023-11-03T10:54:42+01:00 Add NCG support for common 64bit operations to the x86 backend. These used to be implemented via C calls which was obviously quite bad for performance for operations like simple addition. Co-authored-by: Andreas Klebinger - - - - - 0dfb1fa7 by Vladislav Zavialov at 2023-11-03T14:08:41-04:00 T2T in Expressions (#23738) This patch implements the T2T (term-to-type) transformation in expressions. Given a function with a required type argument vfun :: forall a -> ... the user can now call it as vfun (Maybe Int) instead of vfun (type (Maybe Int)) The Maybe Int argument is parsed and renamed as a term (HsExpr), but then undergoes a conversion to a type (HsType). See the new function expr_to_type in compiler/GHC/Tc/Gen/App.hs and Note [RequiredTypeArguments and the T2T mapping] Left as future work: checking for puns. - - - - - cc1c7c54 by Duncan Coutts at 2023-11-05T00:23:44-04:00 Add a test for I/O managers It tries to cover the cases of multiple threads waiting on the same fd for reading and multiple threads waiting for writing, including wait cancellation by async exceptions. It should work for any I/O manager, in-RTS or in-Haskell. Unfortunately it will not currently work for Windows because it relies on anonymous unix sockets. It could in principle be ported to use Windows named pipes. - - - - - 2e448f98 by Cheng Shao at 2023-11-05T00:23:44-04:00 Skip the IOManager test on wasm32 arch. The test relies on the sockets API which are not (yet) available. - - - - - fe50eb35 by Cheng Shao at 2023-11-05T00:24:20-04:00 compiler: fix eager blackhole symbol in wasm32 NCG - - - - - af771148 by Cheng Shao at 2023-11-05T00:24:20-04:00 testsuite: fix optasm tests for wasm32 - - - - - 1b90735c by Matthew Pickering at 2023-11-05T00:24:20-04:00 testsuite: Add wasm32 to testsuite arches with NCG The compiler --info reports that wasm32 compilers have a NCG, so we should agree with that here. - - - - - db9a6496 by Alan Zimmerman at 2023-11-05T00:24:55-04:00 EPA: make locA a function, not a field name And use it to generalise reLoc The following for the windows pipeline one. 5.5% Metric Increase: T5205 - - - - - 833e250c by Simon Peyton Jones at 2023-11-05T00:25:31-04:00 Update the unification count in wrapUnifierX Omitting this caused type inference to fail in #24146. This was an accidental omision in my refactoring of the equality solver. - - - - - e451139f by Andreas Klebinger at 2023-11-05T00:26:07-04:00 Remove an accidental git conflict marker from a comment. - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 30baac7a by Tobias Haslop at 2023-11-06T10:50:32+00:00 Add laws relating between Foldable/Traversable with their Bi- superclasses See https://github.com/haskell/core-libraries-committee/issues/205 for discussion. This commit also documents that the tuple instances only satisfy the laws up to lazyness, similar to the documentation added in !9512. - - - - - df626f00 by Tobias Haslop at 2023-11-07T02:20:37-05:00 Elaborate on the quantified superclass of Bifunctor This was requested in the comment https://github.com/haskell/core-libraries-committee/issues/93#issuecomment-1597271700 for when Traversable becomes a superclass of Bitraversable, but similarly applies to Functor/Bifunctor, which already are in a superclass relationship. - - - - - 8217acb8 by Alan Zimmerman at 2023-11-07T02:21:12-05:00 EPA: get rid of l2l and friends Replace them with l2l to convert the location la2la to convert a GenLocated thing Updates haddock submodule - - - - - dd88a260 by Luite Stegeman at 2023-11-07T02:21:53-05:00 JS: remove broken newIdents from JStg Monad GHC.JS.JStg.Monad.newIdents was broken, resulting in duplicate identifiers being generated in h$c1, h$c2, ... . This change removes the broken newIdents. - - - - - 455524a2 by Matthew Craven at 2023-11-09T08:41:59-05:00 Create specially-solved DataToTag class Closes #20532. This implements CLC proposal 104: https://github.com/haskell/core-libraries-committee/issues/104 The design is explained in Note [DataToTag overview] in GHC.Tc.Instance.Class. This replaces the existing `dataToTag#` primop. These metric changes are not "real"; they represent Unique-related flukes triggering on a different set of jobs than they did previously. See also #19414. Metric Decrease: T13386 T8095 Metric Increase: T13386 T8095 Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - a05f4554 by Alan Zimmerman at 2023-11-09T08:42:35-05:00 EPA: get rid of glRR and friends in GHC/Parser.y With the HasLoc and HasAnnotation classes, we can replace a number of type-specific helper functions in the parser with polymorphic ones instead Metric Decrease: MultiLayerModulesTH_Make - - - - - 18498538 by Cheng Shao at 2023-11-09T16:58:12+00:00 ci: bump ci-images for wasi-sdk upgrade - - - - - 52c0fc69 by PHO at 2023-11-09T19:16:22-05:00 Don't assume the current locale is *.UTF-8, set the encoding explicitly primops.txt contains Unicode characters: > LC_ALL=C ./genprimopcode --data-decl < ./primops.txt > genprimopcode: <stdin>: hGetContents: invalid argument (cannot decode byte sequence starting from 226) Hadrian must also avoid using readFile' to read primops.txt because it tries to decode the file with a locale-specific encoding. - - - - - 7233b3b1 by PHO at 2023-11-09T19:17:01-05:00 Use '[' instead of '[[' because the latter is a Bash-ism It doesn't work on platforms where /bin/sh is something other than Bash. - - - - - 6dbab180 by Simon Peyton Jones at 2023-11-09T19:17:36-05:00 Add an extra check in kcCheckDeclHeader_sig Fix #24083 by checking for a implicitly-scoped type variable that is not actually bound. See Note [Disconnected type variables] in GHC.Tc.Gen.HsType For some reason, on aarch64-darwin we saw a 2.8% decrease in compiler allocations for MultiLayerModulesTH_Make; but 0.0% on other architectures. Metric Decrease: MultiLayerModulesTH_Make - - - - - 22551364 by Sven Tennie at 2023-11-11T06:35:22-05:00 AArch64: Delete unused LDATA pseudo-instruction Though there were consuming functions for LDATA, there were no producers. Thus, the removed code was "dead". - - - - - 2a0ec8eb by Alan Zimmerman at 2023-11-11T06:35:59-05:00 EPA: harmonise acsa and acsA in GHC/Parser.y With the HasLoc class, we can remove the acsa helper function, using acsA instead. - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 7ae517a0 by Teo Camarasu at 2023-11-12T08:04:12-05:00 nofib: bump submodule This includes changes that: - fix building a benchmark with HEAD - remove a Makefile-ism that causes errors in bash scripts Resolves #24178 - - - - - 3f0036ec by Alan Zimmerman at 2023-11-12T08:04:47-05:00 EPA: Replace Anchor with EpaLocation An Anchor has a location and an operation, which is either that it is unchanged or that it has moved with a DeltaPos data Anchor = Anchor { anchor :: RealSrcSpan , anchor_op :: AnchorOperation } An EpaLocation also has either a location or a DeltaPos data EpaLocation = EpaSpan !RealSrcSpan !(Strict.Maybe BufSpan) | EpaDelta !DeltaPos ![LEpaComment] Now that we do not care about always having a location in the anchor, we remove Anchor and replace it with EpaLocation We do this with a type alias initially, to ease the transition. The alias will be removed in time. We also have helpers to reconstruct the AnchorOperation from an EpaLocation. This is also temporary. Updates Haddock submodule - - - - - a7492048 by Alan Zimmerman at 2023-11-12T13:43:07+00:00 EPA: get rid of AnchorOperation Now that the Anchor type is an alias for EpaLocation, remove AnchorOperation. Updates haddock submodule - - - - - 0745c34d by Andrew Lelechenko at 2023-11-13T16:25:07-05:00 Add since annotation for showHFloat - - - - - e98051a5 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 Suppress duplicate librares linker warning of new macOS linker Fixes #24167 XCode 15 introduced a new linker which warns on duplicate libraries being linked. To disable this warning, we pass -Wl,-no_warn_duplicate_libraries as suggested by Brad King in CMake issue #25297. This flag isn't necessarily available to other linkers on darwin, so we must only configure it into the CC linker arguments if valid. - - - - - c411c431 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Encoding test witnesses recent iconv bug is fragile A regression in the new iconv() distributed with XCode 15 and MacOS Sonoma causes the test 'encoding004' to fail in the CP936 roundrip. We mark this test as fragile until this is fixed upstream (rather than broken, since previous versions of iconv pass the test) See #24161 - - - - - ce7fe5a9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Update to LC_ALL=C no longer being ignored in darwin MacOS seems to have fixed an issue where it used to ignore the variable `LC_ALL` in program invocations and default to using Unicode. Since the behaviour seems to be fixed to account for the locale variable, we mark tests that were previously broken in spite of it as fragile (since they now pass in recent macOS distributions) See #24161 - - - - - e6c803f7 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 darwin: Fix single_module is obsolete warning In XCode 15's linker, -single_module is the default and otherwise passing it as a flag results in a warning being raised: ld: warning: -single_module is obsolete This patch fixes this warning by, at configure time, determining whether the linker supports -single_module (which is likely false for all non-darwin linkers, and true for darwin linkers in previous versions of macOS), and using that information at runtime to decide to pass or not the flag in the invocation. Fixes #24168 - - - - - 929ba2f9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Skip MultiLayerModulesTH_Make on darwin The recent toolchain upgrade on darwin machines resulted in the MultiLayerModulesTH_Make test metrics varying too much from the baseline, ultimately blocking the CI pipelines. This commit skips the test on darwin to temporarily avoid failures due to the environment change in the runners. However, the metrics divergence is being investigated still (tracked in #24177) - - - - - af261ccd by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 configure: check target (not build) understands -no_compact_unwind Previously, we were branching on whether the build system was darwin to shortcut this check, but we really want to branch on whether the target system (which is what we are configuring ld_prog for) is darwin. - - - - - 2125c176 by Luite Stegeman at 2023-11-15T13:19:38-05:00 JS: Fix missing variable declarations The JStg IR update was missing some local variable declarations that were present earlier, causing global variables to be used implicitly (or an error in JavaScript strict mode). This adds the local variable declarations again. - - - - - 99ced73b by Krzysztof Gogolewski at 2023-11-15T13:20:14-05:00 Remove loopy superclass solve mechanism Programs with a -Wloopy-superclass-solve warning will now fail with an error. Fixes #23017 - - - - - 2aff2361 by Zubin Duggal at 2023-11-15T13:20:50-05:00 users-guide: Fix links to libraries from the users-guide. The unit-ids generated in c1a3ecde720b3bddc2c8616daaa06ee324e602ab include the package name, so we don't need to explicitly add it to the links. Fixes #24151 - - - - - 27981fac by Alan Zimmerman at 2023-11-15T13:21:25-05:00 EPA: splitLHsForAllTyInvis does not return ann We did not use the annotations returned from splitLHsForAllTyInvis, so do not return them. - - - - - a6467834 by Krzysztof Gogolewski at 2023-11-15T22:22:59-05:00 Document defaulting of RuntimeReps Fixes #24099 - - - - - 2776920e by Simon Peyton Jones at 2023-11-15T22:23:35-05:00 Second fix to #24083 My earlier fix turns out to be too aggressive for data/type families See wrinkle (DTV1) in Note [Disconnected type variables] - - - - - cee81370 by Sylvain Henry at 2023-11-16T09:57:46-05:00 Fix unusable units and module reexport interaction (#21097) This commit fixes an issue with ModUnusable introduced in df0f148feae. In mkUnusableModuleNameProvidersMap we traverse the list of unusable units and generate ModUnusable origin for all the modules they contain: exposed modules, hidden modules, and also re-exported modules. To do this we have a two-level map: ModuleName -> Unit:ModuleName (aka Module) -> ModuleOrigin So for each module name "M" in broken unit "u" we have: "M" -> u:M -> ModUnusable reason However in the case of module reexports we were using the *target* module as a key. E.g. if "u:M" is a reexport for "X" from unit "o": "M" -> o:X -> ModUnusable reason Case 1: suppose a reexport without module renaming (u:M -> o:M) from unusable unit u: "M" -> o:M -> ModUnusable reason Here it's claiming that the import of M is unusable because a reexport from u is unusable. But if unit o isn't unusable we could also have in the map: "M" -> o:M -> ModOrigin ... Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModOrigin) Case 2: similarly we could have 2 unusable units reexporting the same module without renaming, say (u:M -> o:M) and (v:M -> o:M) with u and v unusable. It gives: "M" -> o:M -> ModUnusable ... (for u) "M" -> o:M -> ModUnusable ... (for v) Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModUnusable). This led to #21097, #16996, #11050. To fix this, in this commit we make ModUnusable track whether the module used as key is a reexport or not (for better error messages) and we use the re-export module as key. E.g. if "u:M" is a reexport for "o:X" and u is unusable, we now record: "M" -> u:M -> ModUnusable reason reexported=True So now, we have two cases for a reexport u:M -> o:X: - u unusable: "M" -> u:M -> ModUnusable ... reexported=True - u usable: "M" -> o:X -> ModOrigin ... reexportedFrom=u:M The second case is indexed with o:X because in this case the Semigroup instance of ModOrigin is used to combine valid expositions of a module (directly or via reexports). Note that module lookup functions select usable modules first (those who have a ModOrigin value), so it doesn't matter if we add new ModUnusable entries in the map like this: "M" -> { u:M -> ModUnusable ... reexported=True o:M -> ModOrigin ... } The ModOrigin one will be used. Only if there is no ModOrigin or ModHidden entry will the ModUnusable error be printed. See T21097 for an example printing several reasons why an import is unusable. - - - - - 3e606230 by Krzysztof Gogolewski at 2023-11-16T09:58:22-05:00 Fix IPE test A helper function was defined in a different module than used. To reproduce: ./hadrian/build test --test-root-dirs=testsuite/tests/rts/ipe - - - - - 49f5264b by Andreas Klebinger at 2023-11-16T20:52:11-05:00 Properly compute unpacked sizes for -funpack-small-strict-fields. Use rep size rather than rep count to compute the size. Fixes #22309 - - - - - b4f84e4b by James Henri Haydon at 2023-11-16T20:52:53-05:00 Explicit methods for Alternative Compose Explicitly define some and many in Alternative instance for Data.Functor.Compose Implementation of https://github.com/haskell/core-libraries-committee/issues/181 - - - - - 9bc0dd1f by Ignat Insarov at 2023-11-16T20:53:34-05:00 Add permutations for non-empty lists. Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 5643ecf9 by Andrew Lelechenko at 2023-11-16T20:53:34-05:00 Update changelog and since annotations for Data.List.NonEmpty.permutations Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 94ff2134 by Oleg Alexander at 2023-11-16T20:54:15-05:00 Update doc string for traceShow Updated doc string for traceShow. - - - - - faff671a by Luite Stegeman at 2023-11-17T14:12:51+01:00 JS: clean up some foreign imports - - - - - 856e0a4e by Sven Tennie at 2023-11-18T06:54:11-05:00 AArch64: Remove unused instructions As these aren't ever emitted, we don't even know if they work or will ever be used. If one of them is needed in future, we may easily re-add it. Deleted instructions are: - CMN - ANDS - BIC - BICS - EON - ORN - ROR - TST - STP - LDP - DMBSY - - - - - 615441ef by Alan Zimmerman at 2023-11-18T06:54:46-05:00 EPA: Replace Monoid with NoAnn Remove the final Monoid instances in the exact print infrastructure. For Windows CI Metric Decrease: T5205 - - - - - 5a6c49d4 by David Feuer at 2023-11-20T18:53:18-05:00 Speed up stimes in instance Semigroup Endo As discussed at https://github.com/haskell/core-libraries-committee/issues/4 - - - - - cf9da4b3 by Andrew Lelechenko at 2023-11-20T18:53:18-05:00 base: reflect latest changes in the changelog - - - - - 48bf364e by Alan Zimmerman at 2023-11-20T18:53:54-05:00 EPA: Use SrcSpan in EpaSpan This is more natural, since we already need to deal with invalid RealSrcSpans, and that is exactly what SrcSpan.UnhelpfulSpan is for. Updates haddock submodule. - - - - - 97ec37cc by Sebastian Graf at 2023-11-20T18:54:31-05:00 Add regression test for #6070 Fixes #6070. - - - - - e9d5ae41 by Owen Shepherd at 2023-11-21T18:32:23-05:00 chore: Correct typo in the gitlab MR template [skip ci] - - - - - f158a8d0 by Rodrigo Mesquita at 2023-11-21T18:32:59-05:00 Improve error message when reading invalid `.target` files A `.target` file generated by ghc-toolchain or by configure can become invalid if the target representation (`Toolchain.Target`) is changed while the files are not re-generated by calling `./configure` or `ghc-toolchain` again. There is also the issue of hadrian caching the dependencies on `.target` files, which makes parsing fail when reading reading the cached value if the representation has been updated. This patch provides a better error message in both situations, moving away from a terrible `Prelude.read: no parse` error that you would get otherwise. Fixes #24199 - - - - - 955520c6 by Ben Gamari at 2023-11-21T18:33:34-05:00 users guide: Note that QuantifiedConstraints implies ExplicitForAll Fixes #24025. - - - - - 17ec3e97 by Owen Shepherd at 2023-11-22T09:37:28+01:00 fix: Change type signatures in NonEmpty export comments to reflect reality This fixes several typos in the comments of Data.List.NonEmpty export list items. - - - - - 2fd78f9f by Samuel Thibault at 2023-11-22T11:49:13-05:00 Fix the platform string for GNU/Hurd As commited in Cargo https://github.com/haskell/cabal/pull/9434 there is confusion between "gnu" and "hurd". This got fixed in Cargo, we need the converse in Hadrian. Fixes #24180 - - - - - a79960fe by Alan Zimmerman at 2023-11-22T11:49:48-05:00 EPA: Tuple Present no longer has annotation The Present constructor for a Tuple argument will never have an exact print annotation. So make this impossible. - - - - - 121c9ab7 by David Binder at 2023-11-22T21:12:29-05:00 Unify the hpc testsuites The hpc testsuite was split between testsuite/tests/hpc and the submodule libraries/hpc/test. This commit unifies the two testsuites in the GHC repository in the directory testsuite/tests/hpc. - - - - - d2733a05 by Alan Zimmerman at 2023-11-22T21:13:05-05:00 EPA: empty tup_tail has noAnn In Parser.y, the tup_tail rule had the following option | {- empty -} %shift { return [Left noAnn] } Once this works through PostProcess.hs, it means we add an extra Missing constructor if the last item was a comma. Change the annotation type to a Bool to indicate this, and use the EpAnn Anchor for the print location for the others. - - - - - fa576eb8 by Andreas Klebinger at 2023-11-24T08:29:13-05:00 Fix FMA primops generating broken assembly on x86. `genFMA3Code` assumed that we had to take extra precations to avoid overwriting the result of `getNonClobberedReg`. One of these special cases caused a bug resulting in broken assembly. I believe we don't need to hadle these cases specially at all, which means this MR simply deletes the special cases to fix the bug. Fixes #24160 - - - - - 34d86315 by Alan Zimmerman at 2023-11-24T08:29:49-05:00 EPA: Remove parenthesizeHsType This is called from PostProcess.hs, and adds spurious parens. With the looser version of exact printing we had before we could tolerate this, as they would be swallowed by the original at the same place. But with the next change (remove EpAnnNotUsed) they result in duplicates in the output. For Darwin build: Metric Increase: MultiLayerModulesTH_OneShot - - - - - 3ede659d by Vladislav Zavialov at 2023-11-26T06:43:32-05:00 Add name for -Wdeprecated-type-abstractions (#24154) This warning had no name or flag and was triggered unconditionally. Now it is part of -Wcompat. - - - - - 7902ebf8 by Alan Zimmerman at 2023-11-26T06:44:08-05:00 EPA: Remove EpAnnNotUsed We no longer need the EpAnnNotUsed constructor for EpAnn, as we can represent an unused annotation with an anchor having a EpaDelta of zero, and empty comments and annotations. This simplifies code handling annotations considerably. Updates haddock submodule Metric Increase: parsing001 - - - - - 471b2672 by Mario Blažević at 2023-11-26T06:44:48-05:00 Bumped the upper bound of text to <2.2 - - - - - d1bf25c7 by Vladislav Zavialov at 2023-11-26T11:45:49-05:00 Term variable capture (#23740) This patch changes type variable lookup rules (lookupTypeOccRn) and implicit quantification rules (filterInScope) so that variables bound in the term namespace can be captured at the type level {-# LANGUAGE RequiredTypeArguments #-} f1 x = g1 @x -- `x` used in a type application f2 x = g2 (undefined :: x) -- `x` used in a type annotation f3 x = g3 (type x) -- `x` used in an embedded type f4 x = ... where g4 :: x -> x -- `x` used in a type signature g4 = ... This change alone does not allow us to accept examples shown above, but at least it gets them past the renamer. - - - - - da863d15 by Vladislav Zavialov at 2023-11-26T11:46:26-05:00 Update Note [hsScopedTvs and visible foralls] The Note was written before GHC gained support for visible forall in types of terms. Rewrite a few sentences and use a better example. - - - - - b5213542 by Matthew Pickering at 2023-11-27T12:53:59-05:00 testsuite: Add mechanism to collect generic metrics * Generalise the metric logic by adding an additional field which allows you to specify how to query for the actual value. Previously the method of querying the baseline value was abstracted (but always set to the same thing). * This requires rejigging how the stat collection works slightly but now it's more uniform and hopefully simpler. * Introduce some new "generic" helper functions for writing generic stats tests. - collect_size ( deviation, path ) Record the size of the file as a metric - stat_from_file ( metric, deviation, path ) Read a value from the given path, and store that as a metric - collect_generic_stat ( metric, deviation, get_stat) Provide your own `get_stat` function, `lambda way: <Int>`, which can be used to establish the current value of the metric. - collect_generic_stats ( metric_info ): Like collect_generic_stat but provide the whole dictionary of metric definitions. { metric: { deviation: <Int> current: lambda way: <Int> } } * Introduce two new "size" metrics for keeping track of build products. - `size_hello_obj` - The size of `hello.o` from compiling hello.hs - `libdir` - The total size of the `libdir` folder. * Track the number of modules in the AST tests - CountDepsAst - CountDepsParser This lays the infrastructure for #24191 #22256 #17129 - - - - - 7d9a2e44 by ARATA Mizuki at 2023-11-27T12:54:39-05:00 x86: Don't require -mavx2 when using 256-bit floating-point SIMD primitives Fixes #24222 - - - - - 4e5ff6a4 by Alan Zimmerman at 2023-11-27T12:55:15-05:00 EPA: Remove SrcSpanAnn Now that we only have a single constructor for EpAnn, And it uses a SrcSpan for its location, we can do away with SrcSpanAnn completely. It only existed to wrap the original SrcSpan in a location, and provide a place for the exact print annotation. For darwin only: Metric Increase: MultiLayerModulesTH_OneShot Updates haddock submodule - - - - - e05bca39 by Krzysztof Gogolewski at 2023-11-28T08:00:55-05:00 testsuite: don't initialize testdir to '.' The test directory is removed during cleanup, if there's an interrupt that could remove the entire repository. Fixes #24219 - - - - - af881674 by Alan Zimmerman at 2023-11-28T08:01:30-05:00 EPA: Clean up mkScope in Ast.hs Now that we have HasLoc we can get rid of all the custom variants of mkScope For deb10-numa Metric Increase: libdir - - - - - 292983c8 by Ben Gamari at 2023-11-28T22:44:28-05:00 distrib: Rediscover otool and install_name_tool on Darwin In the bindist configure script we must rediscover the `otool` and `install_name_tool`s since they may be different from the build environment. Fixes #24211. - - - - - dfe1c354 by Stefan Schulze Frielinghaus at 2023-11-28T22:45:04-05:00 llvmGen: Align objects in the data section Objects in the data section may be referenced via tagged pointers. Thus, align those objects to a 4- or 8-byte boundary for 32- or 64-bit platforms, respectively. Note, this may need to be reconsidered if objects with a greater natural alignment requirement are emitted as e.g. 128-bit atomics. Fixes #24163. - - - - - f6c486c3 by Matthew Pickering at 2023-11-29T11:08:13-05:00 metrics: Widen libdir and size_hello_obj acceptance window af8816740d9b8759be1a22af8adcb5f13edeb61d shows that the libdir size can fluctuate quite significantly even when the change is quite small. Therefore we widen the acceptance window to 10%. - - - - - 99a6a49c by Alan Zimmerman at 2023-11-29T11:08:49-05:00 EPA: Clean up TC Monad Utils We no longer need the alternative variant of addLocM (addLocMA) nor wrapLocAM, wrapLocSndMA. aarch64-darwin Metric Increase: MultiLayerModulesTH_OneShot deb10-numa-slow Metric Decrease: libdir - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - cbc03fa0 by Sebastian Graf at 2023-11-30T12:37:21-05:00 perf tests: Move comments into new `Note [Sensitivity to unique increment]` (#19414) And additionally to T12545, link from T8095, T13386 to this new Note. - - - - - c7623b22 by Alan Zimmerman at 2023-11-30T12:37:56-05:00 EPA: EpaDelta for comment has no comments EpaLocation is used to position things. It has two constructors, EpaSpan holding a SrcSpan, and EpaDelta with a delta position and a possible list of comments. The comment list is needed because the location in EpaDelta has no absolute information to decide which comments should be emitted before them when printing. But it is also used for specifying the position of a comment. To prevent the absurdity of a comment position having a list of comments in it, we make EpaLocation parameterisable, using comments for the normal case and a constant for within comments. Updates haddock submodule. aarch64-darwin Metric Decrease: MultiLayerModulesTH_OneShot - - - - - bd8acc0c by Krzysztof Gogolewski at 2023-11-30T12:38:32-05:00 Kind-check body of a required forall We now require that in 'forall a -> ty', ty has kind TYPE r for some r. Fixes #24176 - - - - - 010fb784 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove incorrect haddock link quotes in code block - - - - - cda9c12d by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove cycle from group haddock example - - - - - 495265b9 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use repl haddock syntax in group docs - - - - - d134d1de by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use list [] notation in group haddock - - - - - dfcf629c by Owen Shepherd at 2023-12-03T00:10:10-05:00 docs(NonEmpty/group): Specify final property of group function in haddock - - - - - cad3b734 by Owen Shepherd at 2023-12-03T00:10:10-05:00 fix: Add missing property of List.group - - - - - bad37656 by Matthew Pickering at 2023-12-03T00:10:46-05:00 testsuite: Fix T21097b test with make 4.1 (deb9) cee81370cd6ef256f66035e3116878d4cb82e28b recently added a test which failed on deb9 because the version of make was emitting the recipe failure to stdout rather than stderr. One way to fix this is to be more precise in the test about which part of the output we care about inspecting. - - - - - 5efdf421 by Matthew Pickering at 2023-12-03T00:11:21-05:00 testsuite: Track size of libdir in bytes For consistency it's better if we track all size metrics in bytes. Metric Increase: libdir - - - - - f5eb0f29 by Matthew Pickering at 2023-12-03T00:11:22-05:00 testsuite: Remove rogue trace in testsuite I accidentally left a trace in the generics metric patch. - - - - - d5610737 by Claudio Bley at 2023-12-06T16:13:33-05:00 Only exit ghci in -e mode when :add command fails Previously, when running `ghci -e ':add Sample.hs'` the process would exit with exit code 1 if the file exists and could be loaded. Fixes #24115 - - - - - 0f0c53a5 by Vladislav Zavialov at 2023-12-06T16:14:09-05:00 T2T in Patterns (#23739) This patch implements the T2T (term-to-type) transformation in patterns. Patterns that are checked against a visible forall can now be written without the `type` keyword: \(type t) (x :: t) -> ... -- old \t (x :: t) -> ... -- new The `t` binder is parsed and renamed as a term pattern (Pat), but then undergoes a conversion to a type pattern (HsTyPat). See the new function pat_to_type_pat in compiler/GHC/Tc/Gen/Pat.hs - - - - - 10a1a6c6 by Sebastian Graf at 2023-12-06T16:14:45-05:00 Pmc: Fix SrcLoc and warning for incomplete irrefutable pats (#24234) Before, the source location would point at the surrounding function definition, causing the confusion in #24234. I also took the opportunity to introduce a new `LazyPatCtx :: HsMatchContext _` to make the warning message say "irrefutable pattern" instead of "pattern binding". - - - - - 36b9a38c by Matthew Pickering at 2023-12-06T16:15:21-05:00 libraries: Bump filepath to 1.4.200.1 and unix to 2.8.4.0 Updates filepath submodule Updates unix submodule Fixes #24240 - - - - - 91ff0971 by Matthew Pickering at 2023-12-06T16:15:21-05:00 Submodule linter: Allow references to tags We modify the submodule linter so that if the bumped commit is a specific tag then the commit is accepted. Fixes #24241 - - - - - 86f652dc by Zubin Duggal at 2023-12-06T16:15:21-05:00 hadrian: set -Wno-deprecations for directory and Win32 The filepath bump to 1.4.200.1 introduces a deprecation warning. See https://gitlab.haskell.org/ghc/ghc/-/issues/24240 https://github.com/haskell/filepath/pull/206 - - - - - 7ac6006e by Sylvain Henry at 2023-12-06T16:16:02-05:00 Zap OccInfo on case binders during StgCse #14895 #24233 StgCse can revive dead binders: case foo of dead { Foo x y -> Foo x y; ... } ===> case foo of dead { Foo x y -> dead; ... } -- dead is no longer dead So we must zap occurrence information on case binders. Fix #14895 and #24233 - - - - - 57c391c4 by Sebastian Graf at 2023-12-06T16:16:37-05:00 Cpr: Turn an assertion into a check to deal with some dead code (#23862) See the new `Note [Dead code may contain type confusions]`. Fixes #23862. - - - - - c1c8abf8 by Zubin Duggal at 2023-12-08T02:25:07-05:00 testsuite: add test for #23944 - - - - - 6329d308 by Zubin Duggal at 2023-12-08T02:25:07-05:00 driver: Only run a dynamic-too pipeline if object files are going to be generated Otherwise we run into a panic in hscMaybeWriteIface: "Unexpected DT_Dyn state when writing simple interface" when dynamic-too is enabled We could remove the panic and just write the interface even if the state is `DT_Dyn`, but it seems pointless to run the pipeline twice when `hscMaybeWriteIface` is already designed to write both `hi` and `dyn_hi` files if dynamic-too is enabled. Fixes #23944. - - - - - 28811f88 by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Improve duplicate elimination in SpecConstr This partially fixes #24229. See the new Note [Pattern duplicate elimination] in SpecConstr - - - - - fec7894f by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Make SpecConstr deal with casts better This patch does two things, to fix #23209: * It improves SpecConstr so that it no longer quantifies over coercion variables. See Note [SpecConstr and casts] * It improves the rule matcher to deal nicely with the case where the rule does not quantify over coercion variables, but the the template has a cast in it. See Note [Casts in the template] - - - - - 8db8d2fd by Zubin Duggal at 2023-12-08T05:47:54-05:00 driver: Don't lose track of nodes when we fail to resolve cycles The nodes that take part in a cycle should include both hs-boot and hs files, but when we fail to resolve a cycle, we were only counting the nodes from the graph without boot files. Fixes #24196 - - - - - c5b4efd3 by Zubin Duggal at 2023-12-08T05:48:30-05:00 testsuite: Skip MultiLayerModulesTH_OneShot on darwin See #24177 - - - - - fae472a9 by Wendao Lee at 2023-12-08T05:49:12-05:00 docs(Data.Char):Add more detailed descriptions for some functions Related changed function's docs: -GHC.Unicode.isAlpha -GHC.Unicode.isPrint -GHC.Unicode.isAlphaNum Add more details for what the function will return. Co-authored-by: Bodigrim <andrew.lelechenko at gmail.com> - - - - - ca7510e4 by Malik Ammar Faisal at 2023-12-08T05:49:55-05:00 Fix float parsing in GHC Cmm Lexer Add test case for bug #24224 - - - - - d8baa1bd by Simon Peyton Jones at 2023-12-08T15:40:37+00:00 Take care when simplifying unfoldings This MR fixes a very subtle bug exposed by #24242. See Note [Environment for simplLetUnfolding]. I also updated a bunch of Notes on shadowing - - - - - 03ca551d by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in FloatIn Relevant to #3458 - - - - - 50c78779 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in SpecConstr - - - - - 9431e195 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Add test for #22238 - - - - - d9e4c597 by Vladislav Zavialov at 2023-12-11T04:19:34-05:00 Make forall a keyword (#23719) Before this change, GHC used to accept `forall` as a term-level identifier: -- from constraints-0.13 forall :: forall p. (forall a. Dict (p a)) -> Dict (Forall p) forall d = ... Now it is a parse error. The -Wforall-identifier warning has served its purpose and is now a deprecated no-op. - - - - - 58d56644 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we actually clear the interactive context before reloading Previously we called discardIC, but immediately after set the session back to an old HscEnv that still contained the IC Partially addresses #24107 Fixes #23405 - - - - - 8e5745a0 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we force the lookup of old build artifacts before returning the build plan This prevents us from retaining all previous build artifacts in memory until a recompile finishes, instead only retaining the exact artifacts we need. Fixes #24118 - - - - - 105c370c by Zubin Duggal at 2023-12-11T04:20:10-05:00 testsuite: add test for #24118 and #24107 MultiLayerModulesDefsGhci was not able to catch the leak because it uses :l which discards the previous environment. Using :r catches both of these leaks - - - - - e822ff88 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Add some strictness annotations to ImportSpec and related constructors This prevents us from retaining entire HscEnvs. Force these ImportSpecs when forcing the GlobalRdrEltX Adds an NFData instance for Bag Fixes #24107 - - - - - 522c12a4 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Force IfGlobalRdrEnv in NFData instance. - - - - - 188b280d by Arnaud Spiwack at 2023-12-11T15:33:31+01:00 LinearTypes => MonoLocalBinds - - - - - 8e0446df by Arnaud Spiwack at 2023-12-11T15:44:28+01:00 Linear let and where bindings For expediency, the initial implementation of linear types in GHC made it so that let and where binders would always be considered unrestricted. This was rather unpleasant, and probably a big obstacle to adoption. At any rate, this was not how the proposal was designed. This patch fixes this infelicity. It was surprisingly difficult to build, which explains, in part, why it took so long to materialise. As of this patch, let or where bindings marked with %1 will be linear (respectively %p for an arbitrary multiplicity p). Unmarked let will infer their multiplicity. Here is a prototypical example of program that used to be rejected and is accepted with this patch: ```haskell f :: A %1 -> B g :: B %1 -> C h :: A %1 -> C h x = g y where y = f x ``` Exceptions: - Recursive let are unrestricted, as there isn't a clear semantics of what a linear recursive binding would be. - Destructive lets with lazy bindings are unrestricted, as their desugaring isn't linear (see also #23461). - (Strict) destructive lets with inferred polymorphic type are unrestricted. Because the desugaring isn't linear (See #18461 down-thread). Closes #18461 and #18739 Co-authored-by: @jackohughes - - - - - effa7e2d by Matthew Craven at 2023-12-12T04:37:20-05:00 Introduce `dataToTagSmall#` primop (closes #21710) ...and use it to generate slightly better code when dataToTag# is used at a "small data type" where there is no need to mess with "is_too_big_tag" or potentially look at an info table. Metric Decrease: T18304 - - - - - 35c7aef6 by Matthew Craven at 2023-12-12T04:37:20-05:00 Fix formatting of Note [alg-alt heap check] - - - - - 7397c784 by Oleg Grenrus at 2023-12-12T04:37:56-05:00 Allow untyped brackets in typed splices and vice versa. Resolves #24190 Apparently the check was essentially always (as far as I can trace back: d0d47ba76f8f0501cf3c4966bc83966ab38cac27), and while it does catch some mismatches, the type-checker will catch them too. OTOH, it prevents writing completely reasonable programs. - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - a3ee3b99 by Moritz Angermann at 2023-12-12T19:50:58-05:00 Drop hard Xcode dependency XCODE_VERSION calls out to `xcodebuild`, which is only available when having `Xcode` installed. The CommandLineTools are not sufficient. To install Xcode, you must have an apple id to download the Xcode.xip from apple. We do not use xcodebuild anywhere in our build explicilty. At best it appears to be a proxy for checking the linker or the compiler. These should rather be done with ``` xcrun ld -version ``` or similar, and not by proxy through Xcode. The CLR should be sufficient for building software on macOS. - - - - - 1c9496e0 by Vladislav Zavialov at 2023-12-12T19:51:34-05:00 docs: update information on RequiredTypeArguments Update the User's Guide and Release Notes to account for the recent progress in the implementation of RequiredTypeArguments. - - - - - d0b17576 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Fix off-by-one in assertion Previously we failed to account for the NULL terminator `postString` asserted that there is enough room in the buffer for the string. - - - - - a10f9b9b by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Honor result of ensureRoomForVariableEvent is Previously we would keep plugging along, even if isn't enough room for the event. - - - - - 0e0f41c0 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Avoid truncating event sizes Previously ensureRoomForVariableEvent would truncate the desired size to 16-bits, resulting in #24197. Fixes #24197. - - - - - 64e724c8 by Artin Ghasivand at 2023-12-13T06:34:20-05:00 Remove the "Derived Constraint" argument of TcPluginSolver, docs - - - - - fe6d97dd by Vladislav Zavialov at 2023-12-13T06:34:56-05:00 EPA: Move tokens into GhcPs extension fields (#23447) Summary of changes * Remove Language.Haskell.Syntax.Concrete * Move all tokens into GhcPs extension fields (LHsToken -> EpToken) * Create new TTG extension fields as needed * Drop the MultAnn wrapper Updates the haddock submodule. Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 8106e695 by Zubin Duggal at 2023-12-13T06:35:34-05:00 testsuite: use copy_files in T23405 This prevents the tree from being dirtied when the file is modified. - - - - - ed0e4099 by Bryan Richter at 2023-12-14T04:30:53-05:00 Document ghc package's PVP-noncompliance This changes nothing, it just makes the status quo explicit. - - - - - 8bef8d9f by Luite Stegeman at 2023-12-14T04:31:33-05:00 JS: Mark spurious CI failures js_fragile(24259) This marks the spurious test failures on the JS platform as js_fragile(24259), so we don't hold up merge requests while fixing the underlying issues. See #24259 - - - - - 1c79526a by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Late plugins - - - - - 000c3302 by Finley McIlwaine at 2023-12-15T12:24:40-08:00 withTiming on LateCCs and late plugins - - - - - be4551ac by Finley McIlwaine at 2023-12-15T12:24:40-08:00 add test for late plugins - - - - - 7c29da9f by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Document late plugins - - - - - 9a52ae46 by Ben Gamari at 2023-12-20T07:07:26-05:00 Fix thunk update ordering Previously we attempted to ensure soundness of concurrent thunk update by synchronizing on the access of the thunk's info table pointer field. This was believed to be sufficient since the indirectee (which may expose a closure allocated by another core) would not be examined until the info table pointer update is complete. However, it turns out that this can result in data races in the presence of multiple threads racing a update a single thunk. For instance, consider this interleaving under the old scheme: Thread A Thread B --------- --------- t=0 Enter t 1 Push update frame 2 Begin evaluation 4 Pause thread 5 t.indirectee=tso 6 Release t.info=BLACKHOLE 7 ... (e.g. GC) 8 Resume thread 9 Finish evaluation 10 Relaxed t.indirectee=x 11 Load t.info 12 Acquire fence 13 Inspect t.indirectee 14 Release t.info=BLACKHOLE Here Thread A enters thunk `t` but is soon paused, resulting in `t` being lazily blackholed at t=6. Then, at t=10 Thread A finishes evaluation and updates `t.indirectee` with a relaxed store. Meanwhile, Thread B enters the blackhole. Under the old scheme this would introduce an acquire-fence but this would only synchronize with Thread A at t=6. Consequently, the result of the evaluation, `x`, is not visible to Thread B, introducing a data race. We fix this by treating the `indirectee` field as we do all other mutable fields. This means we must always access this field with acquire-loads and release-stores. See #23185. - - - - - f4b53538 by Vladislav Zavialov at 2023-12-20T07:08:02-05:00 docs: Fix link to 051-ghc-base-libraries.rst The proposal is no longer available at the previous URL. - - - - - f7e21fab by Matthew Pickering at 2023-12-21T14:57:40+00:00 hadrian: Build all executables in bin/ folder In the end the bindist creation logic copies them all into the bin folder. There is no benefit to building a specific few binaries in the lib/bin folder anymore. This also removes the ad-hoc logic to copy the touchy and unlit executables from stage0 into stage1. It takes <1s to build so we might as well just build it. - - - - - 0038d052 by Zubin Duggal at 2023-12-22T23:28:00-05:00 testsuite: mark jspace as fragile on i386. This test has been flaky for some time and has been failing consistently on i386-linux since 8e0446df landed. See #24261 - - - - - dfd670a0 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 609e6225 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 865513b2 by Ömer Sinan AÄŸacan at 2023-12-24T10:11:13-05:00 Fix BNF in user manual 6.6.8.2: formal syntax for instance declarations - - - - - c247b6be by Zubin Duggal at 2023-12-25T16:01:23-05:00 docs: document permissibility of -XOverloadedLabels (#24249) Document the permissibility introduced by https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst - - - - - e5b7eb59 by Ömer Sinan AÄŸacan at 2023-12-25T16:02:03-05:00 Fix a code block syntax in user manual sec. 6.8.8.6 - - - - - 2db11c08 by Ben Gamari at 2023-12-29T15:35:48-05:00 genSym: Reimplement via CAS on 32-bit platforms Previously the remaining use of the C implementation on 32-bit platforms resulted in a subtle bug, #24261. This was due to the C object (which used the RTS's `atomic_inc64` macro) being compiled without `-threaded` yet later being used in a threaded compiler. Side-step this issue by using the pure Haskell `genSym` implementation on all platforms. This required implementing `fetchAddWord64Addr#` in terms of CAS on 64-bit platforms. - - - - - 19328a8c by Xiaoyan Ren at 2023-12-29T15:36:30-05:00 Do not color the diagnostic code in error messages (#24172) - - - - - 685b467c by Krzysztof Gogolewski at 2023-12-29T15:37:06-05:00 Enforce that bindings of implicit parameters are lifted Fixes #24298 - - - - - bc4d67b7 by Matthew Craven at 2023-12-31T06:15:42-05:00 StgToCmm: Detect some no-op case-continuations ...and generate no code for them. Fixes #24264. - - - - - 5b603139 by Krzysztof Gogolewski at 2023-12-31T06:16:18-05:00 Revert "testsuite: mark jspace as fragile on i386." This reverts commit 0038d052c8c80b4b430bb2aa1c66d5280be1aa95. The atomicity bug should be fixed by !11802. - - - - - d55216ad by Krzysztof Gogolewski at 2024-01-01T12:05:49-05:00 Refactor: store [[PrimRep]] rather than [Type] in STG StgConApp stored a list of types. This list was used exclusively during unarisation of unboxed sums (mkUbxSum). However, this is at a wrong level of abstraction: STG shouldn't be concerned with Haskell types, only PrimReps. Update the code to store a [[PrimRep]]. Also, there's no point in storing this list when we're not dealing with an unboxed sum. - - - - - 8b340bc7 by Ömer Sinan AÄŸacan at 2024-01-01T12:06:29-05:00 Kind signatures docs: mention that they're allowed in newtypes - - - - - 989bf8e5 by Zubin Duggal at 2024-01-03T20:08:47-05:00 ci: Ensure we use the correct bindist name for the test artifact when generating release ghcup metadata Fixes #24268 - - - - - 89299a89 by Krzysztof Gogolewski at 2024-01-03T20:09:23-05:00 Refactor: remove calls to typePrimRepArgs The function typePrimRepArgs is just a thin wrapper around typePrimRep, adding a VoidRep if the list is empty. However, in StgToByteCode, we were discarding that VoidRep anyway, so there's no point in calling it. - - - - - c7be0c68 by mmzk1526 at 2024-01-03T20:10:07-05:00 Use "-V" for alex version check for better backward compatibility Fixes #24302. In recent versions of alex, "-v" is used for "--verbose" instead of "-version". - - - - - 67dbcc0a by Krzysztof Gogolewski at 2024-01-05T02:07:18-05:00 Fix VoidRep handling in ghci debugger 'go' inside extractSubTerms was giving a bad result given a VoidRep, attempting to round towards the next multiple of 0. I don't understand much about the debugger but the code should be better than it was. Fixes #24306 - - - - - 90ea574e by Krzysztof Gogolewski at 2024-01-05T02:07:54-05:00 VoidRep-related refactor * In GHC.StgToByteCode, replace bcIdPrimId with idPrimRep, bcIdArgRep with idArgRep, atomPrimRep with stgArgRep1. All of them were duplicates. * In GHC.Stg.Unarise, we were converting a PrimRep to a Type and back to PrimRep. Remove the calls to primRepToType and typePrimRep1 which cancel out. * In GHC.STG.Lint, GHC.StgToCmm, GHC.Types.RepType we were filtering out VoidRep from the result of typePrimRep. But typePrimRep never returns VoidRep - remove the filtering. - - - - - eaf72479 by brian at 2024-01-06T23:03:09-05:00 Add unaligned Addr# primops Implements CLC proposal #154: https://github.com/haskell/core-libraries-committee/issues/154 * add unaligned addr primops * add tests * accept tests * add documentation * fix js primops * uncomment in access ops * use Word64 in tests * apply suggestions * remove extra file * move docs * remove random options * use setByteArray# primop * better naming * update base-exports test * add base-exports for other architectures - - - - - d471d445 by Krzysztof Gogolewski at 2024-01-06T23:03:47-05:00 Remove VoidRep from PrimRep, introduce PrimOrVoidRep This introduces data PrimOrVoidRep = VoidRep | NVRep PrimRep changes typePrimRep1 to return PrimOrVoidRep, and adds a new function typePrimRepU to be used when the argument is definitely non-void. Details in Note [VoidRep] in GHC.Types.RepType. Fixes #19520 - - - - - 48720a07 by Matthew Craven at 2024-01-08T18:57:36-05:00 Apply Note [Sensitivity to unique increment] to LargeRecord - - - - - 9e2e180f by Sebastian Graf at 2024-01-08T18:58:13-05:00 Debugging: Add diffUFM for convenient diffing between UniqFMs - - - - - 948f3e35 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Rename Opt_D_dump_stranal to Opt_D_dump_dmdanal ... and Opt_D_dump_str_signatures to Opt_D_dump_dmd_signatures - - - - - 4e217e3e by Sebastian Graf at 2024-01-08T18:58:13-05:00 Deprecate -ddump-stranal and -ddump-str-signatures ... and suggest -ddump-dmdanal and -ddump-dmd-signatures instead - - - - - 6c613c90 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Move testsuite/tests/stranal to testsuite/tests/dmdanal A separate commit so that the rename is obvious to Git(Lab) - - - - - c929f02b by Sebastian Graf at 2024-01-08T18:58:13-05:00 CoreSubst: Stricten `substBndr` and `cloneBndr` Doing so reduced allocations of `cloneBndr` by about 25%. ``` T9233(normal) ghc/alloc 672,488,656 663,083,216 -1.4% GOOD T9675(optasm) ghc/alloc 423,029,256 415,812,200 -1.7% geo. mean -0.1% minimum -1.7% maximum +0.1% ``` Metric Decrease: T9233 - - - - - e3ca78f3 by Krzysztof Gogolewski at 2024-01-10T17:35:59-05:00 Deprecate -Wsemigroup This warning was used to prepare for Semigroup becoming a superclass of Monoid, and for (<>) being exported from Prelude. This happened in GHC 8.4 in 8ae263ceb3566 and feac0a3bc69fd3. The leftover logic for (<>) has been removed in GHC 9.8, 4d29ecdfcc79. Now the warning does nothing at all and can be deprecated. - - - - - 08d14925 by amesgen at 2024-01-10T17:36:42-05:00 WASM metadata: use correct GHC version - - - - - 7a808419 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Allow SCC declarations in TH (#24081) - - - - - 28827c51 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Fix prettyprinting of SCC pragmas - - - - - ae9cc1a8 by Matthew Craven at 2024-01-10T17:38:01-05:00 Fix loopification in the presence of void arguments This also removes Note [Void arguments in self-recursive tail calls], which was just misleading. It's important to count void args both in the function's arity and at the call site. Fixes #24295. - - - - - b718b145 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: Teach testsuite driver about c++ sources - - - - - 09cb57ad by Zubin Duggal at 2024-01-10T17:38:36-05:00 driver: Set -DPROFILING when compiling C++ sources with profiling Earlier, we used to pass all preprocessor flags to the c++ compiler. This meant that -DPROFILING was passed to the c++ compiler because it was a part of C++ flags However, this was incorrect and the behaviour was changed in 8ff3134ed4aa323b0199ad683f72165e51a59ab6. See #21291. But that commit exposed this bug where -DPROFILING was no longer being passed when compiling c++ sources. The fix is to explicitly include -DPROFILING in `opt_cxx` when profiling is enabled to ensure we pass the correct options for the way to both C and C++ compilers Fixes #24286 - - - - - 2cf9dd96 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: rename objcpp -> objcxx To avoid confusion with C Pre Processsor - - - - - af6932d6 by Simon Peyton Jones at 2024-01-10T17:39:12-05:00 Make TYPE and CONSTRAINT not-apart Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty which is supposed to make TYPE and CONSTRAINT be not-apart. Easily fixed. - - - - - 4a39b5ff by Zubin Duggal at 2024-01-10T17:39:48-05:00 ci: Fix typo in mk_ghcup_metadata.py There was a missing colon in the fix to #24268 in 989bf8e53c08eb22de716901b914b3607bc8dd08 - - - - - 13503451 by Zubin Duggal at 2024-01-10T17:40:24-05:00 release-ci: remove release-x86_64-linux-deb11-release+boot_nonmoving_gc job There is no reason to have this release build or distribute this variation. This configuration is for testing purposes only. - - - - - afca46a4 by Sebastian Graf at 2024-01-10T17:41:00-05:00 Parser: Add a Note detailing why we need happy's `error` to implement layout - - - - - eaf8a06d by Krzysztof Gogolewski at 2024-01-11T00:43:17+01:00 Turn -Wtype-equality-out-of-scope on by default Also remove -Wnoncanonical-{monoid,monad}-instances from -Wcompat, since they are enabled by default. Refresh wcompat-warnings/ test with new -Wcompat warnings. Part of #24267 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 42bee5aa by Sebastian Graf at 2024-01-12T21:16:21-05:00 Arity: Require called *exactly once* for eta exp with -fpedantic-bottoms (#24296) In #24296, we had a program in which we eta expanded away an error despite the presence of `-fpedantic-bottoms`. This was caused by turning called *at least once* lambdas into one-shot lambdas, while with `-fpedantic-bottoms` it is only sound to eta expand over lambdas that are called *exactly* once. An example can be found in `Note [Combining arity type with demand info]`. Fixes #24296. - - - - - 7e95f738 by Andreas Klebinger at 2024-01-12T21:16:57-05:00 Aarch64: Enable -mfma by default. Fixes #24311 - - - - - e43788d0 by Jason Shipman at 2024-01-14T12:47:38-05:00 Add more instances for Compose: Fractional, RealFrac, Floating, RealFloat CLC proposal #226 https://github.com/haskell/core-libraries-committee/issues/226 - - - - - ae6d8cd2 by Sebastian Graf at 2024-01-14T12:48:15-05:00 Pmc: COMPLETE pragmas associated with Family TyCons should apply to representation TyCons as well (#24326) Fixes #24326. - - - - - c5fc7304 by sheaf at 2024-01-15T14:15:29-05:00 Use lookupOccRn_maybe in TH.lookupName When looking up a value, we want to be able to find both variables and record fields. So we should not use the lookupSameOccRn_maybe function, as we can't know ahead of time which record field namespace a record field with the given textual name will belong to. Fixes #24293 - - - - - da908790 by Krzysztof Gogolewski at 2024-01-15T14:16:05-05:00 Make the build more strict on documentation errors * Detect undefined labels. This can be tested by adding :ref:`nonexistent` to a documentation rst file; attempting to build docs will fail. Fixed the undefined label in `9.8.1-notes.rst`. * Detect errors. While we have plenty of warnings, we can at least enforce that Sphinx does not report errors. Fixed the error in `required_type_arguments.rst`. Unrelated change: I have documented that the `-dlint` enables `-fcatch-nonexhaustive-cases`, as can be verified by checking `enableDLint`. - - - - - 5077416e by Javier Sagredo at 2024-01-16T15:40:06-05:00 Profiling: Adds an option to not start time profiling at startup Using the functionality provided by d89deeba47ce04a5198a71fa4cbc203fe2c90794, this patch creates a new rts flag `--no-automatic-time-samples` which disables the time profiling when starting a program. It is then expected that the user starts it whenever it is needed. Fixes #24337 - - - - - 5776008c by Matthew Pickering at 2024-01-16T15:40:42-05:00 eventlog: Fix off-by-one error in postIPE We were missing the extra_comma from the calculation of the size of the payload of postIPE. This was causing assertion failures when the event would overflow the buffer by one byte, as ensureRoomForVariable event would report there was enough space for `n` bytes but then we would write `n + 1` bytes into the buffer. Fixes #24287 - - - - - 66dc09b1 by Simon Peyton Jones at 2024-01-16T15:41:18-05:00 Improve SpecConstr (esp nofib/spectral/ansi) This MR makes three improvements to SpecConstr: see #24282 * It fixes an outright (and recently-introduced) bug in `betterPat`, which was wrongly forgetting to compare the lengths of the argument lists. * It enhances ConVal to inclue a boolean for work-free-ness, so that the envt can contain non-work-free constructor applications, so that we can do more: see Note [ConVal work-free-ness] * It rejigs `subsumePats` so that it doesn't reverse the list. This can make a difference because, when patterns overlap, we arbitrarily pick the first. There is no "right" way, but this retains the old pre-subsumePats behaviour, thereby "fixing" the regression in #24282. Nofib results +======================================== | spectral/ansi -21.14% | spectral/hartel/comp_lab_zift -0.12% | spectral/hartel/parstof +0.09% | spectral/last-piece -2.32% | spectral/multiplier +6.03% | spectral/para +0.60% | spectral/simple -0.26% +======================================== | geom mean -0.18% +---------------------------------------- The regression in `multiplier` is sad, but it simply replicates GHC's previous behaviour (e.g. GHC 9.6). - - - - - 65da79b3 by Matthew Pickering at 2024-01-16T15:41:54-05:00 hadrian: Reduce Cabal verbosity The comment claims that `simpleUserHooks` decrease verbosity, and it does, but only for the `postConf` phase. The other phases are too verbose with `-V`. At the moment > 5000 lines of the build log are devoted to output from `cabal copy`. So I take the simple approach and just decrease the verbosity level again. If the output of `postConf` is essential then it would be better to implement our own `UserHooks` which doesn't decrease the verbosity for `postConf`. Fixes #24338 - - - - - 16414d7d by Matthew Pickering at 2024-01-17T10:54:59-05:00 Stop retaining old ModGuts throughout subsequent simplifier phases Each phase of the simplifier typically rewrites the majority of ModGuts, so we want to be able to release the old ModGuts as soon as possible. `name_ppr_ctxt` lives throught the whole optimiser phase and it was retaining a reference to `ModGuts`, so we were failing to release the old `ModGuts` until the end of the phase (potentially doubling peak memory usage for that particular phase). This was discovered using eras profiling (#24332) Fixes #24328 - - - - - 7f0879e1 by Matthew Pickering at 2024-01-17T10:55:35-05:00 Update nofib submodule - - - - - 320454d3 by Cheng Shao at 2024-01-17T23:02:40+00:00 ci: bump ci-images for updated wasm image - - - - - 2eca52b4 by Cheng Shao at 2024-01-17T23:06:44+00:00 base: treat all FDs as "nonblocking" on wasm On posix platforms, when performing read/write on FDs, we check the nonblocking flag first. For FDs without this flag (e.g. stdout), we call fdReady() first, which in turn calls poll() to wait for I/O to be available on that FD. This is problematic for wasm32-wasi: although select()/poll() is supported via the poll_oneoff() wasi syscall, that syscall is rather heavyweight and runtime behavior differs in different wasi implementations. The issue is even worse when targeting browsers, given there's no satisfactory way to implement async I/O as a synchronous syscall, so existing JS polyfills for wasi often give up and simply return ENOSYS. Before we have a proper I/O manager that avoids poll_oneoff() for async I/O on wasm, this patch improves the status quo a lot by merely pretending all FDs are "nonblocking". Read/write on FDs will directly invoke read()/write(), which are much more reliably handled in existing wasi implementations, especially those in browsers. Fixes #23275 and the following test cases: T7773 isEOF001 openFile009 T4808 cgrun025 Approved by CLC proposal #234: https://github.com/haskell/core-libraries-committee/issues/234 - - - - - 83c6c710 by Andrew Lelechenko at 2024-01-18T05:21:49-05:00 base: clarify how to disable warnings about partiality of Data.List.{head,tail} - - - - - c4078f2f by Simon Peyton Jones at 2024-01-18T05:22:25-05:00 Fix four bug in handling of (forall cv. body_ty) These bugs are all described in #24335 It's not easy to provoke the bug, hence no test case. - - - - - 119586ea by Alexis King at 2024-01-19T00:08:00-05:00 Always refresh profiling CCSes after running pending initializers Fixes #24171. - - - - - 9718d970 by Oleg Grenrus at 2024-01-19T00:08:36-05:00 Set default-language: GHC2021 in ghc library Go through compiler/ sources, and remove all BangPatterns (and other GHC2021 enabled extensions in these files). - - - - - 3ef71669 by Matthew Pickering at 2024-01-19T21:55:16-05:00 testsuite: Remove unused have_library function Also remove the hence unused testsuite option `--test-package-db`. Fixes #24342 - - - - - 5b7fa20c by Jade at 2024-01-19T21:55:53-05:00 Fix Spelling in the compiler Tracking: #16591 - - - - - 09875f48 by Matthew Pickering at 2024-01-20T12:20:44-05:00 testsuite: Implement `isInTreeCompiler` in a more robust way Just a small refactoring to avoid redundantly specifying the same strings in two different places. - - - - - 0d12b987 by Jade at 2024-01-20T12:21:20-05:00 Change maintainer email from cvs-ghc at haskell.org to ghc-devs at haskell.org. Fixes #22142 - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - 1fa1c00c by Jade at 2024-01-23T19:17:03-05:00 Enhance Documentation of functions exported by Data.Function This patch aims to improve the documentation of functions exported in Data.Function Tracking: #17929 Fixes: #10065 - - - - - ab47a43d by Jade at 2024-01-23T19:17:39-05:00 Improve documentation of hGetLine. - Add explanation for whether a newline is returned - Add examples Fixes #14804 - - - - - dd4af0e5 by Cheng Shao at 2024-01-23T19:18:17-05:00 Fix genapply for cross-compilation by nuking fragile CPP logic This commit fixes incorrectly built genapply when cross compiling (#24347) by nuking all fragile CPP logic in it from the orbit. All target-specific info are now read from DerivedConstants.h at runtime, see added note for details. Also removes a legacy Makefile and adds haskell language server support for genapply. - - - - - 0cda2b8b by Cheng Shao at 2024-01-23T19:18:17-05:00 rts: enable wasm32 register mapping The wasm backend didn't properly make use of all Cmm global registers due to #24347. Now that it is fixed, this patch re-enables full register mapping for wasm32, and we can now generate smaller & faster wasm modules that doesn't always spill arguments onto the stack. Fixes #22460 #24152. - - - - - 0325a6e5 by Greg Steuck at 2024-01-24T01:29:44-05:00 Avoid utf8 in primops.txt.pp comments They don't make it through readFile' without explicitly setting the encoding. See https://gitlab.haskell.org/ghc/ghc/-/issues/17755 - - - - - 1aaf0bd8 by David Binder at 2024-01-24T01:30:20-05:00 Bump hpc and hpc-bin submodule Bump hpc to 0.7.0.1 Bump hpc-bin to commit d1780eb2 - - - - - e693a4e8 by Ben Gamari at 2024-01-24T01:30:56-05:00 testsuite: Ignore stderr in T8089 Otherwise spurious "Killed: 9" messages to stderr may cause the test to fail. Fixes #24361. - - - - - a40f4ab2 by sheaf at 2024-01-24T14:04:33-05:00 Fix FMA instruction on LLVM We were emitting the wrong instructions for fused multiply-add operations on LLVM: - the instruction name is "llvm.fma.f32" or "llvm.fma.f64", not "fmadd" - LLVM does not support other instructions such as "fmsub"; instead we implement these by flipping signs of some arguments - the instruction is an LLVM intrinsic, which requires handling it like a normal function call instead of a machine instruction Fixes #24223 - - - - - 69abc786 by Andrei Borzenkov at 2024-01-24T14:05:09-05:00 Add changelog entry for renaming tuples from (,,...,,) to Tuple<n> (24291) - - - - - 0ac8f385 by Cheng Shao at 2024-01-25T00:27:48-05:00 compiler: remove unused GHC.Linker module The GHC.Linker module is empty and unused, other than as a hack for the make build system. We can remove it now that make is long gone; the note is moved to GHC.Linker.Loader instead. - - - - - 699da01b by Hécate Moonlight at 2024-01-25T00:28:27-05:00 Clarification for newtype constructors when using `coerce` - - - - - b2d8cd85 by Matt Walker at 2024-01-26T09:50:08-05:00 Fix #24308 Add tests for semicolon separated where clauses - - - - - 0da490a1 by Ben Gamari at 2024-01-26T17:34:41-05:00 hsc2hs: Bump submodule - - - - - 3f442fd2 by Ben Gamari at 2024-01-26T17:34:41-05:00 Bump containers submodule to 0.7 - - - - - 82a1c656 by Sebastian Nagel at 2024-01-29T02:32:40-05:00 base: with{Binary}File{Blocking} only annotates own exceptions Fixes #20886 This ensures that inner, unrelated exceptions are not misleadingly annotated with the opened file. - - - - - 9294a086 by Andreas Klebinger at 2024-01-29T02:33:15-05:00 Fix fma warning when using llvm on aarch64. On aarch64 fma is always on so the +fma flag doesn't exist for that target. Hence no need to try and pass +fma to llvm. Fixes #24379 - - - - - ced2e731 by sheaf at 2024-01-29T17:27:12-05:00 No shadowing warnings for NoFieldSelector fields This commit ensures we don't emit shadowing warnings when a user shadows a field defined with NoFieldSelectors. Fixes #24381 - - - - - 8eeadfad by Patrick at 2024-01-29T17:27:51-05:00 Fix bug wrong span of nested_doc_comment #24378 close #24378 1. Update the start position of span in `nested_doc_comment` correctly. and hence the spans of identifiers of haddoc can be computed correctly. 2. add test `HaddockSpanIssueT24378`. - - - - - a557580f by Alexey Radkov at 2024-01-30T19:41:52-05:00 Fix irrelevant dodgy-foreign-imports warning on import f-pointers by value A test *ÑÑ018* is attached (not sure about the naming convention though). Note that without the fix, the test fails with the *dodgy-foreign-imports* warning passed to stderr. The warning disappears after the fix. GHC shouldn't warn on imports of natural function pointers from C by value (which is feasible with CApiFFI), such as ```haskell foreign import capi "cc018.h value f" f :: FunPtr (Int -> IO ()) ``` where ```c void (*f)(int); ``` See a related real-world use-case [here](https://gitlab.com/daniel-casanueva/pcre-light/-/merge_requests/17). There, GHC warns on import of C function pointer `pcre_free`. - - - - - ca99efaf by Alexey Radkov at 2024-01-30T19:41:53-05:00 Rename test cc018 -> T24034 - - - - - 88c38dd5 by Ben Gamari at 2024-01-30T19:42:28-05:00 rts/TraverseHeap.c: Ensure that PosixSource.h is included first - - - - - ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00 Make decomposeRuleLhs a bit more clever This fixes #24370 by making decomposeRuleLhs undertand dictionary /functions/ as well as plain /dictionaries/ - - - - - 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - 31553b11 by Ben Gamari at 2024-02-01T12:21:29-05:00 cmm: Introduce MO_RelaxedRead In hand-written Cmm it can sometimes be necessary to atomically load from memory deep within an expression (e.g. see the `CHECK_GC` macro). This MachOp provides a convenient way to do so without breaking the expression into multiple statements. - - - - - 0785cf81 by Ben Gamari at 2024-02-01T12:21:29-05:00 codeGen: Use relaxed accesses in ticky bumping - - - - - be423dda by Ben Gamari at 2024-02-01T12:21:29-05:00 base: use atomic write when updating timer manager - - - - - 8a310e35 by Ben Gamari at 2024-02-01T12:21:29-05:00 Use relaxed atomics to manipulate TSO status fields - - - - - d6809ee4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Add necessary barriers when manipulating TSO owner - - - - - 39e3ac5d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Use `switch` to branch on why_blocked This is a semantics-preserving refactoring. - - - - - 515eb33d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix synchronization on thread blocking state We now use a release barrier whenever we update a thread's blocking state. This required widening StgTSO.why_blocked as AArch64 does not support atomic writes on 16-bit values. - - - - - eb38812e by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadPaused This only affects an assertion in the debug RTS and only needs relaxed ordering. - - - - - 26c48dd6 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadStatus# - - - - - 6af43ab4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in Interpreter's preemption check - - - - - 9502ad3c by Ben Gamari at 2024-02-01T12:21:29-05:00 rts/Messages: Fix data race - - - - - 60802db5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts/Prof: Fix data race - - - - - ef8ccef5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use relaxed ordering on dirty/clean info tables updates When changing the dirty/clean state of a mutable object we needn't have any particular ordering. - - - - - 76fe2b75 by Ben Gamari at 2024-02-01T12:21:30-05:00 codeGen: Use relaxed-read in closureInfoPtr - - - - - a6316eb4 by Ben Gamari at 2024-02-01T12:21:30-05:00 STM: Use acquire loads when possible Full sequential consistency is not needed here. - - - - - 6bddfd3d by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use fence rather than redundant load Previously we would use an atomic load to ensure acquire ordering. However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this more directly. - - - - - 55c65dbc by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Fix data races in profiling timer - - - - - 856b5e75 by Ben Gamari at 2024-02-01T12:21:30-05:00 Add Note [C11 memory model] - - - - - 6534da24 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: move generic cmm optimization logic in NCG to a standalone module This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module, GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be run in the wasm backend NCG code, which is defined in other modules that's imported by GHC.CmmToAsm, causing a cyclic dependency issue. - - - - - 87e34888 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: explicitly disable PIC in wasm32 NCG This commit explicitly disables the ncgPIC flag for the wasm32 target. The wasm backend doesn't support PIC for the time being. - - - - - c6ce242e by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: enable generic cmm optimizations in wasm backend NCG This commit enables the generic cmm optimizations in other NCGs to be run in the wasm backend as well, followed by a late cmm control-flow optimization pass. The added optimizations do catch some corner cases not handled by the pre-NCG cmm pipeline and are useful in generating smaller CFGs. - - - - - 151dda4e by Andrei Borzenkov at 2024-02-01T12:22:43-05:00 Namespacing for WARNING/DEPRECATED pragmas (#24396) New syntax for WARNING and DEPRECATED pragmas was added, namely namespace specifierss: namespace_spec ::= 'type' | 'data' | {- empty -} warning ::= warning_category namespace_spec namelist strings deprecation ::= namespace_spec namelist strings A new data type was introduced to represent these namespace specifiers: data NamespaceSpecifier = NoSpecifier | TypeNamespaceSpecifier (EpToken "type") | DataNamespaceSpecifier (EpToken "data") Extension field XWarning now contains this NamespaceSpecifier. lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier and checks that the namespace of the found names matches the passed flag. With this change {-# WARNING data D "..." #-} pragma will only affect value namespace and {-# WARNING type D "..." #-} will only affect type namespace. The same logic is applicable to DEPRECATED pragmas. Finding duplicated warnings inside rnSrcWarnDecls now takes into consideration NamespaceSpecifier flag to allow warnings with the same names that refer to different namespaces. - - - - - 38c3afb6 by Bryan Richter at 2024-02-01T12:23:19-05:00 CI: Disable the test-cabal-reinstall job Fixes #24363 - - - - - 27020458 by Matthew Craven at 2024-02-03T01:53:26-05:00 Bump bytestring submodule to something closer to 0.12.1 ...mostly so that 16d6b7e835ffdcf9b894e79f933dd52348dedd0c (which reworks unaligned writes in Builder) and the stuff in https://github.com/haskell/bytestring/pull/631 can see wider testing. The less-terrible code for unaligned writes used in Builder on hosts not known to be ulaigned-friendly also takes less effort for GHC to compile, resulting in a metric decrease for T21839c on some platforms. The metric increase on T21839r is caused by the unrelated commit 750dac33465e7b59100698a330b44de7049a345c. It perhaps warrants further analysis and discussion (see #23822) but is not critical. Metric Decrease: T21839c Metric Increase: T21839r - - - - - cdddeb0f by Rodrigo Mesquita at 2024-02-03T01:54:02-05:00 Work around autotools setting C11 standard in CC/CXX In autoconf >=2.70, C11 is set by default for $CC and $CXX via the -std=...11 flag. In this patch, we split the "-std" flag out of the $CC and $CXX variables, which we traditionally assume to be just the executable name/path, and move it to $CFLAGS/$CXXFLAGS instead. Fixes #24324 - - - - - 5ff7cc26 by Apoorv Ingle at 2024-02-03T13:14:46-06:00 Expand `do` blocks right before typechecking using the `HsExpansion` philosophy. - Fixes #18324 #20020 #23147 #22788 #15598 #22086 #21206 - The change is detailed in - Note [Expanding HsDo with HsExpansion] in `GHC.Tc.Gen.Do` - Note [Doing HsExpansion in the Renamer vs Typechecker] in `GHC.Rename.Expr` expains the rational of doing expansions in type checker as opposed to in the renamer - Adds new datatypes: - `GHC.Hs.Expr.XXExprGhcRn`: new datatype makes this expansion work easier 1. Expansion bits for Expressions, Statements and Patterns in (`ExpandedThingRn`) 2. `PopErrCtxt` a special GhcRn Phase only artifcat to pop the previous error message in the error context stack - `GHC.Basic.Origin` now tracks the reason for expansion in case of Generated This is useful for type checking cf. `GHC.Tc.Gen.Expr.tcExpr` case for `HsLam` - Kills `HsExpansion` and `HsExpanded` as we have inlined them in `XXExprGhcRn` and `XXExprGhcTc` - Ensures warnings such as 1. Pattern match checks 2. Failable patterns 3. non-() return in body statements are preserved - Kill `HsMatchCtxt` in favor of `TcMatchAltChecker` - Testcases: * T18324 T20020 T23147 T22788 T15598 T22086 * T23147b (error message check), * DoubleMatch (match inside a match for pmc check) * pattern-fails (check pattern match with non-refutable pattern, eg. newtype) * Simple-rec (rec statements inside do statment) * T22788 (code snippet from #22788) * DoExpanion1 (Error messages for body statments) * DoExpansion2 (Error messages for bind statements) * DoExpansion3 (Error messages for let statements) Also repoint haddock to the right submodule so that the test (haddockHypsrcTest) pass Metric Increase 'compile_time/bytes allocated': T9020 The testcase is a pathalogical example of a `do`-block with many statements that do nothing. Given that we are expanding the statements into function binds, we will have to bear a (small) 2% cost upfront in the compiler to unroll the statements. - - - - - 0df8ce27 by Vladislav Zavialov at 2024-02-04T03:55:14-05:00 Reduce parser allocations in allocateCommentsP In the most common case, the comment queue is empty, so we can skip the work of processing it. This reduces allocations by about 10% in the parsing001 test. Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - cfd68290 by Simon Peyton Jones at 2024-02-05T17:58:33-05:00 Stop dropping a case whose binder is demanded This MR fixes #24251. See Note [Case-to-let for strictly-used binders] in GHC.Core.Opt.Simplify.Iteration, plus #24251, for lots of discussion. Final Nofib changes over 0.1%: +----------------------------------------- | imaginary/digits-of-e2 -2.16% | imaginary/rfib -0.15% | real/fluid -0.10% | real/gamteb -1.47% | real/gg -0.20% | real/maillist +0.19% | real/pic -0.23% | real/scs -0.43% | shootout/n-body -0.41% | shootout/spectral-norm -0.12% +======================================== | geom mean -0.05% Pleasingly, overall executable size is down by just over 1%. Compile times (in perf/compiler) wobble around a bit +/- 0.5%, but the geometric mean is -0.1% which seems good. - - - - - e4d137bb by Simon Peyton Jones at 2024-02-05T17:58:33-05:00 Add Note [Bangs in Integer functions] ...to document the bangs in the functions in GHC.Num.Integer - - - - - ce90f12f by Andrei Borzenkov at 2024-02-05T17:59:09-05:00 Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces (#24396) - - - - - e2ea933f by Simon Peyton Jones at 2024-02-06T10:12:04-05:00 Refactoring in preparation for lazy skolemisation * Make HsMatchContext and HsStmtContext be parameterised over the function name itself, rather than over the pass. See [mc_fun field of FunRhs] in Language.Haskell.Syntax.Expr - Replace types HsMatchContext GhcPs --> HsMatchContextPs HsMatchContext GhcRn --> HsMatchContextRn HsMatchContext GhcTc --> HsMatchContextRn (sic! not Tc) HsStmtContext GhcRn --> HsStmtContextRn - Kill off convertHsMatchCtxt * Split GHC.Tc.Type.BasicTypes.TcSigInfo so that TcCompleteSig (describing a complete user-supplied signature) is its own data type. - Split TcIdSigInfo(CompleteSig, PartialSig) into TcCompleteSig(CSig) TcPartialSig(PSig) - Use TcCompleteSig in tcPolyCheck, CheckGen - Rename types and data constructors: TcIdSigInfo --> TcIdSig TcPatSynInfo(TPSI) --> TcPatSynSig(PatSig) - Shuffle around helper functions: tcSigInfoName (moved to GHC.Tc.Types.BasicTypes) completeSigPolyId_maybe (moved to GHC.Tc.Types.BasicTypes) tcIdSigName (inlined and removed) tcIdSigLoc (introduced) - Rearrange the pattern match in chooseInferredQuantifiers * Rename functions and types: tcMatchesCase --> tcCaseMatches tcMatchesFun --> tcFunBindMatches tcMatchLambda --> tcLambdaMatches tcPats --> tcMatchPats matchActualFunTysRho --> matchActualFunTys matchActualFunTySigma --> matchActualFunTy * Add HasDebugCallStack constraints to: mkBigCoreVarTupTy, mkBigCoreTupTy, boxTy, mkPiTy, mkPiTys, splitAppTys, splitTyConAppNoView_maybe * Use `penv` from the outer context in the inner loop of GHC.Tc.Gen.Pat.tcMultiple * Move tcMkVisFunTy, tcMkInvisFunTy, tcMkScaledFunTys down the file, factor out and export tcMkScaledFunTy. * Move isPatSigCtxt down the file. * Formatting and comments Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com> - - - - - f5d3e03c by Andrei Borzenkov at 2024-02-06T10:12:04-05:00 Lazy skolemisation for @a-binders (#17594) This patch is a preparation for @a-binders implementation. The main changes are: * Skolemisation is now prepared to deal with @binders. See Note [Skolemisation overview] in GHC.Tc.Utils.Unify. Most of the action is in - Utils.Unify.matchExpectedFunTys - Gen.Pat.tcMatchPats - Gen.Expr.tcPolyExprCheck - Gen.Binds.tcPolyCheck Some accompanying refactoring: * I found that funTyConAppTy_maybe was doing a lot of allocation, and rejigged userTypeError_maybe to avoid calling it. - - - - - 532993c8 by Zubin Duggal at 2024-02-06T10:12:41-05:00 driver: Really don't lose track of nodes when we fail to resolve cycles This fixes a bug in 8db8d2fd1c881032b1b360c032b6d9d072c11723, where we could lose track of acyclic components at the start of an unresolved cycle. We now ensure we never loose track of any of these components. As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC: When viewed without boot files, we have a single SCC ``` [REC main:T24275B [main:T24275B {-# SOURCE #-}, main:T24275A {-# SOURCE #-}] main:T24275A [main:T24275A {-# SOURCE #-}]] ``` But with boot files this turns into ``` [NONREC main:T24275B {-# SOURCE #-} [], REC main:T24275B [main:T24275B {-# SOURCE #-}, main:T24275A {-# SOURCE #-}] main:T24275A {-# SOURCE #-} [main:T24275B], NONREC main:T24275A [main:T24275A {-# SOURCE #-}]] ``` Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot. However, we treat this entire group as a single "SCC" because it seems so when we analyse the graph without taking boot files into account. Indeed, we must return a single ResolvedCycle element in the BuildPlan for this as described in Note [Upsweep]. However, since after resolving this is not a true SCC anymore, `findCycle` fails to find a cycle and we have a sub-optimal error message as a result. To handle this, I extended `findCycle` to not assume its input is an SCC, and to try harder to find cycles in its input. Fixes #24275 - - - - - b35dd613 by Zubin Duggal at 2024-02-06T10:13:17-05:00 GHCi: Lookup breakpoint CCs in the correct module We need to look up breakpoint CCs in the module that the breakpoint points to, and not the current module. Fixes #24327 - - - - - b09e6958 by Zubin Duggal at 2024-02-06T10:13:17-05:00 testsuite: Add test for #24327 - - - - - 569b4c10 by doyougnu at 2024-02-07T03:06:26-05:00 ts: add compile_artifact, ignore_extension flag In b521354216f2821e00d75f088d74081d8b236810 the testsuite gained the capability to collect generic metrics. But this assumed that the test was not linking and producing artifacts and we only wanted to track object files, interface files, or build artifacts from the compiler build. However, some backends, such as the JS backend, produce artifacts when compiling, such as the jsexe directory which we want to track. This patch: - tweaks the testsuite to collect generic metrics on any build artifact in the test directory. - expands the exe_extension function to consider windows and adds the ignore_extension flag. - Modifies certain tests to add the ignore_extension flag. Tests such as heaprof002 expect a .ps file, but on windows without ignore_extensions the testsuite will look for foo.exe.ps. Hence the flag. - adds the size_hello_artifact test - - - - - 75a31379 by doyougnu at 2024-02-07T03:06:26-05:00 ts: add wasm_arch, heapprof002 wasm extension - - - - - c9731d6d by Rodrigo Mesquita at 2024-02-07T03:07:03-05:00 Synchronize bindist configure for #24324 In cdddeb0f1280b40cc194028bbaef36e127175c4c, we set up a workaround for #24324 in the in-tree configure script, but forgot to update the bindist configure script accordingly. This updates it. - - - - - d309f4e7 by Matthew Pickering at 2024-02-07T03:07:38-05:00 distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we were missing passing `--target` when invoking the linker. Fixes #24414 - - - - - 77db84ab by Ben Gamari at 2024-02-08T00:35:22-05:00 llvmGen: Adapt to allow use of new pass manager. We now must use `-passes` in place of `-O<n>` due to #21936. Closes #21936. - - - - - 3c9ddf97 by Matthew Pickering at 2024-02-08T00:35:59-05:00 testsuite: Mark length001 as fragile on javascript Modifying the timeout multiplier is not a robust way to get this test to reliably fail. Therefore we mark it as fragile until/if javascript ever supports the stack limit. - - - - - 20b702b5 by Matthew Pickering at 2024-02-08T00:35:59-05:00 Javascript: Don't filter out rtsDeps list This logic appears to be incorrect as it would drop any dependency which was not in a direct dependency of the package being linked. In the ghc-internals split this started to cause errors because `ghc-internal` is not a direct dependency of most packages, and hence important symbols to keep which are hard coded into the js runtime were getting dropped. - - - - - 2df96366 by Ben Gamari at 2024-02-08T00:35:59-05:00 base: Cleanup whitespace in cbits - - - - - 44f6557a by Ben Gamari at 2024-02-08T00:35:59-05:00 Move `base` to `ghc-internal` Here we move a good deal of the implementation of `base` into a new package, `ghc-internal` such that it can be evolved independently from the user-visible interfaces of `base`. While we want to isolate implementation from interfaces, naturally, we would like to avoid turning `base` into a mere set of module re-exports. However, this is a non-trivial undertaking for a variety of reasons: * `base` contains numerous known-key and wired-in things, requiring corresponding changes in the compiler * `base` contains a significant amount of C code and corresponding autoconf logic, which is very fragile and difficult to break apart * `base` has numerous import cycles, which are currently dealt with via carefully balanced `hs-boot` files * We must not break existing users To accomplish this migration, I tried the following approaches: * [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental migration of modules into ghc-internal: this knot is simply too intertwined to be easily pulled apart, especially given the rather tricky import cycles that it contains) * [Move-Core]: Moving the "core" connected component of base (roughly 150 modules) into ghc-internal. While the Haskell side of this seems tractable, the C dependencies are very subtle to break apart. * [Move-Incrementally]: 1. Move all of base into ghc-internal 2. Examine the module structure and begin moving obvious modules (e.g. leaves of the import graph) back into base 3. Examine the modules remaining in ghc-internal, refactor as necessary to facilitate further moves 4. Go to (2) iterate until the cost/benefit of further moves is insufficient to justify continuing 5. Rename the modules moved into ghc-internal to ensure that they don't overlap with those in base 6. For each module moved into ghc-internal, add a shim module to base with the declarations which should be exposed and any requisite Haddocks (thus guaranteeing that base will be insulated from changes in the export lists of modules in ghc-internal Here I am using the [Move-Incrementally] approach, which is empirically the least painful of the unpleasant options above Bumps haddock submodule. Metric Decrease: haddock.Cabal haddock.base Metric Increase: MultiComponentModulesRecomp T16875 size_hello_artifact - - - - - e8fb2451 by Vladislav Zavialov at 2024-02-08T00:36:36-05:00 Haddock comments on infix constructors (#24221) Rewrite the `HasHaddock` instance for `ConDecl GhcPs` to account for infix constructors. This change fixes a Haddock regression (introduced in 19e80b9af252) that affected leading comments on infix data constructor declarations: -- | Docs for infix constructor | Int :* Bool The comment should be associated with the data constructor (:*), not with its left-hand side Int. - - - - - 9060d55b by Ben Gamari at 2024-02-08T00:37:13-05:00 Add os-string as a boot package Introduces `os-string` submodule. This will be necessary for `filepath-1.5`. - - - - - 9d65235a by Ben Gamari at 2024-02-08T00:37:13-05:00 gitignore: Ignore .hadrian_ghci_multi/ - - - - - d7ee12ea by Ben Gamari at 2024-02-08T00:37:13-05:00 hadrian: Set -this-package-name When constructing the GHC flags for a package Hadrian must take care to set `-this-package-name` in addition to `-this-unit-id`. This hasn't broken until now as we have not had any uses of qualified package imports. However, this will change with `filepath-1.5` and the corresponding `unix` bump, breaking `hadrian/multi-ghci`. - - - - - f2dffd2e by Ben Gamari at 2024-02-08T00:37:13-05:00 Bump filepath to 1.5.0.0 Required bumps of the following submodules: * `directory` * `filepath` * `haskeline` * `process` * `unix` * `hsc2hs` * `Win32` * `semaphore-compat` and the addition of `os-string` as a boot package. - - - - - ab533e71 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Use specific clang assembler when compiling with -fllvm There are situations where LLVM will produce assembly which older gcc toolchains can't handle. For example on Deb10, it seems that LLVM >= 13 produces assembly which the default gcc doesn't support. A more robust solution in the long term is to require a specific LLVM compatible assembler when using -fllvm. Fixes #16354 - - - - - c32b6426 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Update CI images with LLVM 15, ghc-9.6.4 and cabal-install-3.10.2.0 - - - - - 5fcd58be by Matthew Pickering at 2024-02-08T00:37:50-05:00 Update bootstrap plans for 9.4.8 and 9.6.4 - - - - - 707a32f5 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Add alpine 3_18 release job This is mainly experimental and future proofing to enable a smooth transition to newer alpine releases once 3_12 is too old. - - - - - c37931b3 by John Ericson at 2024-02-08T06:39:05-05:00 Generate LLVM min/max bound policy via Hadrian Per #23966, I want the top-level configure to only generate configuration data for Hadrian, not do any "real" tasks on its own. This is part of that effort --- one less file generated by it. (It is still done with a `.in` file, so in a future world non-Hadrian also can easily create this file.) Split modules: - GHC.CmmToLlvm.Config - GHC.CmmToLlvm.Version - GHC.CmmToLlvm.Version.Bounds - GHC.CmmToLlvm.Version.Type This also means we can get rid of the silly `unused.h` introduced in !6803 / 7dfcab2f4bcb7206174ea48857df1883d05e97a2 as temporary kludge. Part of #23966 - - - - - 9f987235 by Apoorv Ingle at 2024-02-08T06:39:42-05:00 Enable mdo statements to use HsExpansions Fixes: #24411 Added test T24411 for regression - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 762b2120 by Jade at 2024-02-08T15:17:15+00:00 Improve Monad, Functor & Applicative docs This patch aims to improve the documentation of Functor, Applicative, Monad and related symbols. The main goal is to make it more consistent and make accessible. See also: !10979 (closed) and !10985 (closed) Ticket #17929 Updates haddock submodule - - - - - 151770ca by Josh Meredith at 2024-02-10T14:28:15-05:00 JavaScript codegen: Use GHC's tag inference where JS backend-specific evaluation inference was previously used (#24309) - - - - - 2e880635 by Zubin Duggal at 2024-02-10T14:28:51-05:00 ci: Allow release-hackage-lint to fail Otherwise it blocks the ghcup metadata pipeline from running. - - - - - b0293f78 by Matthew Pickering at 2024-02-10T14:29:28-05:00 rts: eras profiling mode The eras profiling mode is useful for tracking the life-time of closures. When a closure is written, the current era is recorded in the profiling header. This records the era in which the closure was created. * Enable with -he * User mode: Use functions ghc-experimental module GHC.Profiling.Eras to modify the era * Automatically: --automatic-era-increment, increases the user era on major collections * The first era is era 1 * -he<era> can be used with other profiling modes to select a specific era If you just want to record the era but not to perform heap profiling you can use `-he --no-automatic-heap-samples`. https://well-typed.com/blog/2024/01/ghc-eras-profiling/ Fixes #24332 - - - - - be674a2c by Jade at 2024-02-10T14:30:04-05:00 Adjust error message for trailing whitespace in as-pattern. Fixes #22524 - - - - - 53ef83f9 by doyougnu at 2024-02-10T14:30:47-05:00 gitlab: js: add codeowners Fixes: - #24409 Follow on from: - #21078 and MR !9133 - When we added the JS backend this was forgotten. This patch adds the rightful codeowners. - - - - - 8bbe12f2 by Matthew Pickering at 2024-02-10T14:31:23-05:00 Bump CI images so that alpine3_18 image includes clang15 The only changes here are that clang15 is now installed on the alpine-3_18 image. - - - - - df9fd9f7 by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: handle stored null StablePtr Some Haskell codes unsafely cast StablePtr into ptr to compare against NULL. E.g. in direct-sqlite: if castStablePtrToPtr aggStPtr /= nullPtr then where `aggStPtr` is read (`peek`) from zeroed memory initially. We fix this by giving these StablePtr the same representation as other null pointers. It's safe because StablePtr at offset 0 is unused (for this exact reason). - - - - - 55346ede by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: disable MergeObjsMode test This isn't implemented for JS backend objects. - - - - - aef587f6 by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: add support for linking C sources Support linking C sources with JS output of the JavaScript backend. See the added documentation in the users guide. The implementation simply extends the JS linker to use the objects (.o) that were already produced by the emcc compiler and which were filtered out previously. I've also added some options to control the link with C functions (see the documentation about pragmas). With this change I've successfully compiled the direct-sqlite package which embeds the sqlite.c database code. Some wrappers are still required (see the documentation about wrappers) but everything generic enough to be reused for other libraries have been integrated into rts/js/mem.js. - - - - - b71b392f by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: avoid EMCC logging spurious failure emcc would sometime output messages like: cache:INFO: generating system asset: symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json... (this will be cached in "/emsdk/upstream/emscripten/cache/symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json" for subsequent builds) cache:INFO: - ok Cf https://github.com/emscripten-core/emscripten/issues/18607 This breaks our tests matching the stderr output. We avoid this by setting EMCC_LOGGING=0 - - - - - ff2c0cc9 by Simon Peyton Jones at 2024-02-12T12:19:17-05:00 Remove a dead comment Just remove an out of date block of commented-out code, and tidy up the relevant Notes. See #8317. - - - - - bedb4f0d by Teo Camarasu at 2024-02-12T18:50:33-05:00 nonmoving: Add support for heap profiling Add support for heap profiling while using the nonmoving collector. We greatly simply the implementation by disabling concurrent collection for GCs when heap profiling is enabled. This entails that the marked objects on the nonmoving heap are exactly the live objects. Note that we match the behaviour for live bytes accounting by taking the size of objects on the nonmoving heap to be that of the segment's block rather than the object itself. Resolves #22221 - - - - - d0d5acb5 by Teo Camarasu at 2024-02-12T18:51:09-05:00 doc: Add requires prof annotation to options that require it Resolves #24421 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 57bb8c92 by Cheng Shao at 2024-02-13T14:07:49-05:00 deriveConstants: add needed constants for wasm backend This commit adds needed constants to deriveConstants. They are used by RTS code in the wasm backend to support the JSFFI logic. - - - - - 615eb855 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms The pure Haskell implementation causes i386 regression in unrelated work that can be fixed by using C-based atomic increment, see added comment for details. - - - - - a9918891 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: allow JSFFI for wasm32 This commit allows the javascript calling convention to be used when the target platform is wasm32. - - - - - 8771a53b by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: allow boxed JSVal as a foreign type This commit allows the boxed JSVal type to be used as a foreign argument/result type. - - - - - 053c92b3 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: ensure ctors have the right priority on wasm32 This commit fixes the priorities of ctors generated by GHC codegen on wasm32, see the referred note for details. - - - - - b7942e0a by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: add JSFFI desugar logic for wasm32 This commit adds JSFFI desugar logic for the wasm backend. - - - - - 2c1dca76 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: add JavaScriptFFI to supported extension list on wasm32 This commit adds JavaScriptFFI as a supported extension when the target platform is wasm32. - - - - - 9ad0e2b4 by Cheng Shao at 2024-02-13T14:07:49-05:00 rts/ghc-internal: add JSFFI support logic for wasm32 This commit adds rts/ghc-internal logic to support the wasm backend's JSFFI functionality. - - - - - e9ebea66 by Cheng Shao at 2024-02-13T14:07:49-05:00 ghc-internal: fix threadDelay for wasm in browsers This commit fixes broken threadDelay for wasm when it runs in browsers, see added note for detailed explanation. - - - - - f85f3fdb by Cheng Shao at 2024-02-13T14:07:49-05:00 utils: add JSFFI utility code This commit adds JavaScript util code to utils to support the wasm backend's JSFFI functionality: - jsffi/post-link.mjs, a post-linker to process the linked wasm module and emit a small complement JavaScript ESM module to be used with it at runtime - jsffi/prelude.js, a tiny bit of prelude code as the JavaScript side of runtime logic - jsffi/test-runner.mjs, run the jsffi test cases Co-authored-by: amesgen <amesgen at amesgen.de> - - - - - 77e91500 by Cheng Shao at 2024-02-13T14:07:49-05:00 hadrian: distribute jsbits needed for wasm backend's JSFFI support The post-linker.mjs/prelude.js files are now distributed in the bindist libdir, so when using the wasm backend's JSFFI feature, the user wouldn't need to fetch them from a ghc checkout manually. - - - - - c47ba1c3 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: add opts.target_wrapper This commit adds opts.target_wrapper which allows overriding the target wrapper on a per test case basis when testing a cross target. This is used when testing the wasm backend's JSFFI functionality; the rest of the cases are tested using wasmtime, though the jsffi cases are tested using the node.js based test runner. - - - - - 8e048675 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: T22774 should work for wasm JSFFI T22774 works since the wasm backend now supports the JSFFI feature. - - - - - 1d07f9a6 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: add JSFFI test cases for wasm backend This commit adds a few test cases for the wasm backend's JSFFI functionality, as well as a simple README to instruct future contributors to add new test cases. - - - - - b8997080 by Cheng Shao at 2024-02-13T14:07:49-05:00 docs: add documentation for wasm backend JSFFI This commit adds changelog and user facing documentation for the wasm backend's JSFFI feature. - - - - - ffeb000d by David Binder at 2024-02-13T14:08:30-05:00 Add tests from libraries/process/tests and libraries/Win32/tests to GHC These tests were previously part of the libraries, which themselves are submodules of the GHC repository. This commit moves the tests directly to the GHC repository. - - - - - 5a932cf2 by David Binder at 2024-02-13T14:08:30-05:00 Do not execute win32 tests on non-windows runners - - - - - 500d8cb8 by Jade at 2024-02-13T14:09:07-05:00 prevent GHCi (and runghc) from suggesting other symbols when not finding main Fixes: #23996 - - - - - b19ec331 by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: update xxHash to v0.8.2 - - - - - 4a97bdb8 by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: use XXH3_64bits hash on all 64-bit platforms This commit enables XXH3_64bits hash to be used on all 64-bit platforms. Previously it was only enabled on x86_64, so platforms like aarch64 silently falls back to using XXH32 which degrades the hashing function quality. - - - - - ee01de7d by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: define XXH_INLINE_ALL This commit cleans up how we include the xxhash.h header and only define XXH_INLINE_ALL, which is sufficient to inline the xxHash functions without symbol collision. - - - - - 0e01e1db by Alan Zimmerman at 2024-02-14T02:13:22-05:00 EPA: Move EpAnn out of extension points Leaving a few that are too tricky, maybe some other time. Also - remove some unneeded helpers from Parser.y - reduce allocations with strictness annotations Updates haddock submodule Metric Decrease: parsing001 - - - - - de589554 by Andreas Klebinger at 2024-02-14T02:13:59-05:00 Fix ffi callbacks with >6 args and non-64bit args. Check for ptr/int arguments rather than 64-bit width arguments when counting integer register arguments. The old approach broke when we stopped using exclusively W64-sized types to represent sub-word sized integers. Fixes #24314 - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 325b7613 by Ben Gamari at 2024-02-14T14:27:45-05:00 rts/EventLog: Place eliminate duplicate strlens Previously many of the `post*` implementations would first compute the length of the event's strings in order to determine the event length. Later we would then end up computing the length yet again in `postString`. Now we instead pass the string length to `postStringLen`, avoiding the repeated work. - - - - - 8aafa51c by Ben Gamari at 2024-02-14T14:27:46-05:00 rts/eventlog: Place upper bound on IPE string field lengths The strings in IPE events may be of unbounded length. Limit the lengths of these fields to 64k characters to ensure that we don't exceed the maximum event length. - - - - - 0e60d52c by Zubin Duggal at 2024-02-14T14:27:46-05:00 rts: drop unused postString function - - - - - d8d1333a by Cheng Shao at 2024-02-14T14:28:23-05:00 compiler/rts: fix wasm unreg regression This commit fixes two wasm unreg regressions caught by a nightly pipeline: - Unknown stg_scheduler_loopzh symbol when compiling scheduler.cmm - Invalid _hs_constructor(101) function name when handling ctor - - - - - 264a4fa9 by Owen Shepherd at 2024-02-15T09:41:06-05:00 feat: Add sortOn to Data.List.NonEmpty Adds `sortOn` to `Data.List.NonEmpty`, and adds comments describing when to use it, compared to `sortWith` or `sortBy . comparing`. The aim is to smooth out the API between `Data.List`, and `Data.List.NonEmpty`. This change has been discussed in the [clc issue](https://github.com/haskell/core-libraries-committee/issues/227). - - - - - b57200de by Fendor at 2024-02-15T09:41:47-05:00 Prefer RdrName over OccName for looking up locations in doc renaming step Looking up by OccName only does not take into account when functions are only imported in a qualified way. Fixes issue #24294 Bump haddock submodule to include regression test - - - - - 8ad02724 by Luite Stegeman at 2024-02-15T17:33:32-05:00 JS: add simple optimizer The simple optimizer reduces the size of the code generated by the JavaScript backend without the complexity and performance penalty of the optimizer in GHCJS. Also see #22736 Metric Decrease: libdir size_hello_artifact - - - - - 20769b36 by Matthew Pickering at 2024-02-15T17:34:07-05:00 base: Expose `--no-automatic-time-samples` in `GHC.RTS.Flags` API This patch builds on 5077416e12cf480fb2048928aa51fa4c8fc22cf1 and modifies the base API to reflect the new RTS flag. CLC proposal #243 - https://github.com/haskell/core-libraries-committee/issues/243 Fixes #24337 - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 08031ada by Teo Camarasu at 2024-02-16T13:37:00-05:00 base: export System.Mem.performBlockingMajorGC The corresponding C function was introduced in ba73a807edbb444c49e0cf21ab2ce89226a77f2e. As part of #22264. Resolves #24228 The CLC proposal was disccused at: https://github.com/haskell/core-libraries-committee/issues/230 Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 1f534c2e by Florian Weimer at 2024-02-16T13:37:42-05:00 Fix C output for modern C initiative GCC 14 on aarch64 rejects the C code written by GHC with this kind of error: error: assignment to ‘ffi_arg’ {aka ‘long unsigned int’} from ‘HsPtr’ {aka ‘void *’} makes integer from pointer without a cast [-Wint-conversion] 68 | *(ffi_arg*)resp = cret; | ^ Add the correct cast. For more information on this see: https://fedoraproject.org/wiki/Changes/PortingToModernC Tested-by: Richard W.M. Jones <rjones at redhat.com> - - - - - 5d3f7862 by Matthew Craven at 2024-02-16T13:38:18-05:00 Bump bytestring submodule to 0.12.1.0 - - - - - 902ebcc2 by Ian-Woo Kim at 2024-02-17T06:01:01-05:00 Add missing BCO handling in scavenge_one. - - - - - 97d26206 by Sylvain Henry at 2024-02-17T06:01:44-05:00 Make cast between words and floats real primops (#24331) First step towards fixing #24331. Replace foreign prim imports with real primops. - - - - - a40e4781 by Sylvain Henry at 2024-02-17T06:01:44-05:00 Perf: add constant folding for bitcast between float and word (#24331) - - - - - 5fd2c00f by Sylvain Henry at 2024-02-17T06:01:44-05:00 Perf: replace stack checks with assertions in casting primops There are RESERVED_STACK_WORDS free words (currently 21) on the stack, so omit the checks. Suggested by Cheng Shao. - - - - - 401dfe7b by Sylvain Henry at 2024-02-17T06:01:44-05:00 Reexport primops from GHC.Float + add deprecation - - - - - 4ab48edb by Ben Gamari at 2024-02-17T06:02:21-05:00 rts/Hash: Don't iterate over chunks if we don't need to free data When freeing a `HashTable` there is no reason to walk over the hash list before freeing it if the user has not given us a `dataFreeFun`. Noticed while looking at #24410. - - - - - bd5a1f91 by Cheng Shao at 2024-02-17T06:03:00-05:00 compiler: add SEQ_CST fence support In addition to existing Acquire/Release fences, this commit adds SEQ_CST fence support to GHC, allowing Cmm code to explicitly emit a fence that enforces total memory ordering. The following logic is added: - The MO_SeqCstFence callish MachOp - The %prim fence_seq_cst() Cmm syntax and the SEQ_CST_FENCE macro in Cmm.h - MO_SeqCstFence lowering logic in every single GHC codegen backend - - - - - 2ce2a493 by Cheng Shao at 2024-02-17T06:03:38-05:00 testsuite: fix hs_try_putmvar002 for targets without pthread.h hs_try_putmvar002 includes pthread.h and doesn't work on targets without this header (e.g. wasm32). It doesn't need to include this header at all. This was previously unnoticed by wasm CI, though recent toolchain upgrade brought in upstream changes that completely removes pthread.h in the single-threaded wasm32-wasi sysroot, therefore we need to handle that change. - - - - - 1fb3974e by Cheng Shao at 2024-02-17T06:03:38-05:00 ci: bump ci-images to use updated wasm image This commit bumps our ci-images revision to use updated wasm image. - - - - - 56e3f097 by Andrew Lelechenko at 2024-02-17T06:04:13-05:00 Bump submodule text to 2.1.1 T17123 allocates less because of improvements to Data.Text.concat in 1a6a06a. Metric Decrease: T17123 - - - - - a7569495 by Cheng Shao at 2024-02-17T06:04:51-05:00 rts: remove redundant rCCCS initialization This commit removes the redundant logic of initializing each Capability's rCCCS to CCS_SYSTEM in initProfiling(). Before initProfiling() is called during RTS startup, each Capability's rCCCS has already been assigned CCS_SYSTEM when they're first initialized. - - - - - 7a0293cc by Ben Gamari at 2024-02-19T07:11:00-05:00 Drop dependence on `touch` This drops GHC's dependence on the `touch` program, instead implementing it within GHC. This eliminates an external dependency and means that we have one fewer program to keep track of in the `configure` script - - - - - 0dbd729e by Andrei Borzenkov at 2024-02-19T07:11:37-05:00 Parser, renamer, type checker for @a-binders (#17594) GHC Proposal 448 introduces binders for invisible type arguments (@a-binders) in various contexts. This patch implements @-binders in lambda patterns and function equations: {-# LANGUAGE TypeAbstractions #-} id1 :: a -> a id1 @t x = x :: t -- @t-binder on the LHS of a function equation higherRank :: (forall a. (Num a, Bounded a) => a -> a) -> (Int8, Int16) higherRank f = (f 42, f 42) ex :: (Int8, Int16) ex = higherRank (\ @a x -> maxBound @a - x ) -- @a-binder in a lambda pattern in an argument -- to a higher-order function Syntax ------ To represent those @-binders in the AST, the list of patterns in Match now uses ArgPat instead of Pat: data Match p body = Match { ... - m_pats :: [LPat p], + m_pats :: [LArgPat p], ... } + data ArgPat pass + = VisPat (XVisPat pass) (LPat pass) + | InvisPat (XInvisPat pass) (HsTyPat (NoGhcTc pass)) + | XArgPat !(XXArgPat pass) The VisPat constructor represents patterns for visible arguments, which include ordinary value-level arguments and required type arguments (neither is prefixed with a @), while InvisPat represents invisible type arguments (prefixed with a @). Parser ------ In the grammar (Parser.y), the lambda and lambda-cases productions of aexp non-terminal were updated to accept argpats instead of apats: aexp : ... - | '\\' apats '->' exp + | '\\' argpats '->' exp ... - | '\\' 'lcases' altslist(apats) + | '\\' 'lcases' altslist(argpats) ... + argpat : apat + | PREFIX_AT atype Function left-hand sides did not require any changes to the grammar, as they were already parsed with productions capable of parsing @-binders. Those binders were being rejected in post-processing (isFunLhs), and now we accept them. In Parser.PostProcess, patterns are constructed with the help of PatBuilder, which is used as an intermediate data structure when disambiguating between FunBind and PatBind. In this patch we define ArgPatBuilder to accompany PatBuilder. ArgPatBuilder is a short-lived data structure produced in isFunLhs and consumed in checkFunBind. Renamer ------- Renaming of @-binders builds upon prior work on type patterns, implemented in 2afbddb0f24, which guarantees proper scoping and shadowing behavior of bound type variables. This patch merely defines rnLArgPatsAndThen to process a mix of visible and invisible patterns: + rnLArgPatsAndThen :: NameMaker -> [LArgPat GhcPs] -> CpsRn [LArgPat GhcRn] + rnLArgPatsAndThen mk = mapM (wrapSrcSpanCps rnArgPatAndThen) where + rnArgPatAndThen (VisPat x p) = ... rnLPatAndThen ... + rnArgPatAndThen (InvisPat _ tp) = ... rnHsTyPat ... Common logic between rnArgPats and rnPats is factored out into the rn_pats_general helper. Type checker ------------ Type-checking of @-binders builds upon prior work on lazy skolemisation, implemented in f5d3e03c56f. This patch extends tcMatchPats to handle @-binders. Now it takes and returns a list of LArgPat rather than LPat: tcMatchPats :: ... - -> [LPat GhcRn] + -> [LArgPat GhcRn] ... - -> TcM ([LPat GhcTc], a) + -> TcM ([LArgPat GhcTc], a) Invisible binders in the Match are matched up with invisible (Specified) foralls in the type. This is done with a new clause in the `loop` worker of tcMatchPats: loop :: [LArgPat GhcRn] -> [ExpPatType] -> TcM ([LArgPat GhcTc], a) loop (L l apat : pats) (ExpForAllPatTy (Bndr tv vis) : pat_tys) ... -- NEW CLAUSE: | InvisPat _ tp <- apat, isSpecifiedForAllTyFlag vis = ... In addition to that, tcMatchPats no longer discards type patterns. This is done by filterOutErasedPats in the desugarer instead. x86_64-linux-deb10-validate+debug_info Metric Increase: MultiLayerModulesTH_OneShot - - - - - 486979b0 by Jade at 2024-02-19T07:12:13-05:00 Add specialized sconcat implementation for Data.Monoid.First and Data.Semigroup.First Approved CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/246 Fixes: #24346 - - - - - 17e309d2 by John Ericson at 2024-02-19T07:12:49-05:00 Fix reST in users guide It appears that aef587f65de642142c1dcba0335a301711aab951 wasn't valid syntax. - - - - - 35b0ad90 by Brandon Chinn at 2024-02-19T07:13:25-05:00 Fix searching for errors in sphinx build - - - - - 4696b966 by Cheng Shao at 2024-02-19T07:14:02-05:00 hadrian: fix wasm backend post linker script permissions The post-link.mjs script was incorrectly copied and installed as a regular data file without executable permission, this commit fixes it. - - - - - a6142e0c by Cheng Shao at 2024-02-19T07:14:40-05:00 testsuite: mark T23540 as fragile on i386 See #24449 for details. - - - - - 249caf0d by Matthew Craven at 2024-02-19T20:36:09-05:00 Add @since annotation to Data.Data.mkConstrTag - - - - - cdd939e7 by Jade at 2024-02-19T20:36:46-05:00 Enhance documentation of Data.Complex - - - - - d04f384f by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian/bindist: Ensure that phony rules are marked as such Otherwise make may not run the rule if file with the same name as the rule happens to exist. - - - - - efcbad2d by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian: Generate HSC2HS_EXTRAS variable in bindist installation We must generate the hsc2hs wrapper at bindist installation time since it must contain `--lflag` and `--cflag` arguments which depend upon the installation path. The solution here is to substitute these variables in the configure script (see mk/hsc2hs.in). This is then copied over a dummy wrapper in the install rules. Fixes #24050. - - - - - c540559c by Matthew Pickering at 2024-02-21T04:59:23-05:00 ci: Show --info for installed compiler - - - - - ab9281a2 by Matthew Pickering at 2024-02-21T04:59:23-05:00 configure: Correctly set --target flag for linker opts Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4 arguments, when it only takes 3 arguments. Instead we need to use the `FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags. Actually fixes #24414 - - - - - 9460d504 by Rodrigo Mesquita at 2024-02-21T04:59:59-05:00 configure: Do not override existing linker flags in FP_LD_NO_FIXUP_CHAINS - - - - - 77629e76 by Andrei Borzenkov at 2024-02-21T05:00:35-05:00 Namespacing for fixity signatures (#14032) Namespace specifiers were added to syntax of fixity signatures: - sigdecl ::= infix prec ops | ... + sigdecl ::= infix prec namespace_spec ops | ... To preserve namespace during renaming MiniFixityEnv type now has separate FastStringEnv fields for names that should be on the term level and for name that should be on the type level. makeMiniFixityEnv function was changed to fill MiniFixityEnv in the right way: - signatures without namespace specifiers fill both fields - signatures with 'data' specifier fill data field only - signatures with 'type' specifier fill type field only Was added helper function lookupMiniFixityEnv that takes care about looking for a name in an appropriate namespace. Updates haddock submodule. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 84357d11 by Teo Camarasu at 2024-02-21T05:01:11-05:00 rts: only collect live words in nonmoving census when non-concurrent This avoids segfaults when the mutator modifies closures as we examine them. Resolves #24393 - - - - - 9ca56dd3 by Ian-Woo Kim at 2024-02-21T05:01:53-05:00 mutex wrap in refreshProfilingCCSs - - - - - 1387966a by Cheng Shao at 2024-02-21T05:02:32-05:00 rts: remove unused HAVE_C11_ATOMICS macro This commit removes the unused HAVE_C11_ATOMICS macro. We used to have a few places that have fallback paths when HAVE_C11_ATOMICS is not defined, but that is completely redundant, since the FP_CC_SUPPORTS__ATOMICS configure check will fail when the C compiler doesn't support C11 style atomics. There are also many places (e.g. in unreg backend, SMP.h, library cbits, etc) where we unconditionally use C11 style atomics anyway which work in even CentOS 7 (gcc 4.8), the oldest distro we test in our CI, so there's no value in keeping HAVE_C11_ATOMICS. - - - - - 0f40d68f by Andreas Klebinger at 2024-02-21T05:03:09-05:00 RTS: -Ds - make sure incall is non-zero before dereferencing it. Fixes #24445 - - - - - e5886de5 by Ben Gamari at 2024-02-21T05:03:44-05:00 rts/AdjustorPool: Use ExecPage abstraction This is just a minor cleanup I found while reviewing the implementation. - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 09941666 by Adam Gundry at 2024-02-21T13:53:12+00:00 Define GHC2024 language edition (#24320) See https://github.com/ghc-proposals/ghc-proposals/pull/613. Also fixes #24343 and improves the documentation of language editions. Co-authored-by: Joachim Breitner <mail at joachim-breitner.de> - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 5121a4ed by Ben Gamari at 2024-02-23T06:40:55-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. Bumps haddock submodule. - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 0eb2265d by Hécate Moonlight at 2024-02-24T16:02:16-05:00 Improve the synopsis and description of base - - - - - 2e36f5d2 by Jade at 2024-02-24T16:02:51-05:00 Error Messages: Properly align cyclic module error Fixes: #24476 - - - - - bbfb051c by Ben Gamari at 2024-02-24T19:10:23-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. - - - - - d8d6ad8c by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Move modules into GHC.Internal.* namespace Bumps haddock submodule due to testsuite output changes. - - - - - a82af7cd by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Rewrite `@since ` to `@since base-` These will be incrementally moved to the export sites in `base` where possible. - - - - - ca3836e1 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Migrate Haddock `not-home` pragmas from `ghc-internal` This ensures that we do not use `base` stub modules as declarations' homes when not appropriate. - - - - - c8cf3e26 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Partially freeze exports of GHC.Base Sadly there are still a few module reexports. However, at least we have decoupled from the exports of `GHC.Internal.Base`. - - - - - 272573c6 by Ben Gamari at 2024-02-24T19:10:23-05:00 Move Haddock named chunks - - - - - 2d8a881d by Ben Gamari at 2024-02-24T19:10:23-05:00 Drop GHC.Internal.Data.Int - - - - - 55c4c385 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler: Fix mention to `GHC....` modules in wasm desugaring Really, these references should be via known-key names anyways. I have fixed the proximate issue here but have opened #24472 to track the additional needed refactoring. - - - - - 64150911 by Ben Gamari at 2024-02-24T19:10:23-05:00 Accept performance shifts from ghc-internal restructure As expected, Haddock now does more work. Less expected is that some other testcases actually get faster, presumably due to less interface file loading. As well, the size_hello_artifact test regressed a bit when debug information is enabled due to debug information for the new stub symbols. Metric Decrease: T12227 T13056 Metric Increase: haddock.Cabal haddock.base MultiLayerModulesTH_OneShot size_hello_artifact - - - - - 317a915b by Ben Gamari at 2024-02-24T19:10:23-05:00 Expose GHC.Wasm.Prim from ghc-experimental Previously this was only exposed from `ghc-internal` which violates our agreement that users shall not rely on things exposed from that package. Fixes #24479. - - - - - 3bbd2bf2 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Small optimisation of evCallStack Don't lookupIds unless we actually need them. - - - - - 3e5c9e3c by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Use toException instead of SomeException - - - - - 125714a6 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Factor out errorBelch This was useful when debugging - - - - - 3d6aae7c by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Clean up imports of GHC.Stack.CloneStack - - - - - 6900306e by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move PrimMVar to GHC.Internal.MVar - - - - - 28f8a148 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move prettyCallStack to GHC.Internal.Stack - - - - - 4892de47 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Explicit dependency to workaround #24436 Currently `ghc -M` fails to account for `.hs-boot` files correctly, leading to issues with cross-package one-shot builds failing. This currently manifests in `GHC.Exception` due to the boot file for `GHC.Internal.Stack`. Work around this by adding an explicit `import`, ensuring that `GHC.Internal.Stack` is built before `GHC.Exception`. See #24436. - - - - - 294c93a5 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Use displayException in top-level exception handler Happily this also allows us to eliminate a special case for Deadlock exceptions. Implements [CLC #198](https://github.com/haskell/core-libraries-committee/issues/198). - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - cf756a25 by Ben Gamari at 2024-02-24T22:11:53-05:00 rts: Fix symbol references in Wasm RTS - - - - - 4e4d47a0 by Jade at 2024-02-26T15:17:20-05:00 GHCi: Improve response to unloading, loading and reloading modules Fixes #13869 - - - - - f3de8a3c by Zubin Duggal at 2024-02-26T15:17:57-05:00 rel-eng/fetch-gitlab.py: Fix name of aarch64 alpine 3_18 release job - - - - - c71bfdff by Cheng Shao at 2024-02-26T15:18:35-05:00 hadrian/hie-bios: pass -j to hadrian This commit passes -j to hadrian in the hadrian/hie-bios scripts. When the user starts HLS in a fresh clone that has just been configured, it takes quite a while for hie-bios to pick up the ghc flags and start actual indexing, due to the fact that the hadrian build step defaulted to -j1, so -j speeds things up and improve HLS user experience in GHC. Also add -j flag to .ghcid to speed up ghcid, and sets the Windows build root to .hie-bios which also works and unifies with other platforms, the previous build root _hie-bios was missing from .gitignore anyway. - - - - - 50bfdb46 by Cheng Shao at 2024-02-26T15:18:35-05:00 ci: enable parallelism in hadrian/ghci scripts This commit enables parallelism when the hadrian/ghci scripts are called in CI. The time bottleneck is in the hadrian build step, but previously the build step wasn't parallelized. - - - - - 61a78231 by Felix Yan at 2024-02-26T15:19:14-05:00 m4: Correctly detect GCC version When calling as `cc`, GCC does not outputs lowercased "gcc" at least in 13.2.1 version here. ``` $ cc --version cc (GCC) 13.2.1 20230801 ... ``` This fails the check and outputs the confusing message: `configure: $CC is not gcc; assuming it's a reasonably new C compiler` This patch makes it check for upper-cased "GCC" too so that it works correctly: ``` checking version of gcc... 13.2.1 ``` - - - - - 001aa539 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Fix formatting in whereFrom docstring Previously it used markdown syntax rather than Haddock syntax for code quotes - - - - - e8034d15 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Move ClosureType type to ghc-internal - Use ClosureType for InfoProv.ipDesc. - Use ClosureType for CloneStack.closureType. - Now ghc-heap re-exports this type from ghc-internal. See the accompanying CLC proposal: https://github.com/haskell/core-libraries-committee/issues/210 Resolves #22600 - - - - - 3da0a551 by Matthew Craven at 2024-02-27T13:27:22-05:00 StgToJS: Simplify ExprInline constructor of ExprResult Its payload was used only for a small optimization in genAlts, avoiding a few assignments for programs of this form: case NormalDataCon arg1 arg2 of x { NormalDataCon x1 x2 -> ... ; } But when compiling with optimizations, this sort of code is generally eliminated by case-of-known-constructor in Core-to-Core. So it doesn't seem worth tracking and cleaning up again in StgToJS. - - - - - 61bc92cc by Cheng Shao at 2024-02-27T16:58:42-05:00 rts: add missing ccs_mutex guard to internal_dlopen See added comment for details. Closes #24423. - - - - - dd29d3b2 by doyougnu at 2024-02-27T16:59:23-05:00 cg: Remove GHC.Cmm.DataFlow.Collections In pursuit of #15560 and #17957 and generally removing redundancy. - - - - - d3a050d2 by Cheng Shao at 2024-02-27T17:00:00-05:00 utils: remove unused lndir from tree Ever since the removal of the make build system, the in tree lndir hasn't been actually built, so this patch removes it. - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 74b24a9b by Teo Camarasu at 2024-02-28T16:32:58+00:00 rts: avoid checking bdescr of value outside of Haskell heap In nonmovingTidyWeaks we want to check if the key of a weak pointer lives in the non-moving heap. We do this by checking the flags of the block the key lives in. But we need to be careful with values that live outside the Haskell heap, since they will lack a block descriptor and looking for one may lead to a segfault. In this case we should just accept that it isn't on the non-moving heap. Resolves #24492 - - - - - b4cae4ec by Simon Peyton Jones at 2024-02-29T02:10:08-05:00 In mkDataConRep, ensure the in-scope set is right A small change that fixes #24489 - - - - - 3836a110 by Cheng Shao at 2024-02-29T21:25:45-05:00 testsuite: fix T23540 fragility on 32-bit platforms T23540 is fragile on 32-bit platforms. The root cause is usage of `getEvidenceTreesAtPoint`, which internally relies on `Name`'s `Ord` instance, which is indeterministic. The solution is adding a deterministic `Ord` instance for `EvidenceInfo` and sorting the evidence trees before pretty printing. Fixes #24449. - - - - - 960c8d47 by Teo Camarasu at 2024-02-29T21:26:20-05:00 Reduce AtomicModifyIORef increment count This test leads to a lot of contention when N>2 and becomes very slow. Let's reduce the amount of work we do to compensate. Resolves #24490 - - - - - 2e46c8ad by Matthew Pickering at 2024-03-01T05:48:06-05:00 hadrian: Improve parallelism in binary-dist-dir rule I noticed that the "docs" target was needed after the libraries and executables were built. We can improve the parallelism by needing everything at once so that documentation can be built immediately after a library is built for example. - - - - - cb6c11fe by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Bump windows and freebsd boot compilers to 9.6.4 We have previously bumped the docker images to use 9.6.4, but neglected to bump the windows images until now. - - - - - 30f06996 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: darwin: Update to 9.6.2 for boot compiler 9.6.4 is currently broken due to #24050 Also update to use LLVM-15 rather than LLVM-11, which is out of date. - - - - - d9d69e12 by Matthew Pickering at 2024-03-01T05:48:07-05:00 Bump minimum bootstrap version to 9.6 - - - - - 67ace1c5 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Enable more documentation building Here we enable documentation building on 1. Darwin: The sphinx toolchain was already installed so we enable html and manpages. 2. Rocky8: Full documentation (toolchain already installed) 3. Alpine: Full documetnation (toolchain already installed) 4. Windows: HTML and manpages (toolchain already installed) Fixes #24465 - - - - - 39583c39 by Matthew Pickering at 2024-03-01T05:48:42-05:00 ci: Bump ci-images to allow updated aarch64-alpine image with llvm15 and clang15 - - - - - d91d00fc by Torsten Schmits at 2024-03-01T15:01:50-05:00 Introduce ListTuplePuns extension This implements Proposal 0475, introducing the `ListTuplePuns` extension which is enabled by default. Disabling this extension makes it invalid to refer to list, tuple and sum type constructors by using built-in syntax like `[Int]`, `(Int, Int)`, `(# Int#, Int# #)` or `(# Int | Int #)`. Instead, this syntax exclusively denotes data constructors for use with `DataKinds`. The conventional way of referring to these data constructors by prefixing them with a single quote (`'(Int, Int)`) is now a parser error. Tuple declarations have been moved to `GHC.Tuple.Prim` and the `Solo` data constructor has been renamed to `MkSolo` (in a previous commit). Unboxed tuples and sums now have real source declarations in `GHC.Types`. Unit and solo types for tuples are now called `Unit`, `Unit#`, `Solo` and `Solo#`. Constraint tuples now have the unambiguous type constructors `CTuple<n>` as well as `CUnit` and `CSolo`, defined in `GHC.Classes` like before. A new parser construct has been added for the unboxed sum data constructor declarations. The type families `Tuple`, `Sum#` etc. that were intended to provide nicer syntax have been omitted from this change set due to inference problems, to be implemented at a later time. See the MR discussion for more info. Updates the submodule utils/haddock. Updates the cabal submodule due to new language extension. Metric Increase: haddock.base Metric Decrease: MultiLayerModulesTH_OneShot size_hello_artifact Proposal document: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst Merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8820 Tracking ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/21294 - - - - - bbdb6286 by Sylvain Henry at 2024-03-01T15:01:50-05:00 JS linker: filter unboxed tuples - - - - - dec6d8d3 by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Improve error messages coming from non-linear patterns This enriched the `CtOrigin` for non-linear patterns to include data of the pattern that created the constraint (which can be quite useful if it occurs nested in a pattern) as well as an explanation why the pattern is non-restricted in (at least in some cases). - - - - - 6612388e by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Adjust documentation of linear lets according to committee decision - - - - - 1c064ef1 by Cheng Shao at 2024-03-02T17:11:19-05:00 compiler: start deprecating cmmToRawCmmHook cmmToRawCmmHook was added 4 years ago in d561c8f6244f8280a2483e8753c38e39d34c1f01. Its only user is the Asterius project, which has been archived and deprecated in favor of the ghc wasm backend. This patch starts deprecating cmmToRawCmmHook by placing a DEPRECATED pragma, and actual removal shall happen in a future GHC major release if no issue to oppose the deprecation has been raised in the meantime. - - - - - 9b74845f by Andrew Lelechenko at 2024-03-02T17:11:55-05:00 Data.List.NonEmpty.unzip: use WARNING with category instead of DEPRECATED CLC proposal: https://github.com/haskell/core-libraries-committee/issues/258 - - - - - 61bb5ff6 by Finley McIlwaine at 2024-03-04T09:01:40-08:00 add -fprof-late-overloaded and -fprof-late-overloaded-calls * Refactor late cost centre insertion for extensibility * Add two more late cost centre insertion methods that add SCCs to overloaded top level bindings and call sites with dictionary arguments. * Some tests for the basic functionality of the new insertion methods Resolves: #24500 - - - - - 82ccb801 by Andreas Klebinger at 2024-03-04T19:59:14-05:00 x86-ncg: Fix fma codegen when arguments are globals Fix a bug in the x86 ncg where results would be wrong when the desired output register and one of the input registers were the same global. Also adds a tiny optimization to make use of the memory addressing support when convenient. Fixes #24496 - - - - - 18ad1077 by Matthew Pickering at 2024-03-05T14:22:31-05:00 rel_eng: Update hackage docs upload scripts This adds the upload of ghc-internal and ghc-experimental to our scripts which upload packages to hackage. - - - - - bf47c9ba by Matthew Pickering at 2024-03-05T14:22:31-05:00 docs: Remove stray module comment from GHC.Profiling.Eras - - - - - 37d9b340 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix ghc-internal cabal file The file mentioned some artifacts relating to the base library. I have renamed these to the new ghc-internal variants. - - - - - 23f2a478 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix haddock source links and hyperlinked source There were a few issues with the hackage links: 1. We were using the package id rather than the package name for the package links. This is fixed by now allowing the template to mention %pkg% or %pkgid% and substituing both appropiatly. 2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage` as the new base link works on a local or remote hackage server. 3. The "src" path including too much stuff, so cross-package source links were broken as the template was getting double expanded. Fixes #24086 - - - - - 2fa336a9 by Ben Gamari at 2024-03-05T14:23:07-05:00 filepath: Bump submodule to 1.5.2.0 - - - - - 31217944 by Ben Gamari at 2024-03-05T14:23:07-05:00 os-string: Bump submodule to 2.0.2 - - - - - 4074a3f2 by Matthew Pickering at 2024-03-05T21:44:35-05:00 base: Reflect new era profiling RTS flags in GHC.RTS.Flags * -he profiling mode * -he profiling selector * --automatic-era-increment CLC proposal #254 - https://github.com/haskell/core-libraries-committee/issues/254 - - - - - a8c0e31b by Sylvain Henry at 2024-03-05T21:45:14-05:00 JS: faster implementation for some numeric primitives (#23597) Use faster implementations for the following primitives in the JS backend by not using JavaScript's BigInt: - plusInt64 - minusInt64 - minusWord64 - timesWord64 - timesInt64 Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com> - - - - - 21e3f325 by Cheng Shao at 2024-03-05T21:45:52-05:00 rts: add -xr option to control two step allocator reserved space size This patch adds a -xr RTS option to control the size of virtual memory address space reserved by the two step allocator on a 64-bit platform, see added documentation for explanation. Closes #24498. - - - - - dedcf102 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: expose HeapAlloc.h as public header This commit exposes HeapAlloc.h as a public header. The intention is to expose HEAP_ALLOCED/HEAP_ALLOCED_GC, so they can be used in assertions in other public headers, and they may also be useful for user code. - - - - - d19441d7 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: assert pointer is indeed heap allocated in Bdescr() This commit adds an assertion to Bdescr() to assert the pointer is indeed heap allocated. This is useful to rule out RTS bugs that attempt to access non-existent block descriptor of a static closure, #24492 being one such example. - - - - - 9a656a04 by Ben Gamari at 2024-03-06T13:39:39-05:00 ghc-experimental: Add dummy dependencies to work around #23942 This is a temporary measure to improve CI reliability until a proper solution is developed. Works around #23942. - - - - - 1e84b924 by Simon Peyton Jones at 2024-03-06T13:39:39-05:00 Three compile perf improvements with deep nesting These were changes are all triggered by #24471. 1. Make GHC.Core.Opt.SetLevels.lvlMFE behave better when there are many free variables. See Note [Large free-variable sets]. 2. Make GHC.Core.Opt.Arity.floatIn a bit lazier in its Cost argument. This benefits the common case where the ArityType turns out to be nullary. See Note [Care with nested expressions] 3. Make GHC.CoreToStg.Prep.cpeArg behave for deeply-nested expressions. See Note [Eta expansion of arguments in CorePrep] wrinkle (EA2). Compile times go down by up to 4.5%, and much more in artificial cases. (Geo mean of compiler/perf changes is -0.4%.) Metric Decrease: CoOpt_Read T10421 T12425 - - - - - c4b13113 by Hécate Moonlight at 2024-03-06T13:40:17-05:00 Use "module" instead of "library" when applicable in base haddocks - - - - - 9cd9efb4 by Vladislav Zavialov at 2024-03-07T13:01:54+03:00 Rephrase error message to say "visible arguments" (#24318) * Main change: make the error message generated by mkFunTysMsg more accurate by changing "value arguments" to "visible arguments". * Refactor: define a new type synonym VisArity and use it instead of Arity in a few places. It might be the case that there other places in the compiler that should talk about visible arguments rather than value arguments, but I haven't tried to find them all, focusing only on the error message reported in the ticket. - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - d523a6a7 by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump array submodule - - - - - 7e55003c by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump stm submodule - - - - - 32d337ef by Ben Gamari at 2024-03-07T19:40:45-05:00 Introduce exception context Here we introduce the `ExceptionContext` type and `ExceptionAnnotation` class, allowing dynamically-typed user-defined annotations to be attached to exceptions. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 - - - - - 39f3d922 by Ben Gamari at 2024-03-07T19:40:46-05:00 testsuite/interface-stability: Update documentation - - - - - fdea7ada by Ben Gamari at 2024-03-07T19:40:46-05:00 ghc-internal: comment formatting - - - - - 4fba42ef by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Default and warn ExceptionContext constraints - - - - - 3886a205 by Ben Gamari at 2024-03-07T19:40:46-05:00 base: Introduce exception backtraces Here we introduce the `Backtraces` type and associated machinery for attaching these via `ExceptionContext`. These has a few compile-time regressions (`T15703` and `T9872d`) due to the additional dependencies in the exception machinery. As well, there is a surprisingly large regression in the `size_hello_artifact` test. This appears to be due to various `Integer` and `Read` bits now being reachable at link-time. I believe it should be possible to avoid this but I have accepted the change for now to get the feature merged. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 Metric Increase: T15703 T9872d size_hello_artifact - - - - - 18c5409f by Ben Gamari at 2024-03-07T19:40:46-05:00 users guide: Release notes for exception backtrace work - - - - - f849c5fc by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Don't show ExceptionContext of GhcExceptions Most GhcExceptions are user-facing errors and therefore the ExceptionContext has little value. Ideally we would enable it in the DEBUG compiler but I am leaving this for future work. - - - - - dc646e6f by Sylvain Henry at 2024-03-07T19:40:46-05:00 Disable T9930fail for the JS target (cf #19174) - - - - - bfc09760 by Alan Zimmerman at 2024-03-07T19:41:22-05:00 Update showAstData to honour blanking of AnnParen Also tweak rendering of SrcSpan to remove extra blank line. - - - - - 50454a29 by Ben Gamari at 2024-03-08T03:32:42-05:00 ghc-internal: Eliminate GHC.Internal.Data.Kind This was simply reexporting things from `ghc-prim`. Instead reexport these directly from `Data.Kind`. Also add build ordering dependency to work around #23942. - - - - - 38a4b6ab by Ben Gamari at 2024-03-08T03:33:18-05:00 rts: Fix SET_HDR initialization of retainer set This fixes a regression in retainer set profiling introduced by b0293f78cb6acf2540389e22bdda420d0ab874da. Prior to that commit the heap traversal word would be initialized by `SET_HDR` using `LDV_RECORD_CREATE`. However, the commit added a `doingLDVProfiling` check in `LDV_RECORD_CREATE`, meaning that this initialization no longer happened. Given that this initialization was awkwardly indirectly anyways, I have fixed this by explicitly initializating the heap traversal word to `NULL` in `SET_PROF_HDR`. This is equivalent to the previous behavior, but much more direct. Fixes #24513. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00 base: Use strerror_r instead of strerror As noted by #24344, `strerror` is not necessarily thread-safe. Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is safe to use. Fixes #24344. CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - edb9bf77 by Jade at 2024-03-09T03:39:38-05:00 Error messages: Improve Error messages for Data constructors in type signatures. This patch improves the error messages from invalid type signatures by trying to guess what the user did and suggesting an appropriate fix. Partially fixes: #17879 - - - - - cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00 HieAst: add module name #24493 The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst. It should fix #24493. The following have been done: 1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))` To store the located module name information. 2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information. 3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests. 4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53 - - - - - 2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00 GHC.Utils.Binary: fix a couple of typos - - - - - 5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00 rts: Drop .wasm suffix from .prof file names This replicates the behavior on Windows, where `Hi.exe` will produce profiling output named `Hi.prof` instead of `Hi.exe.prof`. While in the area I also fixed the extension-stripping logic, which incorrectly rewrote `Hi.exefoo` to `Hi.foo`. Closes #24515. - - - - - 259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00 testsuite: drop exe extension from .hp & .prof filenames See #24515 for details. - - - - - c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00 rts/linker: Enable GOT support on all platforms There is nothing platform-dependent about our GOT implementation and GOT support is needed by `T24171` on i386. - - - - - 2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00 Drop outdated comment on TcRnIllformedTypePattern This should have been done in 0f0c53a501b but I missed it. - - - - - c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Bounds check array write - - - - - 15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Don't expose helper functions in header - - - - - e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00 base: Move internals of GHC.InfoProv into GHC.InfoProv.Types Such that we can add new helpers into GHC.InfoProv.Types without breakage. - - - - - 6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00 rts: Lazily decode IPE tables Previously we would eagerly allocate `InfoTableEnt`s for each info table registered in the info table provenance map. However, this costs considerable memory and initialization time. Instead we now lazily decode these tables. This allows us to use one-third the memory *and* opens the door to taking advantage of sharing opportunities within a module. This required considerable reworking since lookupIPE now must be passed its result buffer. - - - - - 9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Don't expose helper in header - - - - - 308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Share module_name within a Node This allows us to shave a 64-bit word off of the packed IPE entry size. - - - - - bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00 IPE: Expose unit ID in InfoTableProv Here we add the unit ID to the info table provenance structure. - - - - - 6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00 rts: Refactor GHC.Stack.CloneStack.decode Don't allocate a Ptr constructor per frame. - - - - - ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00 base: Do not expose whereFrom# from GHC.Exts - - - - - 2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00 docs: Update info on TypeAbstractions * Mention TypeAbstractions in 9.10.1-notes.rst * Set the status to "Experimental". * Add a "Since: GHC 9.x" comment to each section. - - - - - f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00 ci-images: Bump Alpine image to bootstrap with 9.8.2 - - - - - 705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark T24171 as fragile due to #24512 I will fix this but not in time for 9.10.1-alpha1 - - - - - c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark linker_unload_native as fragile In particular this fails on platforms without `dlinfo`. I plan to address this but not before 9.10.1-alpha1. - - - - - f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00 configure: Bump version to 9.10 - - - - - 88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00 Bump transformers submodule to 0.6.1.1 - - - - - 8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Increase ulimit for T18623 1 MByte was just too tight and failed intermittently on some platforms (e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient headroom. Fixes #23139. - - - - - c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00 base: Bump version to 4.20.0.0 - - - - - b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-internal: Set initial version at 9.1001.0 This provides PVP compliance while maintaining a clear correspondence between GHC releases and `ghc-internal` versions. - - - - - 4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-prim: Bump version to 0.11.0 - - - - - 50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00 template-haskell: Bump version to 2.22.0.0 - - - - - 8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00 base-exports: Accommodate spurious whitespace changes in 32-bit output It appears that this was - - - - - 9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00 users-guide: Move exception backtrace relnotes to 9.10 This was previously mistakenly added to the GHC 9.8 release notes. - - - - - 145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix name of Rocky8 artifact - - - - - 39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix path of generate_jobs_metadata - - - - - aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/upload: Rework recompression The old `combine` approach was quite fragile due to use of filename globbing. Moreover, it didn't parallelize well. This refactoring makes the goal more obvious, parallelizes better, and is more robust. - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00 configure: Bump GHC version to 9.11 Bumps haddock submodule. - - - - - 8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload code when profiling is enabled The heap census may contain references (e.g. `Counter.identity`) to static data which must be available when the census is reported at the end of execution. Fixes #24512. - - - - - 7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload native objects when dlinfo isn't available To do so is unsafe as we have no way of identifying references to symbols provided by the object. Fixes #24513. Fixes #23993. - - - - - 0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00 rel_eng/upload: Purge both $rel_name/ and $ver/ This is necessary for prereleases, where GHCup accesses the release via `$ver/` - - - - - b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Remove duplicate code normalising slashes - - - - - c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Simplify regexes with raw strings - - - - - 1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00 Don't normalize backslashes in characters - - - - - 7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00 Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470) - - - - - 39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00 Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms" This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was originally intended to fix #24449, but it was merely sweeping the bug under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly fixed the fragile test, and we no longer need the C version of genSym. Furthermore, the C implementation causes trouble when compiling with clang that targets i386 due to alignment warning and libatomic linking issue, so it makes sense to revert it. - - - - - e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00 compiler: fix out-of-bound memory access of genSym on 32-bit This commit fixes an unnoticed out-of-bound memory access of genSym on 32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms, but we mistakenly treat it as a Word64 pointer in genSym, and therefore will accidentally load 2 garbage higher bytes, or with a small but non-zero chance, overwrite something else in the data section depends on how the linker places the data segments. This regression was introduced in !11802 and fixed here. - - - - - 77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00 Note mutability of array and address access primops Without an understanding of immutable vs. mutable memory, the index primop family have a potentially non-intuitive type signature: indexOffAddr :: Addr# -> Int# -> a readOffAddr :: Addr# -> Int# -> State# d -> (# State# d, a #) indexOffAddr# might seem like a free generality improvement, which it certainly is not! This change adds a brief note on mutability expectations for most index/read/write access primops. - - - - - 7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00 EPA: Fix regression discarding comments in contexts Closes #24533 - - - - - 73be65ab by Fendor at 2024-03-19T01:42:53-04:00 Fix sharing of 'IfaceTyConInfo' during core to iface type translation During heap analysis, we noticed that during generation of 'mi_extra_decls' we have lots of duplicates for the instances: * `IfaceTyConInfo NotPromoted IfaceNormalTyCon` * `IfaceTyConInfo IsPromoted IfaceNormalTyCon` which should be shared instead of duplicated. This duplication increased the number of live bytes by around 200MB while loading the agda codebase into GHCi. These instances are created during `CoreToIface` translation, in particular `toIfaceTyCon`. The generated core looks like: toIfaceTyCon = \ tc_sjJw -> case $wtoIfaceTyCon tc_sjJw of { (# ww_sjJz, ww1_sjNL, ww2_sjNM #) -> IfaceTyCon ww_sjJz (IfaceTyConInfo ww1_sjNL ww2_sjNM) } whichs removes causes the sharing to work propery. Adding explicit sharing, with NOINLINE annotations, changes the core to: toIfaceTyCon = \ tc_sjJq -> case $wtoIfaceTyCon tc_sjJq of { (# ww_sjNB, ww1_sjNC #) -> IfaceTyCon ww_sjNB ww1_sjNC } which looks much more like sharing is happening. We confirmed via ghc-debug that all duplications were eliminated and the number of live bytes are noticeably reduced. - - - - - bd8209eb by Alan Zimmerman at 2024-03-19T01:43:28-04:00 EPA: Address more 9.10.1-alpha1 regressions from recent changes Closes #24533 Hopefully for good this time - - - - - 31bf85ee by Fendor at 2024-03-19T14:48:08-04:00 Escape multiple arguments in the settings file Uses responseFile syntax. The issue arises when GHC is installed on windows into a location that has a space, for example the user name is 'Fake User'. The $topdir will also contain a space, consequentially. When we resolve the top dir in the string `-I$topdir/mingw/include`, then `words` will turn this single argument into `-I/C/Users/Fake` and `User/.../mingw/include` which trips up the flag argument parser of various tools such as gcc or clang. We avoid this by escaping the $topdir before replacing it in `initSettngs`. Additionally, we allow to escape spaces and quotation marks for arguments in `settings` file. Add regression test case to count the number of options after variable expansion and argument escaping took place. Additionally, we check that escaped spaces and double quotation marks are correctly parsed. - - - - - f45f700e by Matthew Pickering at 2024-03-19T14:48:44-04:00 Read global package database from settings file Before this patch, the global package database was always assumed to be in libdir </> package.conf.d. This causes issues in GHC's build system because there are sometimes situations where the package database you need to use is not located in the same place as the settings file. * The stage1 compiler needs to use stage1 libraries, so we should set "Global Package DB" for the stage1 compiler to the stage1 package database. * Stage 2 cross compilers need to use stage2 libraries, so likewise, we should set the package database path to `_build/stage2/lib/` * The normal situation is where the stage2 compiler uses stage1 libraries. Then everything lines up. * When installing we have rearranged everything so that the settings file and package database line up properly, so then everything should continue to work as before. In this case we set the relative package db path to `package.conf.d`, so it resolves the same as before. * ghc-pkg needs to be modified as well to look in the settings file fo the package database rather than assuming the global package database location relative to the lib folder. * Cabal/cabal-install will work correctly because they query the global package database using `--print-global-package-db`. A reasonable question is why not generate the "right" settings files in the right places in GHC's build system. In order to do this you would need to engineer wrappers for all executables to point to a specific libdir. There are also situations where the same package db is used by two different compilers with two different settings files (think stage2 cross compiler and stage3 compiler). In short, this 10 line patch allows for some reasonable simplifications in Hadrian at very little cost to anything else. Fixes #24502 - - - - - 4c8f1794 by Matthew Pickering at 2024-03-19T14:48:44-04:00 hadrian: Remove stage1 testsuite wrappers logic Now instead of producing wrappers which pass the global package database argument to ghc and ghc-pkg, we write the location of the correct package database into the settings file so you can just use the intree compiler directly. - - - - - da0d8ba5 by Matthew Craven at 2024-03-19T14:49:20-04:00 Remove unused ghc-internal module "GHC.Internal.Constants" - - - - - b56d2761 by Matthew Craven at 2024-03-19T14:49:20-04:00 CorePrep: Rework lowering of BigNat# literals Don't use bigNatFromWord#, because that's terrible: * We shouldn't have to traverse a linked list at run-time to build a BigNat# literal. That's just silly! * The static List object we have to create is much larger than the actual BigNat#'s contents, bloating code size. * We have to read the corresponding interface file, which causes un-tracked implicit dependencies. (#23942) Instead, encode them into the appropriate platform-dependent sequence of bytes, and generate code that copies these bytes at run-time from an Addr# literal into a new ByteArray#. A ByteArray# literal would be the correct thing to generate, but these are not yet supported; see also #17747. Somewhat surprisingly, this change results in a slight reduction in compiler allocations, averaging around 0.5% on ghc's compiler performance tests, including when compiling programs that contain no bignum literals to begin with. The specific cause of this has not been investigated. Since this lowering no longer reads the interface file for GHC.Num.BigNat, the reasoning in Note [Depend on GHC.Num.Integer] is obsoleted. But the story of un-tracked built-in dependencies remains complex, and Note [Tracking dependencies on primitives] now exists to explain this complexity. Additionally, many empty imports have been modified to refer to this new note and comply with its guidance. Several empty imports necessary for other reasons have also been given brief explanations. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 349ea330 by Fendor at 2024-03-19T14:50:00-04:00 Eliminate thunk in 'IfaceTyCon' Heap analysis showed that `IfaceTyCon` retains a thunk to `IfaceTyConInfo`, defeating the sharing of the most common instances of `IfaceTyConInfo`. We make sure the indirection is removed by adding bang patterns to `IfaceTyCon`. Experimental results on the agda code base, where the `mi_extra_decls` were read from disk: Before this change, we observe around 8654045 instances of: `IfaceTyCon[Name,THUNK_1_0]` But these thunks almost exclusively point to a shared value! Forcing the thunk a little bit more, leads to `ghc-debug` reporting: `IfaceTyCon[Name:Name,IfaceTyConInfo]` and a noticeable reduction of live bytes (on agda ~10%). - - - - - 594bee0b by Krzysztof Gogolewski at 2024-03-19T14:50:36-04:00 Minor misc cleanups - GHC.HsToCore.Foreign.JavaScript: remove dropRuntimeRepArgs; boxed tuples don't take RuntimeRep args - GHC.HsToCore.Foreign.Call: avoid partial pattern matching - GHC.Stg.Unarise: strengthen the assertion; we can assert that non-rubbish literals are unary rather than just non-void - GHC.Tc.Gen.HsType: make sure the fsLit "literal" rule fires - users_guide/using-warnings.rst: remove -Wforall-identifier, now deprecated and does nothing - users_guide/using.rst: fix formatting - andy_cherry/test.T: remove expect_broken_for(23272...), 23272 is fixed The rest are simple cleanups. - - - - - cf55a54b by Ben Gamari at 2024-03-19T14:51:12-04:00 mk/relpath: Fix quoting Previously there were two instances in this script which lacked proper quoting. This resulted in `relpath` invocations in the binary distribution Makefile producing incorrect results on Windows, leading to confusing failures from `sed` and the production of empty package registrations. Fixes #24538. - - - - - 5ff88389 by Bryan Richter at 2024-03-19T14:51:48-04:00 testsuite: Disable T21336a on wasm - - - - - 60023351 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian/bindist: Eliminate extraneous `dirname` invocation Previously we would call `dirname` twice per installed library file. We now instead reuse this result. This helps appreciably on Windows, where processes are quite expensive. - - - - - 616ac300 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian: Package mingw toolchain in expected location This fixes #24525, a regression due to 41cbaf44a6ab5eb9fa676d65d32df8377898dc89. Specifically, GHC expects to find the mingw32 toolchain in the binary distribution root. However, after this patch it was packaged in the `lib/` directory. - - - - - de9daade by Ben Gamari at 2024-03-19T22:33:11-04:00 gitlab/rel_eng: More upload.sh tweaks - - - - - 1dfe12db by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_eng: Drop dead prepare_docs codepath - - - - - dd2d748b by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_env/recompress_all: unxz before recompressing Previously we would rather compress the xz *again*, before in addition compressing it with the desired scheme. Fixes #24545. - - - - - 9d936c57 by Ben Gamari at 2024-03-19T22:33:11-04:00 mk-ghcup-metadata: Fix directory of testsuite tarball As reported in #24546, the `dlTest` artifact should be extracted into the `testsuite` directory. - - - - - 6d398066 by Ben Gamari at 2024-03-19T22:33:11-04:00 ghcup-metadata: Don't populate dlOutput unless necessary ghcup can apparently infer the output name of an artifact from its URL. Consequently, we should only include the `dlOutput` field when it would differ from the filename of `dlUri`. Fixes #24547. - - - - - 576f8b7e by Zubin Duggal at 2024-03-19T22:33:46-04:00 Revert "Apply shellcheck suggestion to SUBST_TOOLDIR" This reverts commit c82770f57977a2b5add6e1378f234f8dd6153392. The shellcheck suggestion is spurious and results in SUBST_TOOLDIR being a no-op. `set` sets positional arguments for bash, but we want to set the variable given as the first autoconf argument. Fixes #24542 Metric decreases because the paths in the settings file are now shorter, so we allocate less when we read the settings file. ------------------------- Metric Decrease: T12425 T13035 T9198 ------------------------- - - - - - cdfe6e01 by Fendor at 2024-03-19T22:34:22-04:00 Compact serialisation of IfaceAppArgs In #24563, we identified that IfaceAppArgs serialisation tags each cons cell element with a discriminator byte. These bytes add up quickly, blowing up interface files considerably when '-fwrite-if-simplified-core' is enabled. We compact the serialisation by writing out the length of 'IfaceAppArgs', followed by serialising the elements directly without any discriminator byte. This improvement can decrease the size of some interface files by up to 35%. - - - - - 97a2bb1c by Simon Peyton Jones at 2024-03-20T17:11:29+00:00 Expand untyped splices in tcPolyExprCheck Fixes #24559 - - - - - 5f275176 by Alan Zimmerman at 2024-03-20T22:44:12-04:00 EPA: Clean up Exactprint helper functions a bit - Introduce a helper lens to compose on `EpAnn a` vs `a` versions - Rename some prime versions of functions back to non-prime They were renamed during the rework - - - - - da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00 Type operators in promoteOccName (#24570) Type operators differ from term operators in that they are lexically classified as (type) constructors, not as (type) variables. Prior to this change, promoteOccName did not account for this difference, causing a scoping issue that affected RequiredTypeArguments. type (!@#) = Bool f = idee (!@#) -- Not in scope: ‘!@#’ (BUG) Now we have a special case in promoteOccName to account for this. - - - - - 247fc0fa by Preetham Gujjula at 2024-03-21T10:19:18-04:00 docs: Remove mention of non-existent Ord instance for Complex The documentation for Data.Complex says that the Ord instance for Complex Float is deficient, but there is no Ord instance for Complex a. The Eq instance for Complex Float is similarly deficient, so we use that as an example instead. - - - - - 6fafc51e by Andrei Borzenkov at 2024-03-21T10:19:54-04:00 Fix TH handling in `pat_to_type_pat` function (#24571) There was missing case for `SplicePat` in `pat_to_type_at` function, hence patterns with splicing that checked against `forall->` doesn't work properly because they fall into the "illegal pattern" case. Code example that is now accepted: g :: forall a -> () g $([p| a |]) = () - - - - - 52072f8e by Sylvain Henry at 2024-03-21T21:01:59-04:00 Type-check default declarations before deriving clauses (#24566) See added Note and #24566. Default declarations must be type-checked before deriving clauses. - - - - - 7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00 Lexer: small perf changes - Use unsafeChr because we know our values to be valid - Remove some unnecessary use of `ord` (return Word8 values directly) - - - - - 864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00 JS: fix some comments - - - - - 3e0b2b1f by Sebastian Graf at 2024-03-21T21:03:16-04:00 Simplifier: Re-do dependency analysis in abstractFloats (#24551) In #24551, we abstracted a string literal binding over a type variable, triggering a CoreLint error when that binding floated to top-level. The solution implemented in this patch fixes this by re-doing dependency analysis on a simplified recursive let binding that is about to be type abstracted, in order to find the minimal set of type variables to abstract over. See wrinkle (AB5) of Note [Floating and type abstraction] for more details. Fixes #24551 - - - - - 8a8ac65a by Matthew Craven at 2024-03-23T00:20:52-04:00 Improve toInteger @Word32 on 64-bit platforms On 64-bit platforms, every Word32 fits in an Int, so we can convert to Int# without having to perform the overflow check integerFromWord# uses internally. - - - - - 0c48f2b9 by Apoorv Ingle at 2024-03-23T00:21:28-04:00 Fix for #24552 (see testcase T24552) Fixes for a bug in desugaring pattern synonyms matches, introduced while working on on expanding `do`-blocks in #18324 The `matchWrapper` unecessarily (and incorrectly) filtered out the default wild patterns in a match. Now the wild pattern alternative is simply ignored by the pm check as its origin is `Generated`. The current code now matches the expected semantics according to the language spec. - - - - - b72705e9 by Simon Peyton Jones at 2024-03-23T00:22:04-04:00 Print more info about kinds in error messages This fixes #24553, where GHC unhelpfully said error: [GHC-83865] • Expected kind ‘* -> * -> *’, but ‘Foo’ has kind ‘* -> * -> *’ See Note [Showing invisible bits of types in error messages] - - - - - 8f7cfc7e by Tristan Cacqueray at 2024-03-23T00:22:44-04:00 docs: remove the don't use float hint This hint is outdated, ``Complex Float`` are now specialised, and the heap space suggestion needs more nuance so it should be explained in the unboxed/storable array documentation. - - - - - 5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00 NCG: Fix a bug in jump shortcutting. When checking if a jump has more than one destination account for the possibility of some jumps not being representable by a BlockId. We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing represents non-BlockId jump destinations. Fixes #24507 - - - - - 8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00 docs: Drop old release notes, add for 9.12.1 - - - - - 7db8c992 by Cheng Shao at 2024-03-25T13:45:46-04:00 rts: fix clang compilation on aarch64 This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h which causes "error: address argument to atomic operation must be a pointer to _Atomic type" when compiling with clang on aarch64. - - - - - 237194ce by Sylvain Henry at 2024-03-25T13:46:27-04:00 Lexer: fix imports for Alex 3.5.1 (#24583) - - - - - 810660b7 by Cheng Shao at 2024-03-25T22:19:16-04:00 libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6 This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which includes numerous upstream libffi fixes, especially https://github.com/libffi/libffi/issues/760. - - - - - d2ba41e8 by Alan Zimmerman at 2024-03-25T22:19:51-04:00 EPA: do not duplicate comments in signature RHS - - - - - 32a8103f by Rodrigo Mesquita at 2024-03-26T21:16:12-04:00 configure: Use LDFLAGS when trying linkers A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to check for a working linker. If either of these fail, we try the next in line. However, we were not considering the `$LDFLAGS` when checking if these linkers worked. So we would pick a linker that does not support the current $LDFLAGS and fail further down the line when we used that linker with those flags. Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not supported by `ld.gold` but that was being picked still. - - - - - bf65a7c3 by Rodrigo Mesquita at 2024-03-26T21:16:48-04:00 bindist: Clean xattrs of bin and lib at configure time For issue #21506, we started cleaning the extended attributes of binaries and libraries from the bindist *after* they were installed to workaround notarisation (#17418), as part of `make install`. However, the `ghc-toolchain` binary that is now shipped with the bindist must be run at `./configure` time. Since we only cleaned the xattributes of the binaries and libs after they were installed, in some situations users would be unable to run `ghc-toolchain` from the bindist, failing at configure time (#24554). In this commit we move the xattr cleaning logic to the configure script. Fixes #24554 - - - - - cfeb70d3 by Rodrigo Mesquita at 2024-03-26T21:17:24-04:00 Revert "NCG: Fix a bug in jump shortcutting." This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66. Fixes #24586 - - - - - 13223f6d by Serge S. Gulin at 2024-03-27T07:28:51-04:00 JS: `h$rts_isProfiled` is removed from `profiling` and left its version at `rts/js/config.js` - - - - - 0acfe391 by Alan Zimmerman at 2024-03-27T07:29:27-04:00 EPA: Do not extend declaration range for trailine zero len semi The lexer inserts virtual semicolons having zero width. Do not use them to extend the list span of items in a list. - - - - - cd0fb82f by Alan Zimmerman at 2024-03-27T19:33:08+00:00 EPA: Fix FamDecl range The span was incorrect if opt_datafam_kind_sig was empty - - - - - f8f384a8 by Ben Gamari at 2024-03-29T01:23:03-04:00 Fix type of _get_osfhandle foreign import Fixes #24601. - - - - - 00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00:00 EPA: Extend StringLiteral range to include trailing commas This goes slightly against the exact printing philosophy where trailing decorations should be in an annotation, but the practicalities of adding it to the WarningTxt environment, and the problems caused by deviating do not make a more principles approach worthwhile. - - - - - efab3649 by brandon s allbery kf8nh at 2024-03-31T20:04:01-04:00 clarify Note [Preproccesing invocations] - - - - - c8a4c050 by Ben Gamari at 2024-04-02T12:50:35-04:00 rts: Fix TSAN_ENABLED CPP guard This should be `#if defined(TSAN_ENABLED)`, not `#if TSAN_ENABLED`, lest we suffer warnings. - - - - - e91dad93 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix errors when compiling with TSAN This commit fixes rts compilation errors when compiling with TSAN: - xxx_FENCE macros are redefined and trigger CPP warnings. - Use SIZEOF_W. WORD_SIZE_IN_BITS is provided by MachDeps.h which Cmm.h doesn't include by default. - - - - - a9ab9455 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix clang-specific errors when compiling with TSAN This commit fixes clang-specific rts compilation errors when compiling with TSAN: - clang doesn't have -Wtsan flag - Fix prototype of ghc_tsan_* helper functions - __tsan_atomic_* functions aren't clang built-ins and sanitizer/tsan_interface_atomic.h needs to be included - On macOS, TSAN runtime library is libclang_rt.tsan_osx_dynamic.dylib, not libtsan. -fsanitize-thread as a link-time flag will take care of linking the TSAN runtime library anyway so remove tsan as an rts extra library - - - - - 865bd717 by Cheng Shao at 2024-04-02T12:50:35-04:00 compiler: fix github link to __tsan_memory_order in a comment - - - - - 07cb627c by Cheng Shao at 2024-04-02T12:50:35-04:00 ci: improve TSAN CI jobs - Run TSAN jobs with +thread_sanitizer_cmm which enables Cmm instrumentation as well. - Run TSAN jobs in deb12 which ships gcc-12, a reasonably recent gcc that @bgamari confirms he's using in #GHC:matrix.org. Ideally we should be using latest clang release for latest improvements in sanitizers, though that's left as future work. - Mark TSAN jobs as manual+allow_failure in validate pipelines. The purpose is to demonstrate that we have indeed at least fixed building of TSAN mode in CI without blocking the patch to land, and once merged other people can begin playing with TSAN using their own dev setups and feature branches. - - - - - a1c18c7b by Andrei Borzenkov at 2024-04-02T12:51:11-04:00 Merge tc_infer_hs_type and tc_hs_type into one function using ExpType philosophy (#24299, #23639) This patch implements refactoring which is a prerequisite to updating kind checking of type patterns. This is a huge simplification of the main worker that checks kind of HsType. It also fixes the issues caused by previous code duplication, e.g. that we didn't add module finalizers from splices in inference mode. - - - - - 817e8936 by Rodrigo Mesquita at 2024-04-02T20:13:05-04:00 th: Hide the Language.Haskell.TH.Lib.Internal module from haddock Fixes #24562 - - - - - b36ee57b by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: reenable h$appendToHsString optimization (#24495) The optimization introducing h$appendToHsString wasn't kicking in anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30). This patch reenables the optimization by matching on case-expression, as done in Cmm for unpackCString# standard thunks. The test is also T24495 added in the next commits (two commits for ease of backporting to 9.8). - - - - - 527616e9 by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: fix h$appendToHsString implementation (#24495) h$appendToHsString needs to wrap its argument in an updatable thunk to behave like unpackAppendCString#. Otherwise if a SingleEntry thunk is passed, it is stored as-is in a CONS cell, making the resulting list impossible to deepseq (forcing the thunk doesn't update the contents of the CONS cell)! The added test checks that the optimization kicks in and that h$appendToHsString works as intended. Fix #24495 - - - - - faa30b41 by Simon Peyton Jones at 2024-04-02T20:14:22-04:00 Deal with duplicate tyvars in type declarations GHC was outright crashing before this fix: #24604 - - - - - e0b0c717 by Simon Peyton Jones at 2024-04-02T20:14:58-04:00 Try using MCoercion in exprIsConApp_maybe This is just a simple refactor that makes exprIsConApp_maybe a little bit more direct, simple, and efficient. Metrics: compile_time/bytes allocated geo. mean -0.1% minimum -2.0% maximum -0.0% Not a big gain, but worthwhile given that the code is, if anything, easier to grok. - - - - - 15f4d867 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Initial ./configure support for selecting I/O managers In this patch we just define new CPP vars, but don't yet use them or replace the existing approach. That will follow. The intention here is that every I/O manager can be enabled/disabled at GHC build time (subject to some constraints). More than one I/O manager can be enabled to be built. At least one I/O manager supporting the non-threaded RTS must be enabled as well as at least one supporting the non-threaded RTS. The I/O managers enabled here will become the choices available at runtime at RTS startup (in later patches). The choice can be made with RTS flags. There are separate sets of choices for the threaded and non-threaded RTS ways, because most I/O managers are specific to these ways. Furthermore we must establish a default I/O manager for the threaded and non-threaded RTS. Most I/O managers are platform-specific so there are checks to ensure each one can be enabled on the platform. Such checks are also where (in future) any system dependencies (e.g. libraries) can be checked. The output is a set of CPP flags (in the mk/config.h file), with one flag per named I/O manager: * IOMGR_BUILD_<name> : which ones should be built (some) * IOMGR_DEFAULT_NON_THREADED_<name> : which one is default (exactly one) * IOMGR_DEFAULT_THREADED_<name> : which one is default (exactly one) and a set of derived flags in IOManager.h * IOMGR_ENABLED_<name> : enabled for the current RTS way Note that IOMGR_BUILD_<name> just says that an I/O manager will be built for _some_ RTS way (i.e. threaded or non-threaded). The derived flags IOMGR_ENABLED_<name> in IOManager.h say if each I/O manager is enabled in the "current" RTS way. These are the ones that can be used for conditional compilation of the I/O manager code. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - 85b0f87a by Duncan Coutts at 2024-04-03T01:27:17-04:00 Change the handling of the RTS flag --io-manager= Now instead of it being just used on Windows to select between the WinIO vs the MIO or Win32-legacy I/O managers, it is now used on all platforms for selecting the I/O manager to use. Right now it remains the case that there is only an actual choice on Windows, but that will change later. Document the --io-manager flag in the user guide. This change is also reflected in the RTS flags types in the base library. Deprecate the export of IoSubSystem from GHC.RTS.Flags with a message to import it from GHC.IO.Subsystem. The way the 'IoSubSystem' is detected also changes. Instead of looking at the RTS flag, there is now a C bool global var in the RTS which gets set on startup when the I/O manager is selected. This bool var says whether the selected I/O manager classifies as "native" on Windows, which in practice means the WinIO I/O manager has been selected. Similarly, the is_io_mng_native_p RTS helper function is re-implemented in terms of the selected I/O manager, rather than based on the RTS flags. We do however remove the ./configure --native-io-manager flag because we're bringing the WinIO/MIO/Win32-legacy choice under the new general scheme for selecting I/O managers, and that new scheme involves no ./configure time user choices, just runtime RTS flag choices. - - - - - 1a8f020f by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert {init,stop,exit}IOManager to switch style Rather than ad-hoc cpp conitionals on THREADED_RTS and mingw32_HOST_OS, we use a style where we switch on the I/O manager impl, with cases for each I/O manager impl. - - - - - a5bad3d2 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Split up the CapIOManager content by I/O manager Using the new IOMGR_ENABLED_<name> CPP defines. - - - - - 1d36e609 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert initIOManagerAfterFork and wakeupIOManager to switch style - - - - - c2f26f36 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of waitRead#/Write# from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. - - - - - 457705a8 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of the delay# impl from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. Uses a new IOManager API: syncDelay, following the naming convention of sync* for thread-synchronous I/O & timer/delay operations. As part of porting from cmm to C, we maintain the rule that the why_blocked gets accessed using load acquire and store release atomic memory operations. There was one exception to this rule: in the delay# primop cmm code on posix (not win32), the why_blocked was being updated using a store relaxed, not a store release. I've no idea why. In this convesion I'm playing it safe here and using store release consistently. - - - - - e93058e0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 insertIntoSleepingQueue is no longer public No longer defined in IOManager.h, just a private function in IOManager.c. Since it is no longer called from cmm code, just from syncDelay. It ought to get moved further into the select() I/O manager impl, rather than living in IOManager.c. On the other hand appendToIOBlockedQueue is still called from cmm code in the win32-legacy I/O manager primops async{Read,Write}#, and it is also used by the select() I/O manager. Update the CPP and comments to reflect this. - - - - - 60ce9910 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move anyPendingTimeoutsOrIO impl from .h to .c The implementation is eventually going to need to use more private things, which will drag in unwanted includes into IOManager.h, so it's better to move the impl out of the header file and into the .c file, at the slight cost of it no longer being inline. At the same time, change to the "switch (iomgr_type)" style. - - - - - f70b8108 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Take a simpler approach to gcc warnings in IOManager.c We have lots of functions with conditional implementations for different I/O managers. Some functions, for some I/O managers, naturally have implementations that do nothing or barf. When only one such I/O manager is enabled then the whole function implementation will have an implementation that does nothing or barfs. This then results in warnings from gcc that parameters are unused, or that the function should be marked with attribute noreturn (since barf does not return). The USED_IF_THREADS trick for fine-grained warning supression is fine for just two cases, but an equivalent here would need USED_IF_THE_ONLY_ENABLED_IOMGR_IS_X_OR_Y which would have combinitorial blowup. So we take a coarse grained approach and simply disable these two warnings for the whole file. So we use a GCC pragma, with its handy push/pop support: #pragma GCC diagnostic push #pragma GCC diagnostic ignored "-Wsuggest-attribute=noreturn" #pragma GCC diagnostic ignored "-Wunused-parameter" ... #pragma GCC diagnostic pop - - - - - b48805b9 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add a new trace class for the iomanager It makes sense now for it to be separate from the scheduler class of tracers. Enabled with +RTS -Do. Document the -Do debug flag in the user guide. - - - - - f0c1f862 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Have the throwTo impl go via (new) IOManager APIs rather than directly operating on the IO manager's data structures. Specifically, when thowing an async exception to a thread that is blocked waiting for I/O or waiting for a timer, then we want to cancel that I/O waiting or cancel the timer. Currently this is done directly in removeFromQueues() in RaiseAsync.c. We want it to go via proper APIs both for modularity but also to let us support multiple I/O managers. So add sync{IO,Delay}Cancel, which is the cancellation for the corresponding sync{IO,Delay}. The implementations of these use the usual "switch (iomgr_type)" style. - - - - - 4f9e9c4e by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move awaitEvent into a proper IOManager API and have the scheduler use it. Previously the scheduler calls awaitEvent directly, and awaitEvent is implemented directly in the RTS I/O managers (select, win32). This relies on the old scheme where there's a single active I/O manager for each platform and RTS way. We want to move that to go via an API in IOManager.{h,c} which can then call out to the active I/O manager. Also take the opportunity to split awaitEvent into two. The existing awaitEvent has a bool wait parameter, to say if the call should be blocking or non-blocking. We split this into two separate functions: pollCompletedTimeoutsOrIO and awaitCompletedTimeoutsOrIO. We split them for a few reasons: they have different post-conditions (specifically the await version is supposed to guarantee that there are threads runnable when it completes). Secondly, it is also anticipated that in future I/O managers the implementations of the two cases will be simpler if they are separated. - - - - - 5ad4b30f by Duncan Coutts at 2024-04-03T01:27:18-04:00 Rename awaitEvent in select and win32 I/O managers These are now just called from IOManager.c and are the per-I/O manager backend impls (whereas previously awaitEvent was the entry point). Follow the new naming convention in the IOManager.{h,c} of awaitCompletedTimeoutsOrIO, with the I/O manager's name as a suffix: so awaitCompletedTimeoutsOrIO{Select,Win32}. - - - - - d30c6bc6 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Tidy up a couple things in Select.{h,c} Use the standard #include {Begin,End}Private.h style rather than RTS_PRIVATE on individual decls. And conditionally build the code for the select I/O manager based on the new CPP IOMGR_ENABLED_SELECT rather than on THREADED_RTS. - - - - - 4161f516 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add an IOManager API for scavenging TSO blocked_info When the GC scavenges a TSO it needs to scavenge the tso->blocked_info but the blocked_info is a big union and what lives there depends on the two->why_blocked, which for I/O-related reasons is something that in principle is the responsibility of the I/O manager and not the GC. So the right thing to do is for the GC to ask the I/O manager to sscavenge the blocked_info if it encounters any I/O-related why_blocked reasons. So we add scavengeTSOIOManager in IOManager.{h,c} with the usual style. Now as it happens, right now, there is no special scavenging to do, so the implementation of scavengeTSOIOManager is a fancy no-op. That's because the select I/O manager uses only the fd and target members, which are not GC pointers, and the win32-legacy I/O manager _ought_ to be using GC-managed heap objects for the StgAsyncIOResult but it is actually usingthe C heap, so again no GC pointers. If the win32-legacy were doing this more sensibly, then scavengeTSOIOManager would be the right place to do the GC magic. Future I/O managers will need GC heap objects in the tso->blocked_info and will make use of this functionality. - - - - - 94a87d21 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add I/O manager API notifyIOManagerCapabilitiesChanged Used in setNumCapabilities. It only does anything for MIO on Posix. Previously it always invoked Haskell code, but that code only did anything on non-Windows (and non-JS), and only threaded. That currently effectively means the MIO I/O manager on Posix. So now it only invokes it for the MIO Posix case. - - - - - 3be6d591 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Select an I/O manager early in RTS startup We need to select the I/O manager to use during startup before the per-cap I/O manager initialisation. - - - - - aaa294d0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Make struct CapIOManager be fully opaque Provide an opaque (forward) definition in Capability.h (since the cap contains a *CapIOManager) and then only provide a full definition in a new file IOManagerInternals.h. This new file is only supposed to be included by the IOManager implementation, not by its users. So that means IOManager.c and individual I/O manager implementations. The posix/Signals.c still needs direct access, but that should be eliminated. Anything that needs direct access either needs to be clearly part of an I/O manager (e.g. the sleect() one) or go via a proper API. - - - - - 877a2a80 by Duncan Coutts at 2024-04-03T01:27:18-04:00 The select() I/O manager does have some global initialisation It's just to make sure an exception CAF is a GC root. - - - - - 9c51473b by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add tracing for the main I/O manager actions Using the new tracer class. Note: The unconditional definition of showIOManager should be compatible with the debugTrace change in 7c7d1f6. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - c7d3e3a3 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Include the default I/O manager in the +RTS --info output Document the extra +RTS --info output in the user guide - - - - - 8023bad4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 waitRead# / waitWrite# do not work for win32-legacy I/O manager Previously it was unclear that they did not work because the code path was shared with other I/O managers (in particular select()). Following the code carefully shows that what actually happens is that the calling thread would block forever: the thread will be put into the blocked queue, but no other action is scheduled that will ever result in it getting unblocked. It's better to just fail loudly in case anyone accidentally calls it, also it's less confusing code. - - - - - 83a74d20 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Conditionally ignore some GCC warnings Some GCC versions don't know about some warnings, and they complain that we're ignoring unknown warnings. So we try to ignore the warning based on the GCC version. - - - - - 1adc6fa4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept changes to base-exports All the changes are in fact not changes at all. Previously, the IoSubSystem data type was defined in GHC.RTS.Flags and exported from both GHC.RTS.Flags and GHC.IO.SubSystem. Now, the data type is defined in GHC.IO.SubSystem and still exported from both modules. Therefore, the same exports and same instances are still available from both modules. But the base-exports records only the defining module, and so it looks like a change when it is fully compatible. Related: we do add a deprecation to the export of the type via GHC.RTS.Flags, telling people to use the export from GHC.IO.SubSystem. Also the sort order for some unrelated Show instances changed. No idea why. The same changes apply in the other versions, with a few more changes due to sort order weirdness. - - - - - 8d950968 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept metric decrease in T12227 I can't think of any good reason that anything in this MR should have changed the number of allocations, up or down. (Yes this is an empty commit.) Metric Decrease: T12227 - - - - - e869605e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Several improvements to the handling of coercions * Make `mkSymCo` and `mkInstCo` smarter Fixes #23642 * Fix return role of `SelCo` in the coercion optimiser. Fixes #23617 * Make the coercion optimiser `opt_trans_rule` work better for newtypes Fixes #23619 - - - - - 1efd0714 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 FloatOut: improve floating for join point See the new Note [Floating join point bindings]. * Completely get rid of the complicated join_ceiling nonsense, which I have never understood. * Do not float join points at all, except perhaps to top level. * Some refactoring around wantToFloat, to treat Rec and NonRec more uniformly - - - - - 9c00154d by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve eta-expansion through call stacks See Note [Eta expanding through CallStacks] in GHC.Core.Opt.Arity This is a one-line change, that fixes an inconsistency - || isCallStackPredTy ty + || isCallStackPredTy ty || isCallStackTy ty - - - - - 95a9a172 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Spelling, layout, pretty-printing only - - - - - bdf1660f by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve exprIsConApp_maybe a little Eliminate a redundant case at birth. This sometimes reduces Simplifier iterations. See Note [Case elim in exprIsConApp_maybe]. - - - - - 609cd32c by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Inline GHC.HsToCore.Pmc.Solver.Types.trvVarInfo When exploring compile-time regressions after meddling with the Simplifier, I discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very delicately balanced. It's a small, heavily used, overloaded function and it's important that it inlines. By a fluke it was before, but at various times in my journey it stopped doing so. So I just added an INLINE pragma to it; no sense in depending on a delicately-balanced fluke. - - - - - ae24c9bc by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Slight improvement in WorkWrap Ensure that WorkWrap preserves lambda binders, in case of join points. Sadly I have forgotten why I made this change (it was while I was doing a lot of meddling in the Simplifier, but * it does no harm, * it is slightly more efficient, and * presumably it made something better! Anyway I have kept it in a separate commit. - - - - - e9297181 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Use named record fields for the CastIt { ... } data constructor This is a pure refactor - - - - - b4581e23 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Remove a long-commented-out line Pure refactoring - - - - - e026bdf2 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Simplifier improvements This MR started as: allow the simplifer to do more in one pass, arising from places I could see the simplifier taking two iterations where one would do. But it turned into a larger project, because these changes unexpectedly made inlining blow up, especially join points in deeply-nested cases. The main changes are below. There are also many new or rewritten Notes. Avoiding simplifying repeatedly ~~~~~~~~~~~~~~~ See Note [Avoiding simplifying repeatedly] * The SimplEnv now has a seInlineDepth field, which says how deep in unfoldings we are. See Note [Inline depth] in Simplify.Env. Currently used only for the next point: avoiding repeatedly simplifying coercions. * Avoid repeatedly simplifying coercions. see Note [Avoid re-simplifying coercions] in Simplify.Iteration As you'll see from the Note, this makes use of the seInlineDepth. * Allow Simplify.Iteration.simplAuxBind to inline used-once things. This is another part of Note [Post-inline for single-use things], and is really good for reducing simplifier iterations in situations like case K e of { K x -> blah } wher x is used once in blah. * Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case elimination. Note [Case elim in exprIsConApp_maybe] * Improve the case-merge transformation: - Move the main code to `GHC.Core.Utils.mergeCaseAlts`, to join `filterAlts` and friends. See Note [Merge Nested Cases] in GHC.Core.Utils. - Add a new case for `tagToEnum#`; see wrinkle (MC3). - Add a new case to look through join points: see wrinkle (MC4) postInlineUnconditionally ~~~~~~~~~~~~~~~~~~~~~~~~~ * Allow Simplify.Utils.postInlineUnconditionally to inline variables that are used exactly once. See Note [Post-inline for single-use things]. * Do not postInlineUnconditionally join point, ever. Doing so does not reduce allocation, which is the main point, and with join points that are used a lot it can bloat code. See point (1) of Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration. * Do not postInlineUnconditionally a strict (demanded) binding. It will not allocate a thunk (it'll turn into a case instead) so again the main point of inlining it doesn't hold. Better to check per-call-site. * Improve occurrence analyis for bottoming function calls, to help postInlineUnconditionally. See Note [Bottoming function calls] in GHC.Core.Opt.OccurAnal Inlining generally ~~~~~~~~~~~~~~~~~~ * In GHC.Core.Opt.Simplify.Utils.interestingCallContext, use RhsCtxt NonRecursive (not BoringCtxt) for a plain-seq case. See Note [Seq is boring] Also, wrinkle (SB1), inline in that `seq` context only for INLINE functions (UnfWhen guidance). * In GHC.Core.Opt.Simplify.Utils.interestingArg, - return ValueArg for OtherCon [c1,c2, ...], but - return NonTrivArg for OtherCon [] This makes a function a little less likely to inline if all we know is that the argument is evaluated, but nothing else. * isConLikeUnfolding is no longer true for OtherCon {}. This propagates to exprIsConLike. Con-like-ness has /positive/ information. Join points ~~~~~~~~~~~ * Be very careful about inlining join points. See these two long Notes Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline * When making join points, don't do so if the join point is so small it will immediately be inlined; check uncondInlineJoin. * In GHC.Core.Opt.Simplify.Inline.tryUnfolding, improve the inlining heuristics for join points. In general we /do not/ want to inline join points /even if they are small/. See Note [Duplicating join points] GHC.Core.Opt.Simplify.Iteration. But sometimes we do: see Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline; and the new `isBetterUnfoldingThan` function. * Do not add an unfolding to a join point at birth. This is a tricky one and has a long Note [Do not add unfoldings to join points at birth] It shows up in two places - In `mkDupableAlt` do not add an inlining - (trickier) In `simplLetUnfolding` don't add an unfolding for a fresh join point I am not fully satisifed with this, but it works and is well documented. * In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise having a non-inlined join point. Performance changes ~~~~~~~~~~~~~~~~~~~ * Binary sizes fall by around 2.6%, according to nofib. * Compile times improve slightly. Here are the figures over 1%. I investiate the biggest differnce in T18304. It's a very small module, just a few hundred nodes. The large percentage difffence is due to a single function that didn't quite inline before, and does now, making code size a bit bigger. I decided gains outweighed the losses. Metrics: compile_time/bytes allocated (changes over +/- 1%) ------------------------------------------------ CoOpt_Singletons(normal) -9.2% GOOD LargeRecord(normal) -23.5% GOOD MultiComponentModulesRecomp(normal) +1.2% MultiLayerModulesTH_OneShot(normal) +4.1% BAD PmSeriesS(normal) -3.8% PmSeriesV(normal) -1.5% T11195(normal) -1.3% T12227(normal) -20.4% GOOD T12545(normal) -3.2% T12707(normal) -2.1% GOOD T13253(normal) -1.2% T13253-spj(normal) +8.1% BAD T13386(normal) -3.1% GOOD T14766(normal) -2.6% GOOD T15164(normal) -1.4% T15304(normal) +1.2% T15630(normal) -8.2% T15630a(normal) NEW T15703(normal) -14.7% GOOD T16577(normal) -2.3% GOOD T17516(normal) -39.7% GOOD T18140(normal) +1.2% T18223(normal) -17.1% GOOD T18282(normal) -5.0% GOOD T18304(normal) +10.8% BAD T18923(normal) -2.9% GOOD T1969(normal) +1.0% T19695(normal) -1.5% T20049(normal) -12.7% GOOD T21839c(normal) -4.1% GOOD T3064(normal) -1.5% T3294(normal) +1.2% BAD T4801(normal) +1.2% T5030(normal) -15.2% GOOD T5321Fun(normal) -2.2% GOOD T6048(optasm) -16.8% GOOD T783(normal) -1.2% T8095(normal) -6.0% GOOD T9630(normal) -4.7% GOOD T9961(normal) +1.9% BAD WWRec(normal) -1.4% info_table_map_perf(normal) -1.3% parsing001(normal) +1.5% geo. mean -2.0% minimum -39.7% maximum +10.8% * Runtimes generally improve. In the testsuite perf/should_run gives: Metrics: runtime/bytes allocated ------------------------------------------ Conversions(normal) -0.3% T13536a(optasm) -41.7% GOOD T4830(normal) -0.1% haddock.Cabal(normal) -0.1% haddock.base(normal) -0.1% haddock.compiler(normal) -0.1% geo. mean -0.8% minimum -41.7% maximum +0.0% * For runtime, nofib is a better test. The news is mostly good. Here are the number more than +/- 0.1%: # bytes allocated ==========================++========== imaginary/digits-of-e1 || -14.40% imaginary/digits-of-e2 || -4.41% imaginary/paraffins || -0.17% imaginary/rfib || -0.15% imaginary/wheel-sieve2 || -0.10% real/compress || -0.47% real/fluid || -0.10% real/fulsom || +0.14% real/gamteb || -1.47% real/gg || -0.20% real/infer || +0.24% real/pic || -0.23% real/prolog || -0.36% real/scs || -0.46% real/smallpt || +4.03% shootout/k-nucleotide || -20.23% shootout/n-body || -0.42% shootout/spectral-norm || -0.13% spectral/boyer2 || -3.80% spectral/constraints || -0.27% spectral/hartel/ida || -0.82% spectral/mate || -20.34% spectral/para || +0.46% spectral/rewrite || +1.30% spectral/sphere || -0.14% ==========================++========== geom mean || -0.59% real/smallpt has a huge nest of local definitions, and I could not pin down a reason for a regression. But there are three big wins! Metric Decrease: CoOpt_Singletons LargeRecord T12227 T12707 T13386 T13536a T14766 T15703 T16577 T17516 T18223 T18282 T18923 T21839c T20049 T5321Fun T5030 T6048 T8095 T9630 T783 Metric Increase: MultiLayerModulesTH_OneShot T13253-spj T18304 T18698a T9961 T3294 - - - - - 27db3c5e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Testsuite message changes from simplifier improvements - - - - - 271a7812 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Account for bottoming functions in OccurAnal This fixes #24582, a small but long-standing bug - - - - - 0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00 testsuite: Introduce template-haskell-exports test - - - - - 0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00 Update correct counter in bumpTickyAllocd - - - - - 5f085d3a by Fendor at 2024-04-04T14:47:33-04:00 Replace `SizedSeq` with `FlatBag` for flattened structure LinkedLists are notoriously memory ineffiecient when all we do is traversing a structure. As 'UnlinkedBCO' has been identified as a data structure that impacts the overall memory usage of GHCi sessions, we avoid linked lists and prefer flattened structure for storing. We introduce a new memory efficient representation of sequential elements that has special support for the cases: * Empty * Singleton * Tuple Elements This improves sharing in the 'Empty' case and avoids the overhead of 'Array' until its constant overhead is justified. - - - - - 82cfe10c by Fendor at 2024-04-04T14:47:33-04:00 Compact FlatBag array representation `Array` contains three additional `Word`'s we do not need in `FlatBag`. Move `FlatBag` to `SmallArray`. Expand the API of SmallArray by `sizeofSmallArray` and add common traversal functions, such as `mapSmallArray` and `foldMapSmallArray`. Additionally, allow users to force the elements of a `SmallArray` via `rnfSmallArray`. - - - - - 36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00 Change how invisible patterns represented in haskell syntax and TH AST (#24557) Before this patch: data ArgPat p = InvisPat (LHsType p) | VisPat (LPat p) With this patch: data Pat p = ... | InvisPat (LHsType p) ... And the same transformation in the TH land. The rest of the changes is just updating code to handle new AST and writing tests to check if it is possible to create invalid states using TH. Metric Increase: MultiLayerModulesTH_OneShot - - - - - 28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00 Fix off by one error in seekBinNoExpand and seekBin - - - - - 9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00 compiler: Allow more types in GHCForeignImportPrim For many, many years `GHCForeignImportPrim` has suffered from the rather restrictive limitation of not allowing any non-trivial types in arguments or results. This limitation was justified by the code generator allegely barfing in the presence of such types. However, this restriction appears to originate well before the NCG rewrite and the new NCG does not appear to have any trouble with such types (see the added `T24598` test). Lift this restriction. Fixes #24598. - - - - - 1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00 EPA: Use EpaLocation not SrcSpan in ForeignDecls This allows us to update them for makeDeltaAst in ghc-exactprint - - - - - 19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00 EPA: Use EpaLocation for RecFieldsDotDot So we can update it to a delta position in makeDeltaAst if needed. - - - - - e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00 Remove accidentally committed test.hs - - - - - 88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00 Avoid UArray when indexing is not required `UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO` references two `UArray`'s but never indexes them. They are only needed to encode the elements into a `ByteArray#`. The three words for the lower bound, upper bound and number of elements are essentially unused, thus we replace `UArray` with a wrapper around `ByteArray#`. This saves us up to three words for each `UnlinkedBCO`. Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances. For example, agda's repl session has around 360_000 UnlinkedBCO's, so avoiding these three words is already saving us around 8MB residency. - - - - - f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00 Never UNPACK `FastMutInt` for counting z-encoded `FastString`s In `FastStringTable`, we count the number of z-encoded FastStrings that exist in a GHC session. We used to UNPACK the counters to not waste memory, but live retainer analysis showed that we allocate a lot of `FastMutInt`s, retained by `mkFastZString`. We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is forced. The function `mkFastStringWith` calls `mkZFastString` and boxes the `FastMutInt`, leading to the following core: mkFastStringWith = \ mk_fs _ -> = case stringTable of { FastStringTable _ n_zencs segments# _ -> ... case ((mk_fs (I# ...) (FastMutInt n_zencs)) `cast` <Co:2> :: ...) ... Marking this field as `NOUNPACK` avoids this reboxing, eliminating the allocation of a fresh `FastMutInt` on every `FastString` allocation. - - - - - c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00 Force in_multi to avoid retaining entire hsc_env - - - - - fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00 Eliminate name thunk in declaration fingerprinting Thunk analysis showed that we have about 100_000 thunks (in agda and `-fwrite-simplified-core`) pointing to the name of the name decl. Forcing this thunk fixes this issue. The thunk created here is retained by the thunk created by forkM, it is better to eagerly force this because the result (a `Name`) is already retained indirectly via the `IfaceDecl`. - - - - - 3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Use EpaLocation in WarningTxt This allows us to use an EpDelta if needed when using makeDeltaAst. - - - - - 12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc This allows us to use a NoCommentsLocation for the possibly trailing comma location in a StringLiteral. This in turn allows us to correctly roundtrip via makeDeltaAst. - - - - - 868c8a78 by Fendor at 2024-04-09T08:51:50-04:00 Prefer packed representation for CompiledByteCode As there are many 'CompiledByteCode' objects alive during a GHCi session, representing its element in a more packed manner improves space behaviour at a minimal cost. When running GHCi on the agda codebase, we find around 380 live 'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode' can save quite some pointers. - - - - - be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00 EPA: Capture all comments in a ClassDecl Hopefully the final fix needed for #24533 - - - - - 3d0806fc by Jade at 2024-04-10T05:39:53-04:00 Validate -main-is flag using parseIdentifier Fixes #24368 - - - - - dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c - - - - - e008a19a by Alexis King at 2024-04-10T05:40:29-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) - - - - - dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. - - - - - 12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. - - - - - dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00 testsuite: Add test for lookupSymbolInNativeObj - - - - - 1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00 EPA: Remove unnecessary XRec in CompleteMatchSig The XRec for [LIdP pass] is not needed for exact printing, remove it. - - - - - 6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00 users-guide: Clarify language extension documentation Over the years the users guide's language extension documentation has gone through quite a few refactorings. In the process some of the descriptions have been rendered non-sensical. For instance, the description of `NoImplicitPrelude` actually describes the semantics of `ImplicitPrelude`. To fix this we: * ensure that all extensions are named in their "positive" sense (e.g. `ImplicitPrelude` rather than `NoImplicitPrelude`). * rework the documentation to avoid flag-oriented wording like "enable" and "disable" * ensure that the polarity of the documentation is consistent with reality. Fixes #23895. - - - - - a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. - - - - - 23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00 RTS: Emit warning when -M < -H Fixes #24487 - - - - - d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00 testsuite: Add broken test for CApiFFI with -fprefer-bytecode See #24634. - - - - - a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00 base: Deprecate GHC.Pack As proposed in #21461. Closes #21540. - - - - - 55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00 ghc-internal: Fix mentions of ghc-internal in deprecation warnings Closes #24609. - - - - - b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00 rts: Implement set_initial_registers for AArch64 Fixes #23680. - - - - - 14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00 ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17 Closes #24646. - - - - - 35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00 Bump unix submodule to 2.8.5.1 Closes #24640. - - - - - a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00 Correct default -funfolding-use-threshold in docs - - - - - 0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00 FastString is a __Modified__ UTF-8 - - - - - c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00 rts: Improve tracing message when nursery is resized It is sometimes more useful to know how much bigger or smaller the nursery got when it is resized. In particular I am trying to investigate situations where we end up with fragmentation due to the nursery (#24577) - - - - - 5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00 Don't generate wrappers for `type data` constructors with StrictData Previously, the logic for checking if a data constructor needs a wrapper or not would take into account whether the constructor's fields have explicit strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into account whether `StrictData` was enabled. This meant that something like `type data T = MkT Int` would incorrectly generate a wrapper for `MkT` if `StrictData` was enabled, leading to the horrible errors seen in #24620. To fix this, we disable generating wrappers for `type data` constructors altogether. Fixes #24620. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00 Implements MO_S_Mul2 and MO_U_Mul2 using the UMULH, UMULL and SMULH instructions for AArch64 Also adds a test for MO_S_Mul2 - - - - - 42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00 Make template-haskell a stage1 package Promoting template-haskell from a stage0 to a stage1 package means that we can much more easily refactor template-haskell. We implement this by duplicating the in-tree `template-haskell`. A new `template-haskell-next` library is autogenerated to mirror `template-haskell` `stage1:ghc` to depend on the new interface of the library including the `Binary` instances without adding an explicit dependency on `template-haskell`. This is controlled by the `bootstrap-th` cabal flag When building `template-haskell` modules as part of this vendoring we do not have access to quote syntax, so we cannot use variable quote notation (`'Just`). So we either replace these with hand-written `Name`s or hide the code behind CPP. We can remove the `th_hack` from hadrian, which was required when building stage0 packages using the in-tree `template-haskell` library. For more details see Note [Bootstrapping Template Haskell]. Resolves #23536 Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - 3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00 Bump parsec submodule to 3.1.17.0 - - - - - 9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00 Clone CoVars in CorePrep This MR addresses #24463. It's all explained in the new Note [Cloning CoVars and TyVars] - - - - - 0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00 NCG: Fix a bug where we errounously removed a required jump instruction. Add a new method to the Instruction class to check if we can eliminate a jump in favour of fallthrough control flow. Fixes #24507 - - - - - 9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00 Fix documentation preview from doc-tarball job - Include all the .html files and assets in the job artefacts - Include all the .pdf files in the job artefacts - Mark the artefact as an "exposed" artefact meaning it turns up in the UI. Resolves #24651 - - - - - 3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00 rts: Ignore EINTR while polling in timerfd itimer implementation While the RTS does attempt to mask signals, it may be that a foreign library unmasks them. This previously caused benign warnings which we now ignore. See #24610. - - - - - 9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00 EPA: Add additional comments field to AnnsModule This is used in exact printing to store comments coming after the `where` keyword but before any comments allocated to imports or decls. It is used in ghc-exactprint, see https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7 - - - - - e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00 Remove unrunnable FreeBSD CI jobs FreeBSD runner supply is inelastic. Currently there is only one, and it's unavailable because of a hardware issue. - - - - - 914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00 rel-eng: Fix mktemp usage in recompress-all We need a temporary directory, not a file. - - - - - f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00 Fix ghc API link in docs/index.html This was missing part of the unit ID meaning it would 404. Resolves #24674 - - - - - d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00 template-haskell: Declare TH.Lib.Internal as not-home Rather than `hide`. Closes #24659. - - - - - 5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00 testsuite: Rename isCross() predicate to needsTargetWrapper() isCross() was a misnamed because it assumed that all cross targets would provide a target wrapper, but the two most common cross targets (javascript, wasm) don't need a target wrapper. Therefore we rename this predicate to `needsTargetWrapper()` so situations in the testsuite where we can check whether running executables requires a target wrapper or not. - - - - - 55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00 Do not float HNFs out of lambdas This MR adjusts SetLevels so that it is less eager to float a HNF (lambda or constructor application) out of a lambda, unless it gets to top level. Data suggests that this change is a small net win: * nofib bytes-allocated falls by -0.09% (but a couple go up) * perf/should_compile bytes-allocated falls by -0.5% * perf/should_run bytes-allocated falls by -0.1% See !12410 for more detail. When fiddling elsewhere, I also found that this patch had a huge positive effect on the (very delicate) test perf/should_run/T21839r But that improvement doesn't show up in this MR by itself. Metric Decrease: MultiLayerModulesRecomp T15703 parsing001 - - - - - f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00 EPA: Fix comments in mkListSyntaxTy0 Also extend the test to confirm. Addresses #24669, 1 of 4 - - - - - b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00 JS: set image `x86_64-linux-deb11-emsdk-closure` for build - - - - - c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00 EPA: Provide correct span for PatBind And remove unused parameter in checkPatBind Contributes to #24669 - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - 26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00 EPA: Fix span for PatBuilderAppType Include the location of the prefix @ in the span for InVisPat. Also removes unnecessary annotations from HsTP. Contributes to #24669 - - - - - dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00 testsuite: Give the pre_cmd for mhu-perf more time - - - - - d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00 Fix quantification order for a `op` b and a %m -> b Fixes #23764 Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst Updates haddock submodule. - - - - - 385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00 Make `seq#` a magic Id and inline it in CorePrep (#24124) We can save much code and explanation in Tag Inference and StgToCmm by making `seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in CorePrep. See the updated `Note [seq# magic]`. I also implemented a new `Note [Flatten case-bind]` to get better code for otherwise nested case scrutinees. I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to resolve the clash between `type CpeApp = CoreExpr` and the data constructor of `ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`. Fixes #24252 and #24124. - - - - - 275e41a9 by Jade at 2024-04-20T11:10:40-04:00 Put the newline after errors instead of before them This mainly has consequences for GHCi but also slightly alters how the output of GHC on the commandline looks. Fixes: #22499 - - - - - dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00 Remove unecessary stage0 packages Historically quite a few packages had to be stage0 as they depended on `template-haskell` and that was stage0. In #23536 we made it so that was no longer the case. This allows us to remove a bunch of packages from this list. A few still remain. A new version of `Win32` is required by `semaphore-compat`. Including `Win32` in the stage0 set requires also including `filepath` because otherwise Hadrian's dependency logic gets confused. Once our boot compiler has a newer version of `Win32` all of these will be able to be dropped. Resolves #24652 - - - - - 2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00 EPA: Avoid duplicated comments in splice decls Contributes to #24669 - - - - - c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fix typos and namings (fixes #24602) You may noted that I've also changed term of ``` , global "h$vt_double" ||= toJExpr IntV ``` See "IntV" and ``` WaitReadOp -> \[] [fd] -> pure $ PRPrimCall $ returnS (app "h$waidRead" [fd]) ``` See "h$waidRead" - - - - - 3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: trivial checks for variable presence (fixes #24602) - - - - - 777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped in a closure to prevent conflict with emscripten (fixes #24602) Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues. At first glance we should try UMD (See https://github.com/umdjs/umd) - - - - - a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal code copied from GHCJS (fixes #24602) I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607). Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};` - - - - - ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: heap and stack overflows reporting defined as js hard failure (fixes #24602) These errors were treated as a hard failure for browser application. The fix is trivial: just throw error. - - - - - 5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00 JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602) These errors were fixed just by introducing stubbed functions with throw for further implementation. - - - - - a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add externs to linker (fixes #24602) After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following: 1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8). 2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle. 3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`. 4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?` - - - - - e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: added both tests: for size and for correctness (fixes #24602) By some reason MacOS builds add to stderr messages like: Ignoring unexpected archive entry: __.SYMDEF ... However I left stderr to `/dev/null` for compatibility with linux CI builds. - - - - - 909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments - - - - - 83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602) Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators. But now there are following compiler options: `-C` and `-CC`. You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC). It seems that `-CC` works better for javascript jsdoc than `-traditional`. At least it leaves `/* ... */` comments w/o changes. - - - - - e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00 fix link in CODEOWNERS It seems that our local Gitlab no longer has documentation for the `CODEOWNERS` file, but the master documentation still does. Use that instead. - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - 593f4e04 by Fendor at 2024-04-23T10:19:14-04:00 Add performance regression test for '-fwrite-simplified-core' - - - - - 1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00 Typecheck corebindings lazily during bytecode generation This delays typechecking the corebindings until the bytecode generation happens. We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`. In general, we shouldn't retain values of the hydrated `Type`, as not evaluating the bytecode object keeps it alive. It is better if we retain the unhydrated `IfaceType`. See Note [Hydrating Modules] - - - - - e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00 EPA: Keep comments in a CaseAlt match The comments now live in the surrounding location, not inside the Match. Make sure we keep them. Closes #24707 - - - - - d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00 driver: force merge objects when building dynamic objects This patch forces the driver to always merge objects when building dynamic objects even when ar -L is supported. It is an oversight of !8887: original rationale of that patch is favoring the relatively cheap ar -L operation over object merging when ar -L is supported, which makes sense but only if we are building static objects! Omitting check for whether we are building dynamic objects will result in broken .so files with undefined reference errors at executable link time when building GHC with llvm-ar. Fixes #22210. - - - - - 209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00 Allow non-absolute values for bootstrap GHC variable Fixes #24682 - - - - - 3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00 Don't depend on registerPackage function in Cabal More recent versions of Cabal modify the behaviour of libAbiHash which breaks our usage of registerPackage. It is simpler to inline the part of registerPackage that we need and avoid any additional dependency and complication using the higher-level function introduces. - - - - - c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: remove obsolete ln script This commit removes an obsolete ln script in ghc-bignum/gmp. See 060251c24ad160264ae8553efecbb8bed2f06360 for its original intention, but it's been obsolete for a long time, especially since the removal of the make build system. Hence the house cleaning. - - - - - 6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: update gmp to 6.3.0 This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0. The tarball format is now xz, and gmpsrc.patch has been patched into the tarball so hadrian no longer needs to deal with patching logic when building in-tree GMP. - - - - - 65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00 hadrian: remove obsolete Patch logic This commit removes obsolete Patch logic from hadrian, given we no longer need to patch the gmp tarball when building in-tree GMP. - - - - - 71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00 autoconf: remove obsolete patch detection This commit removes obsolete deletection logic of the patch command from autoconf scripts, given we no longer need to patch anything in the GHC build process. - - - - - daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00 JS: correctly handle RUBBISH literals (#24664) - - - - - 8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00 Linearise ghc-internal and base build This is achieved by requesting the final package database for ghc-internal, which mandates it is fully built as a dependency of configuring the `base` package. This is at the expense of cross-package parrallelism between ghc-internal and the base package. Fixes #24436 - - - - - 94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00 Fix tuple puns renaming (24702) Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module. I also fixed some hidden bugs that raised after the change was done. - - - - - fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00 Refactor the Binary serialisation interface The goal is simplifiy adding deduplication tables to `ModIface` interface serialisation. We identify two main points of interest that make this difficult: 1. UserData hardcodes what `Binary` instances can have deduplication tables. Moreover, it heavily uses partial functions. 2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and 'FastString', making it difficult to add more deduplication. Instead of having a single `UserData` record with fields for all the types that can have deduplication tables, we allow to provide custom serialisers for any `Typeable`. These are wrapped in existentials and stored in a `Map` indexed by their respective `TypeRep`. The `Binary` instance of the type to deduplicate still needs to explicitly look up the decoder via `findUserDataReader` and `findUserDataWriter`, which is no worse than the status-quo. `Map` was chosen as microbenchmarks indicate it is the fastest for a small number of keys (< 10). To generalise the deduplication table serialisation mechanism, we introduce the types `ReaderTable` and `WriterTable` which provide a simple interface that is sufficient to implement a general purpose deduplication mechanism for `writeBinIface` and `readBinIface`. This allows us to provide a list of deduplication tables for serialisation that can be extended more easily, for example for `IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for more motivation. In addition to this refactoring, we split `UserData` into `ReaderUserData` and `WriterUserData`, to avoid partial functions and reduce overall memory usage, as we need fewer mutable variables. Bump haddock submodule to accomodate for `UserData` split. ------------------------- Metric Increase: MultiLayerModulesTH_Make MultiLayerModulesRecomp T21839c ------------------------- - - - - - bac57298 by Fendor at 2024-04-26T18:03:13-04:00 Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle` A `BinHandle` contains too much information for reading data. For example, it needs to keep a `FastMutInt` and a `IORef BinData`, when the non-mutable variants would suffice. Additionally, this change has the benefit that anyone can immediately tell whether the `BinHandle` is used for reading or writing. Bump haddock submodule BinHandle split. - - - - - 4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00 Fix missing escaping-kind check in tcPatSynSig Note [Escaping kind in type signatures] explains how we deal with escaping kinds in type signatures, e.g. f :: forall r (a :: TYPE r). a where the kind of the body is (TYPE r), but `r` is not in scope outside the forall-type. I had missed this subtlety in tcPatSynSig, leading to #24686. This MR fixes it; and a similar bug in tc_top_lhs_type. (The latter is tested by T24686a.) - - - - - 981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00 EPA: check-exact: check that the roundtrip reproduces the source Closes #24670 - - - - - a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00 Document that setEnv is not thread-safe - - - - - 1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00 CI: Work around frequent Signal 9 errors - - - - - a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00 ghc-internal: add MonadFix instance for (,) Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC proposal https://github.com/haskell/core-libraries-committee/issues/238. Adds a MonadFix instance for tuples, permitting value recursion in the "native" writer monad and bringing consistency with the existing instance for transformers's WriterT (and, to a lesser extent, for Solo). - - - - - 64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00 bindist: Fix xattr cleaning The original fix (725343aa) was incorrect because it used the shell bracket syntax which is the quoting syntax in autoconf, making the test for existence be incorrect and therefore `xattr` was never run. Fixes #24554 - - - - - e2094df3 by damhiya at 2024-04-28T23:52:00+09:00 Make read accepts binary integer formats CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177 - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - 1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00 EPA: Preserve comments in Match Pats Closes #24708 Closes #24715 Closes #24734 - - - - - 4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00 LLVM: better unreachable default destination in Switch (#24717) See added note. Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com> - - - - - a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00 ci: enable wasm jobs for MRs with wasm label This patch enables wasm jobs for MRs with wasm label. Previously the wasm label didn't actually have any effect on the CI pipeline, and full-ci needed to be applied to run wasm jobs which was a waste of runners when working on the wasm backend, hence the fix here. - - - - - 702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00 Make interface files and object files depend on inplace .conf file A potential fix for #24737 - - - - - 728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00 utils: remove obsolete vagrant scripts Vagrantfile has long been removed in !5288. This commit further removes the obsolete vagrant scripts in the tree. - - - - - 36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00 Update autoconf scripts Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02 - - - - - ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00 ghcup-metadata: Drop output_name field This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00 testsuite: Handle exceptions in framework_fail when testdir is not initialised When `framework_fail` is called before initialising testdir, it would fail with an exception reporting the testdir not being initialised instead of the actual failure. Ensure we report the actual reason for the failure instead of failing in this way. One way this can manifest is when trying to run a test that doesn't exist using `--only` - - - - - d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00 EPA: Fix range for GADT decl with sig only Closes #24714 - - - - - 4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00 Fix TH dependencies (#22229) Add a dependency between Syntax and Internal (via module reexport). - - - - - 37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00 Bump haddock submodule - - - - - ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00 JS: cleanup to prepare for #24743 - - - - - 40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00 EPA: Preserve comments for PrefixCon Preserve comments in fun (Con {- c1 -} a b) = undefined Closes #24736 - - - - - 92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00 Correct `@since` metadata in HpcFlags It was introduced in base-4.20, not 4.22. Fix #24721 - - - - - a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00 testsuite: fix req_target_smp predicate - - - - - ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Remove (unused)coarse grained locking. The STM code had a coarse grained locking mode guarded by #defines that was unused. This commit removes the code. - - - - - 917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Be more optimistic when validating in-flight transactions. * Don't lock tvars when performing non-committal validation. * If we encounter a locked tvar don't consider it a failure. This means in-flight validation will only fail if committing at the moment of validation is *guaranteed* to fail. This prevents in-flight validation from failing spuriously if it happens in parallel on multiple threads or parallel to thread comitting. - - - - - 167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00 EPA: fix span for empty \case(s) In instance SDecide Nat where SZero %~ (SSucc _) = Disproved (\case) Ensure the span for the HsLam covers the full construct. Closes #24748 - - - - - 9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00 testsuite: expand size testing infrastructure - closes #24191 - adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so - path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite - adds on_windows and req_dynamic_ghc predicate to testsuite The design is to not make the testsuite too smart and simply offload to ghc-pkg for locations of object files and directories. - - - - - b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00 GHCi: support inlining breakpoints (#24712) When a breakpoint is inlined, its context may change (e.g. tyvars in scope). We must take this into account and not used the breakpoint tick index as its sole identifier. Each instance of a breakpoint (even with the same tick index) now gets a different "info" index. We also need to distinguish modules: - tick module: module with the break array (tick counters, status, etc.) - info module: module having the CgBreakInfo (info at occurrence site) - - - - - 649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00 Expose constructors of SNat, SChar and SSymbol in ghc-internal - - - - - d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00 Add DCoVarSet to PluginProv (!12037) - - - - - ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00 JS: Enable more efficient packing of string data (fixes #24706) - - - - - be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! - - - - - 58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code - - - - - 70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add comments to Prep.hs This documentation patch fixes a TODO left over from !12364 - - - - - e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Use HasDebugCallStack, rather than HasCallStack - - - - - 631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ - - - - - 1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump time submodule to 1.14 As requested in #24528. ------------------------- Metric Decrease: ghc_bignum_so rts_so Metric Increase: cabal_syntax_dir rts_so time_dir time_so ------------------------- - - - - - 4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump terminfo submodule to current master - - - - - 43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00 wasm: use scheduler.postTask() for context switch when available This patch makes use of scheduler.postTask() for JSFFI context switch when it's available. It's a more principled approach than our MessageChannel based setImmediate() implementation, and it's available in latest version of Chromium based browsers. - - - - - 08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00 testsuite: give pre_cmd for mhu-perf 5x time - - - - - bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00 EPA: Preserve comments for pattern synonym sig Closes #24749 - - - - - c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00 tests: Widen acceptance window for dir and so size tests These are testing things which are sometimes out the control of a GHC developer. Therefore we shouldn't fail CI if something about these dependencies change because we can't do anything about it. It is still useful to have these statistics for visualisation in grafana though. Ticket #24759 - - - - - 9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00 Disable rts_so test It has already manifested large fluctuations and destabilising CI Fixes #24762 - - - - - fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 - - - - - 06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00 doc: Fix type error in hs_try_putmvar example - - - - - af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00 Fix parsing of module names in CLI arguments closes issue #24732 - - - - - da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00 ghc-platform: Add Setup.hs The Hadrian bootstrapping script relies upon `Setup.hs` to drive its build. Addresses #24761. - - - - - 35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 - - - - - 03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00 Fix a float-out error Ticket #24768 showed that the Simplifier was accidentally destroying a join point. It turned out to be that we were sending a bottoming join point to the top, accidentally abstracting over /other/ join points. Easily fixed. - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan HrÄek at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan HrÄek at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan HrÄek at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan HrÄek at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan HrÄek at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan HrÄek at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan HrÄek at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` 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 - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules 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 - - - - - 24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR 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 - - - - - 04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00 Fix untouchability test 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. - - - - - 9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00 Fix demand signatures for join points 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. - - - - - 5e8faaf1 by Jan HrÄek at 2024-06-20T07:23:20-04:00 Update haddocks of Import/Export AST types - - - - - cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - 8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00 cmm: Don't parse MO_BSwap for W8 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 - - - - - 5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - 7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00 Remove left over debugging pragma from 2016 This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147 The top-level cost centres lead to a lack of optimisation when compiling with profiling. - - - - - c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00 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 - - - - - 8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 Add test case for #23586 - - - - - 568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 When matching functions in rewrite rules: ignore multiplicity 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. - - - - - c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00 Faster type equality 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 - - - - - 21fc180b by Ryan Hendrickson at 2024-06-22T10:40:55-04:00 base: Add inits1 and tails1 to Data.List - - - - - d640a3b6 by Sebastian Graf at 2024-06-22T10:41:32-04:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 33fee6a2 by Sebastian Graf at 2024-06-22T10:41:32-04:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) 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 - - - - - 383c01a8 by Matthew Pickering at 2024-06-22T10:42:08-04:00 bindist: Use complete relative paths when cding to directories 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 - - - - - 5759133f by Hécate Kleidukos at 2024-06-22T10:42:49-04:00 haddock: Use the more precise SDocContext instead of DynFlags 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 - - - - - 749e089b by Alexander McKenna at 2024-06-22T10:43:24-04:00 Add INLINE [1] pragma to compareInt / compareWord 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 https://gitlab.haskell.org/ghc/ghc/-/issues/22643 - - - - - db033639 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00 ci: Enable strict ghc-toolchain setting for bindists - - - - - 14308a8f by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00 ghc-toolchain: Improve parse failure error Improves the error message for when `ghc-toolchain` fails to read a valid `Target` value from a file (in doFormat mode). - - - - - 6e7cfff1 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00 bindist: ghc-toolchain related options in configure - - - - - 958d6931 by Matthew Pickering at 2024-06-24T17:21:15-04:00 ci: Fail when bindist configure fails when installing bindist It is better to fail earlier if the configure step fails rather than carrying on for a more obscure error message. - - - - - f48d157d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00 ghc-toolchain: Fix error logging indentation - - - - - f1397104 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00 bindist: Correct default.target substitution The substitution on `default.target.in` must be done after `PREP_TARGET_FILE` is called -- that macro is responsible for setting the variables that will be effectively substituted in the target file. Otherwise, the target file is invalid. Fixes #24792 #24574 - - - - - 665e653e by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00 configure: Prefer tool name over tool path 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 bd92182cd56140ffb2f68ec01492e5aa6333a8fc because `AC_CHECK_TOOL` still takes into account the target triples, unlike `AC_CHECK_PROG/AC_PATH_PROG`. - - - - - 463716c2 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00 dist: Don't forget to configure JavascriptCPP 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. - - - - - e99cd73d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00 distrib: LlvmTarget in distrib/configure 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). - - - - - 4199aafe by Matthew Pickering at 2024-06-24T17:21:51-04:00 Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10) - - - - - f599d816 by Matthew Pickering at 2024-06-24T17:21:51-04:00 ci: Add 9_10 bootstrap testing job - - - - - 8f4b799d by Hécate Kleidukos at 2024-06-24T17:22:30-04:00 haddock: Move the usage of mkParserOpts directly to ppHyperlinkedModuleSource in order to avoid passing a whole DynFlags Follow up to !12931 - - - - - 210cf1cd by Hécate Kleidukos at 2024-06-24T17:22:30-04:00 haddock: Remove cabal file linting rule This will be reintroduced with a properly ignored commit when the cabal files are themselves formatted for good. - - - - - 7fe85b13 by Peter Trommler at 2024-06-24T22:03:41-04:00 PPC NCG: Fix sign hints in C calls Sign hints for parameters are in the second component of the pair. Fixes #23034 - - - - - 949a0e0b by Andrew Lelechenko at 2024-06-24T22:04:17-04:00 base: fix missing changelog entries - - - - - 1bfa9111 by Andreas Klebinger at 2024-06-26T21:49:53-04:00 GHCi interpreter: Tag constructor closures when possible. 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. - - - - - caf44a2d by Andrew Lelechenko at 2024-06-26T21:50:30-04:00 Implement Data.List.compareLength and Data.List.NonEmpty.compareLength `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 - - - - - f4606ae0 by Serge S. Gulin at 2024-06-26T21:51:05-04:00 Unicode: adding compact version of GeneralCategory (resolves #24789) 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 ------------------------- - - - - - 0e424304 by Hécate Kleidukos at 2024-06-26T21:51:44-04:00 haddock: Restructure import statements 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. - - - - - 9b8ddaaf by Arnaud Spiwack at 2024-06-26T21:52:23-04:00 Rename test for #24725 I must have fumbled my tabs when I copy/pasted the issue number in 8c87d4e1136ae6d28e92b8af31d78ed66224ee16. - - - - - b0944623 by Arnaud Spiwack at 2024-06-26T21:52:23-04:00 Add original reproducer for #24725 - - - - - 77ce65a5 by Matthew Pickering at 2024-06-27T07:57:14-04:00 Expand LLVM version matching regex for compability with bsd systems 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 - - - - - bdfe4a9e by Matthew Pickering at 2024-06-27T07:57:14-04:00 ci: On darwin configure LLVMAS linker to match LLC and OPT toolchain The version check was previously broken so the toolchain was not detected at all. - - - - - 07e03a69 by Matthew Pickering at 2024-06-27T07:57:15-04:00 Update nixpkgs commit for darwin toolchain One dependency (c-ares) changed where it hosted the releases which breaks the build with the old nixpkgs commit. - - - - - 144afed7 by Rodrigo Mesquita at 2024-06-27T07:57:50-04:00 base: Add changelog entry for #24998 - - - - - eebe1658 by Sylvain Henry at 2024-06-28T07:13:26-04:00 X86/DWARF: support no tables-next-to-code and asm-shortcutting (#22792) - 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. - - - - - 6e86d82b by Sylvain Henry at 2024-06-28T07:14:06-04:00 PPC NCG: handle JMP to ForeignLabels (#23969) - - - - - 9e4b4b0a by Sylvain Henry at 2024-06-28T07:14:06-04:00 PPC NCG: support loading 64-bit value on 32-bit arch (#23969) - - - - - 50caef3e by Sylvain Henry at 2024-06-28T07:14:46-04:00 Fix warnings in genapply - - - - - 37139b17 by Matthew Pickering at 2024-06-28T07:15:21-04:00 libraries: Update os-string to 2.0.4 This updates the os-string submodule to 2.0.4 which removes the usage of `TemplateHaskell` pragma. - - - - - 0f3d3bd6 by Sylvain Henry at 2024-06-30T00:47:40-04:00 Bump array submodule - - - - - 354c350c by Sylvain Henry at 2024-06-30T00:47:40-04:00 GHCi: Don't use deprecated sizeofMutableByteArray# - - - - - 35d65098 by Ben Gamari at 2024-06-30T00:47:40-04:00 primops: Undeprecate addr2Int# and int2Addr# addr2Int# and int2Addr# were marked as deprecated with the introduction of the OCaml code generator (1dfaee318171836b32f6b33a14231c69adfdef2f) due to its use of tagged integers. However, this backend has long vanished and `base` has all along been using `addr2Int#` in the Show instance for Ptr. While it's unlikely that we will have another backend which has tagged integers, we may indeed support platforms which have tagged pointers. Consequently we undeprecate the operations but warn the user that the operations may not be portable. - - - - - 3157d817 by Sylvain Henry at 2024-06-30T00:47:41-04:00 primops: Undeprecate par# par# is still used in base and it's not clear how to replace it with spark# (see #24825) - - - - - c8d5b959 by Ben Gamari at 2024-06-30T00:47:41-04:00 Primops: Make documentation generation more efficient Previously we would do a linear search through all primop names, doing a String comparison on the name of each when preparing the HsDocStringMap. Fix this. - - - - - 65165fe4 by Ben Gamari at 2024-06-30T00:47:41-04:00 primops: Ensure that deprecations are properly tracked We previously failed to insert DEPRECATION pragmas into GHC.Prim's ModIface, meaning that they would appear in the Haddock documentation but not issue warnings. Fix this. See #19629. Haddock also needs to be fixed: https://github.com/haskell/haddock/issues/223 Co-authored-by: Sylvain Henry <sylvain at haskus.fr> - - - - - bc1d435e by Mario Blažević at 2024-06-30T00:48:20-04:00 Improved pretty-printing of unboxed TH sums and tuples, fixes #24997 - - - - - 0d170eaf by Zubin Duggal at 2024-07-04T11:08:41-04:00 compiler: Turn `FinderCache` into a record of operations so that GHC API clients can have full control over how its state is managed by overriding `hsc_FC`. Also removes the `uncacheModule` function as this wasn't being used by anything since 1893ba12fe1fa2ade35a62c336594afcd569736e Fixes #23604 - - - - - 4664997d by Teo Camarasu at 2024-07-04T11:09:18-04:00 Add HasCallStack to T23221 This makes the test a bit easier to debug - - - - - 66919dcc by Teo Camarasu at 2024-07-04T11:09:18-04:00 rts: use live words to estimate heap size We use live words rather than live blocks to determine the size of the heap for determining memory retention. Most of the time these two metrics align, but they can come apart in normal usage when using the nonmoving collector. The nonmoving collector leads to a lot of partially occupied blocks. So, using live words is more accurate. They can also come apart when the heap is suffering from high levels fragmentation caused by small pinned objects, but in this case, the block size is the more accurate metric. Since this case is best avoided anyway. It is ok to accept the trade-off that we might try (and probably) fail to return more memory in this case. See also the Note [Statistics for retaining memory] Resolves #23397 - - - - - 8dfca66a by Oleg Grenrus at 2024-07-04T11:09:55-04:00 Add reflections of GHC.TypeLits/Nats type families ------------------------- Metric Increase: ghc_experimental_dir ghc_experimental_so ------------------------- - - - - - 6c469bd2 by Adam Gundry at 2024-07-04T11:10:33-04:00 Correct -Wpartial-fields warning to say "Definition" rather than "Use" Fixes #24710. The message and documentation for `-Wpartial-fields` were misleading as (a) the warning occurs at definition sites rather than use sites, and (b) the warning relates to the definition of a field independently of the selector function (e.g. because record updates are also partial). - - - - - 977b6b64 by Max Ulidtko at 2024-07-04T11:11:11-04:00 GHCi: Support local Prelude Fixes #10920, an issue where GHCi bails out when started alongside a file named Prelude.hs or Prelude.lhs (even empty file suffices). The in-source Note [GHCi and local Preludes] documents core reasoning. Supplementary changes: * add debug traces for module lookups under -ddump-if-trace; * drop stale comment in GHC.Iface.Load; * reduce noise in -v3 traces from GHC.Utils.TmpFs; * new test, which also exercizes HomeModError. - - - - - 87cf4111 by Ryan Scott at 2024-07-04T11:11:47-04:00 Add missing gParPat in cvtp's ViewP case When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern is parenthesized so that the resulting code will parse correctly when roundtripped back through GHC's parser. Fixes #24894. - - - - - b05613c5 by Adam Gundry at 2024-07-04T11:12:23-04:00 Use structured error representation for module cycle errors (see #18516) This removes the re-export of cyclicModuleErr from the top-level GHC module. - - - - - 70389749 by Adam Gundry at 2024-07-04T11:12:23-04:00 Use structured error representation when reloading a nonexistent module - - - - - 680ade3d by sheaf at 2024-07-04T11:12:23-04:00 Use structured errors for a Backpack instantiation error - - - - - 97c6d6de by sheaf at 2024-07-04T11:12:23-04:00 Move mkFileSrcSpan to GHC.Unit.Module.Location - - - - - f9e7bd9b by Adriaan Leijnse at 2024-07-04T11:12:59-04:00 ttg: Remove SourceText from OverloadedLabel Progress towards #21592 - - - - - 00d63245 by Alexander Foremny at 2024-07-04T11:12:59-04:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - cc846ea5 by Alexander Foremny at 2024-07-04T11:12:59-04:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - 24c7d287 by Fabian Kirchner at 2024-07-04T11:12:59-04:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - 6cbba381 by Fabian Kirchner at 2024-07-04T11:12:59-04:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - 611aa7c6 by Fabian Kirchner at 2024-07-04T11:12:59-04:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - 1b968d16 by Mauricio at 2024-07-04T11:12:59-04:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - 3d192e5d by Fabian Kirchner at 2024-07-04T11:12:59-04:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 257d1adc by Adowrath at 2024-07-04T11:12:59-04:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 24757fec by Mauricio at 2024-07-04T11:12:59-04:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 9be49379 by Mike Pilgrem at 2024-07-04T11:13:41-04:00 Fix #25032 Refer to Cabal's `includes` field, not `include-files` - - - - - 9e2ecf14 by Andrew Lelechenko at 2024-07-04T11:14:17-04:00 base: fix more missing changelog entries - - - - - a82121b3 by Peter Trommler at 2024-07-04T11:14:53-04:00 X86 NCG: Fix argument promotion in foreign C calls Promote 8 bit and 16 bit signed arguments by sign extension. Fixes #25018 - - - - - fab13100 by Bryan Richter at 2024-07-04T11:15:29-04:00 Add .gitlab/README.md with creds instructions - - - - - 564981bd by Matthew Pickering at 2024-07-05T07:35:29-04:00 configure: Set LD_STAGE0 appropiately when 9.10.1 is used as a boot compiler In 9.10.1 the "ld command" has been removed, so we fall back to using the more precise "merge objects command" when it's available as LD_STAGE0 is only used to set the object merging command in hadrian. Fixes #24949 - - - - - a949c792 by Matthew Pickering at 2024-07-05T07:35:29-04:00 hadrian: Don't build ghci object files for ./hadrian/ghci target There is some convoluted logic which determines whether we build ghci object files are not. In any case, if you set `ghcDynPrograms = pure False` then it forces them to be built. Given we aren't ever building executables with this flavour it's fine to leave `ghcDynPrograms` as the default and it should be a bit faster to build less. Also fixes #24949 - - - - - 48bd8f8e by Matthew Pickering at 2024-07-05T07:36:06-04:00 hadrian: Remove STG dump from ticky_ghc flavour transformer This adds 10-15 minutes to build time, it is a better strategy to precisely enable dumps for the modules which show up prominently in a ticky profile. Given I am one of the only people regularly building ticky compilers I think it's worthwhile to remove these. Fixes #23635 - - - - - 5b1aefb7 by Matthew Pickering at 2024-07-05T07:36:06-04:00 hadrian: Add dump_stg flavour transformer This allows you to write `--flavour=default+ticky_ghc+dump_stg` if you really want STG for all modules. - - - - - ab2b60b6 by Sven Tennie at 2024-07-08T15:03:41-04:00 AArch64: Simplify stmtToInstrs type There's no need to hand `Nothing`s around... (there was no case with a `BlockId`.) - - - - - 71a7fa8c by Sven Tennie at 2024-07-08T15:03:41-04:00 AArch64: Simplify stmtsToInstrs type The `BlockId` parameter (`bid`) is never used, only handed around. Deleting it simplifies the surrounding code. - - - - - 8bf6fd68 by Simon Peyton Jones at 2024-07-08T15:04:17-04:00 Fix eta-expansion in Prep As #25033 showed, we were eta-expanding in a way that broke a join point, which messed up Note [CorePrep invariants]. The fix is rather easy. See Wrinkle (EA1) of Note [Eta expansion of arguments in CorePrep] - - - - - 96acf823 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00 One-shot Haddock - - - - - 74ec4c06 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00 Remove haddock-stdout test option Superseded by output handling of Hadrian - - - - - ed8a8f0b by Rodrigo Mesquita at 2024-07-09T06:16:51-04:00 ghc-boot: Relax Cabal bound Fixes #25013 - - - - - 3f9548fe by Matthew Pickering at 2024-07-09T06:17:36-04:00 ci: Unset ALEX/HAPPY variables when testing bootstrap jobs Ticket #24826 reports a regression in 9.10.1 when building from a source distribution. This patch is an attempt to reproduce the issue on CI by more aggressively removing `alex` and `happy` from the environment. - - - - - aba2c9d4 by Andrea Bedini at 2024-07-09T06:17:36-04:00 hadrian: Ignore build-tool-depends fields in cabal files hadrian does not utilise the build-tool-depends fields in cabal files and their presence can cause issues when building source distribution (see #24826) Ideally Cabal would support building "full" source distributions which would remove the need for workarounds in hadrian but for now we can patch the build-tool-depends out of the cabal files. Fixes #24826 - - - - - 12bb9e7b by Matthew Pickering at 2024-07-09T06:18:12-04:00 testsuite: Don't attempt to link when checking whether a way is supported It is sufficient to check that the simple test file compiles as it will fail if there are not the relevant library files for the requested way. If you break a way so badly that even a simple executable fails to link (as I did for profiled dynamic way), it will just mean the tests for that way are skipped on CI rather than displayed. - - - - - 46ec0a8e by Torsten Schmits at 2024-07-09T13:37:02+02:00 Improve docs for NondecreasingIndentation The text stated that this affects indentation of layouts nested in do expressions, while it actually affects that of do layouts nested in any other. - - - - - dddc9dff by Zubin Duggal at 2024-07-12T11:41:24-04:00 compiler: Fingerprint -fwrite-if-simplified-core We need to recompile if this flag is changed because later modules might depend on the simplified core for this module if -fprefer-bytecode is enabled. Fixes #24656 - - - - - 145a6477 by Matthew Pickering at 2024-07-12T11:42:00-04:00 Add support for building profiled dynamic way The main payload of this change is to hadrian. * Default settings will produced dynamic profiled objects * `-fexternal-interpreter` is turned on in some situations when there is an incompatibility between host GHC and the way attempting to be built. * Very few changes actually needed to GHC There are also necessary changes to the bootstrap plans to work with the vendored Cabal dependency. These changes should ideally be reverted by the next GHC release. In hadrian support is added for building profiled dynamic libraries (nothing too exciting to see there) Updates hadrian to use a vendored Cabal submodule, it is important that we replace this usage with a released version of Cabal library before the 9.12 release. Fixes #21594 ------------------------- Metric Increase: libdir ------------------------- - - - - - 414a6950 by Matthew Pickering at 2024-07-12T11:42:00-04:00 testsuite: Make find_so regex more precise The hash contains lowercase [a-z0-9] and crucially not _p which meant we sometimes matched on `libHS.._p` profiled shared libraries rather than the normal shared library. - - - - - dee035bf by Alex Mason at 2024-07-12T11:42:41-04:00 ncg(aarch64): Add fsqrt instruction, byteSwap primitives [#24956] Implements the FSQRT machop using native assembly rather than a C call. Implements MO_BSwap by producing assembly to do the byte swapping instead of producing a foreign call a C function. In `tar`, the hot loop for `deserialise` got almost 4x faster by avoiding the foreign call which caused spilling live variables to the stack -- this means the loop did 4x more memory read/writing than necessary in that particular case! - - - - - 5104ee61 by Sylvain Henry at 2024-07-12T11:43:23-04:00 Linker: use m32 allocator for sections when NEED_PLT (#24432) Use M32 allocator to avoid fragmentation when allocating ELF sections. We already did this when NEED_PLT was undefined. Failing to do this led to relocations impossible to fulfil (#24432). - - - - - 52d66984 by Sylvain Henry at 2024-07-12T11:43:23-04:00 RTS: allow M32 allocation outside of 4GB range when assuming -fPIC - - - - - c34fef56 by Sylvain Henry at 2024-07-12T11:43:23-04:00 Linker: fix stub offset Remove unjustified +8 offset that leads to memory corruption (cf discussion in #24432). - - - - - 280e4bf5 by Simon Peyton Jones at 2024-07-12T11:43:59-04:00 Make type-equality on synonyms a bit faster This MR make equality fast for (S tys1 `eqType` S tys2), where S is a non-forgetful type synonym. It doesn't affect compile-time allocation much, but then comparison doesn't allocate anyway. But it seems like a Good Thing anyway. See Note [Comparing type synonyms] in GHC.Core.TyCo.Compare and Note [Forgetful type synonyms] in GHC.Core.TyCon Addresses #25009. - - - - - cb83c347 by Alan Zimmerman at 2024-07-12T11:44:35-04:00 EPA: Bring back SrcSpan in EpaDelta When processing files in ghc-exactprint, the usual workflow is to first normalise it with makeDeltaAst, and then operate on it. But we need the original locations to operate on it, in terms of finding things. So restore the original SrcSpan for reference in EpaDelta - - - - - 7bcda869 by Matthew Pickering at 2024-07-12T11:45:11-04:00 Update alpine release job to 3.20 alpine 3.20 was recently released and uses a new python and sphinx toolchain which could be useful to test. - - - - - 43aa99b8 by Matthew Pickering at 2024-07-12T11:45:11-04:00 testsuite: workaround bug in python-3.12 There is some unexplained change to binding behaviour in python-3.12 which requires moving this import from the top-level into the scope of the function. I didn't feel any particular desire to do a deep investigation as to why this changed as the code works when modified like this. No one in the python IRC channel seemed to know what the problem was. - - - - - e3914028 by Adam Sandberg Ericsson at 2024-07-12T11:45:47-04:00 initialise mmap_32bit_base during RTS startup #24847 - - - - - 86b8ecee by Hécate Kleidukos at 2024-07-12T11:46:27-04:00 haddock: Only fetch supported languages and extensions once per Interface list This reduces the number of operations done on each Interface, because supported languages and extensions are determined from architecture and operating system of the build host. This information remains stable across Interfaces, and as such doesn not need to be recovered for each Interface. - - - - - 4f85366f by sheaf at 2024-07-13T05:58:14-04:00 Testsuite: use py-cpuinfo to compute CPU features This replaces the rather hacky logic we had in place for checking CPU features. In particular, this means that feature availability now works properly on Windows. - - - - - 41f1354d by Matthew Pickering at 2024-07-13T05:58:51-04:00 testsuite: Replace $CC with $TEST_CC The TEST_CC variable should be set based on the test compiler, which may be different to the compiler which is set to CC on your system (for example when cross compiling). Fixes #24946 - - - - - 572fbc44 by sheaf at 2024-07-15T08:30:32-04:00 isIrrefutableHsPat: consider COMPLETE pragmas This patch ensures we taken into account COMPLETE pragmas when we compute whether a pattern is irrefutable. In particular, if a pattern synonym is the sole member of a COMPLETE pragma (without a result TyCon), then we consider a pattern match on that pattern synonym to be irrefutable. This affects the desugaring of do blocks, as it ensures we don't use a "fail" operation. Fixes #15681 #16618 #22004 - - - - - 84dadea9 by Zubin Duggal at 2024-07-15T08:31:09-04:00 haddock: Handle non-hs files, so that haddock can generate documentation for modules with foreign imports and template haskell. Fixes #24964 - - - - - 0b4ff9fa by Zubin Duggal at 2024-07-15T12:12:30-04:00 haddock: Keep track of warnings/deprecations from dependent packages in `InstalledInterface` and use this to propagate these on items re-exported from dependent packages. Fixes #25037 - - - - - b8b4b212 by Zubin Duggal at 2024-07-15T12:12:30-04:00 haddock: Keep track of instance source locations in `InstalledInterface` and use this to add source locations on out of package instances Fixes #24929 - - - - - 559a7a7c by Matthew Pickering at 2024-07-15T12:13:05-04:00 ci: Refactor job_groups definition, split up by platform The groups are now split up so it's easier to see which jobs are generated for each platform No change in behaviour, just refactoring. - - - - - 20383006 by Matthew Pickering at 2024-07-16T11:48:25+01:00 ci: Replace debian 10 with debian 12 on validation jobs Since debian 10 is now EOL we migrate onwards to debian 12 as the basis for most platform independent validation jobs. - - - - - 12d3b66c by Matthew Pickering at 2024-07-17T13:22:37-04:00 ghcup-metadata: Fix use of arch argument The arch argument was ignored when making the jobname, which lead to failures when generating metadata for the alpine_3_18-aarch64 bindist. Fixes #25089 - - - - - bace981e by Matthew Pickering at 2024-07-19T10:14:02-04:00 testsuite: Delay querying ghc-pkg to find .so dirs until test is run The tests which relied on find_so would fail when `test` was run before the tree was built. This was because `find_so` was evaluated too eagerly. We can fix this by waiting to query the location of the libraries until after the compiler has built them. - - - - - 478de1ab by Torsten Schmits at 2024-07-19T10:14:37-04:00 Add `complete` pragmas for backwards compat patsyns `ModLocation` and `ModIface` !12347 and !12582 introduced breaking changes to these two constructors and mitigated that with pattern synonyms. - - - - - b57792a8 by Matthew Pickering at 2024-07-19T10:15:13-04:00 ci: Fix ghcup-metadata generation (again) I made some mistakes in 203830065b81fe29003c1640a354f11661ffc604 * Syntax error * The aarch-deb11 bindist doesn't exist I tested against the latest nightly pipeline locally: ``` nix run .gitlab/generate-ci#generate-job-metadata nix shell -f .gitlab/rel_eng/ -c ghcup-metadata --pipeline-id 98286 --version 9.11.20240715 --fragment --date 2024-07-17 --metadata=/tmp/meta ``` - - - - - 1fa35b64 by Andreas Klebinger at 2024-07-19T17:35:20+02:00 Revert "Allow non-absolute values for bootstrap GHC variable" This broke configure in subtle ways resulting in #25076 where hadrian didn't end up the boot compiler it was configured to use. This reverts commit 209d09f52363b261b900cf042934ae1e81e2caa7. - - - - - 55117e13 by Simon Peyton Jones at 2024-07-24T02:41:12-04:00 Fix bad bug in mkSynonymTyCon, re forgetfulness As #25094 showed, the previous tests for forgetfulness was plain wrong, when there was a forgetful synonym in the RHS of a synonym. - - - - - a8362630 by Sergey Vinokurov at 2024-07-24T12:22:45-04:00 Define Eq1, Ord1, Show1 and Read1 instances for basic Generic representation types This way the Generically1 newtype could be used to derive Eq1 and Ord1 for user types with DerivingVia. The CLC proposal is https://github.com/haskell/core-libraries-committee/issues/273. The GHC issue is https://gitlab.haskell.org/ghc/ghc/-/issues/24312. - - - - - de5d9852 by Simon Peyton Jones at 2024-07-24T12:23:22-04:00 Address #25055, by disabling case-of-runRW# in Gentle phase See Note [Case-of-case and full laziness] in GHC.Driver.Config.Core.Opt.Simplify - - - - - 3f89ab92 by Andreas Klebinger at 2024-07-25T14:12:54+02:00 Fix -freg-graphs for FP and AARch64 NCG (#24941). It seems we reserve 8 registers instead of four for global regs based on the layout in Note [AArch64 Register assignments]. I'm not sure it's neccesary, but for now we just accept this state of affairs and simple update -fregs-graph to account for this. - - - - - f6b4c1c9 by Simon Peyton Jones at 2024-07-27T09:45:44-04:00 Fix nasty bug in occurrence analyser As #25096 showed, the occurrence analyser was getting one-shot info flat out wrong. This commit does two things: * It fixes the bug and actually makes the code a bit tidier too. The work is done in the new function GHC.Core.Opt.OccurAnal.mkRhsOccEnv, especially the bit that prepares the `occ_one_shots` for the RHS. See Note [The OccEnv for a right hand side] * When floating out a binding we must be conservative about one-shot info. But we were zapping the entire demand info, whereas we only really need zap the /top level/ cardinality. See Note [Floatifying demand info when floating] in GHC.Core.Opt.SetLevels For some reason there is a 2.2% improvement in compile-time allocation for CoOpt_Read. Otherwise nickels and dimes. Metric Decrease: CoOpt_Read - - - - - 646ee207 by Torsten Schmits at 2024-07-27T09:46:20-04:00 add missing cell in flavours table - - - - - ec2eafdb by Ben Gamari at 2024-07-28T20:51:12+02:00 users-guide: Drop mention of dead __PARALLEL_HASKELL__ macro This has not existed for over a decade. - - - - - e2f2a56e by Arnaud Spiwack at 2024-07-28T22:21:07-04:00 Add tests for 25081 - - - - - 23f50640 by Arnaud Spiwack at 2024-07-28T22:21:07-04:00 Scale multiplicity in list comprehension Fixes #25081 - - - - - d2648289 by romes at 2024-07-30T01:38:12-04:00 TTG HsCmdArrForm: use Fixity via extension point Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax since it no longer uses any GHC-specific data types. Fixed arrow desugaring bug. (This was dead code before.) Remove mkOpFormRn, it is also dead code, only used in the arrow desugaring now removed. Co-authored-by: Fabian Kirchner <kirchner at posteo.de> Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - e258ad54 by Matthew Pickering at 2024-07-30T01:38:48-04:00 ghcup-metadata: More metadata fixes * Incorrect version range on the alpine bindists * Missing underscore in "unknown_versioning" Fixes #25119 - - - - - 72b54c07 by Rodrigo Mesquita at 2024-08-01T00:47:29-04:00 Deriving-via one-shot strict state Monad instances A small refactor to use deriving via GHC.Utils.Monad.State.Strict Monad instances for state Monads with unboxed/strict results which all re-implemented the one-shot trick in the instance and used unboxed tuples: * CmmOptM in GHC.Cmm.GenericOpt * RegM in GHC.CmmToAsm.Reg.Linear.State * UniqSM in GHC.Types.Unique.Supply - - - - - bfe4b3d3 by doyougnu at 2024-08-01T00:48:06-04:00 Rts linker: add case for pc-rel 64 relocation part of the upstream haskell.nix patches - - - - - 5843c7e3 by doyougnu at 2024-08-01T00:48:42-04:00 RTS linker: aarch64: better debug information Dump better debugging information when a symbol address is null. Part of the haskell.nix patches upstream project Co-authored-by: Sylvain Henry <sylvain at haskus.fr> - - - - - c2e9c581 by Rodrigo Mesquita at 2024-08-01T00:49:18-04:00 base: Add haddocks to HasExceptionContext Fixes #25091 - - - - - f954f428 by Sylvain Henry at 2024-08-01T00:49:59-04:00 Only lookup ghcversion.h file in the RTS include-dirs by default. The code was introduced in 3549c952b535803270872adaf87262f2df0295a4. It used `getPackageIncludePath` which name doesn't convey that it looks into all include paths of the preload units too. So this behavior is probably unintentional and it should be ok to change it. Fix #25106 - - - - - 951ce3d5 by Matthew Pickering at 2024-08-01T00:50:35-04:00 driver: Fix -Wmissing-home-modules when multiple units have the same module name It was assumed that module names were unique but that isn't true with multiple units. The fix is quite simple, maintain a set of `(ModuleName, UnitId)` and query that to see whether the module has been specified. Fixes #25122 - - - - - bae1fea4 by sheaf at 2024-08-01T00:51:15-04:00 PMC: suggest in-scope COMPLETE sets when possible This commit modifies GHC.HsToCore.Pmc.Solver.generateInhabitingPatterns to prioritise reporting COMPLETE sets in which all of the ConLikes are in scope. This avoids suggesting out of scope constructors when displaying an incomplete pattern match warning, e.g. in baz :: Ordering -> Int baz = \case EQ -> 5 we prefer: Patterns of type 'Ordering' not matched: LT GT over: Patterns of type 'Ordering' not matched: OutOfScope Fixes #25115 - - - - - ff158fcd by Tommy Bidne at 2024-08-02T01:14:32+12:00 Print exception metadata in default handler CLC proposals 231 and 261: - Add exception type metadata to SomeException's displayException. - Add "Exception" header to default exception handler. See: https://github.com/haskell/core-libraries-committee/issues/231 https://github.com/haskell/core-libraries-committee/issues/261 Update stm submodule for test fixes. - - - - - 8b2f70a2 by Andrei Borzenkov at 2024-08-01T23:00:46-04:00 Type syntax in expressions (#24159, #24572, #24226) This patch extends the grammar of expressions with syntax that is typically found only in types: * function types (a -> b), (a ->. b), (a %m -> b) * constrained types (ctx => t) * forall-quantification (forall tvs. t) The new forms are guarded behind the RequiredTypeArguments extension, as specified in GHC Proposal #281. Examples: {-# LANGUAGE RequiredTypeArguments #-} e1 = f (Int -> String) -- function type e2 = f (Int %1 -> String) -- linear function type e3 = f (forall a. Bounded a => a) -- forall type, constraint The GHC AST and the TH AST have been extended as follows: syntax | HsExpr | TH.Exp ---------------+----------+-------------- a -> b | HsFunArr | ConE (->) a %m -> b | HsFunArr | ConE FUN ctx => t | HsQual | ConstrainedE forall a. t | HsForAll | ForallE forall a -> t | HsForAll | ForallVisE Additionally, a new warning flag -Wview-pattern-signatures has been introduced to aid with migration to the new precedence of (e -> p :: t). Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com> - - - - - 66e7f57d by Brandon Chinn at 2024-08-01T21:50:58-07:00 Implement MultilineStrings (#24390) This commit adds support for multiline strings, proposed at https://github.com/ghc-proposals/ghc-proposals/pull/569. Multiline strings can now be written as: myString = """ this is a multiline string """ The multiline string will have leading indentation stripped away. Full details of this post-processing may be found at the new GHC.Parser.String module. In order to cleanly implement this and maximize reusability, I broke out the lexing logic for strings out of Lexer.x into a new GHC.Parser.String module, which lexes strings with any provided "get next character" function. This also gave us the opportunity to clean up this logic, and even optimize it a bit. With this change, parsing string literals now takes 25% less time and 25% less space. - - - - - cf47b96f by Rodrigo Mesquita at 2024-08-03T05:59:40-04:00 hi: Stable sort avails Sorting the Avails in DocStructures is required to produce fully deterministic interface files in presence of re-exported modules. Fixes #25104 - - - - - af2ae742 by M. Taimoor Zaeem at 2024-08-03T18:52:50+05:00 haddock: decrease margin on top of small headings - - - - - a1e42e7a by Rodrigo Mesquita at 2024-08-05T21:03:04-04:00 hi: Deterministic ImportedMods in Usages The `mi_usages` field of the interface files must use a deterministic list of `Usage`s to guarantee a deterministic interface. However, this list was, in its origins, constructed from a `ModuleEnv` which uses a non-deterministic ordering that was leaking into the interface. Specifically, ImportedMods = ModuleEnv ... would get converted to a list and then passed to `mkUsageInfo` to construct the Usages. The solution is simple. Back `ImportedMods` with a deterministic map. `Map Module ...` is enough, since the Ord instance for `Module` already uses a stable, deterministic, comparison. Fixes #25131 - - - - - eb1cb536 by Serge S. Gulin at 2024-08-06T08:54:55+00:00 testsuite: extend size performance tests with gzip (fixes #25046) The main purpose is to create tests for minimal app (hello world and its variations, i.e. unicode used) distribution size metric. Many platforms support distribution in compressed form via gzip. It would be nice to collect information on how much size is taken by the executional bundle for each platform at minimal edge case. 2 groups of tests are added: 1. We extend javascript backend size tests with gzip-enabled versions for all cases where an optimizing compiler is used (for now it is google closure compiler). 2. We add trivial hello world tests with gzip-enabled versions for all other platforms at CI pipeline where no external optimizing compiler is used. - - - - - d94410f8 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00 ghc-internal: @since for backtraceDesired Fixes point 1 in #25052 - - - - - bfe600f5 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00 ghc-internal: No trailing whitespace in exceptions Fixes #25052 - - - - - 62650d9f by Andreas Klebinger at 2024-08-07T11:49:54-04:00 Add since annotation for -fkeep-auto-rules. This partially addresses #25082. - - - - - 5f0e23fd by Andreas Klebinger at 2024-08-07T11:49:54-04:00 Mention `-fkeep-auto-rules` in release notes. It was added earlier but hadn't appeared in any release notes yet. Partially addresses #25082. - - - - - 7446a09a by Sylvain Henry at 2024-08-07T11:50:35-04:00 Cmm: don't perform unsound optimizations on 32-bit compiler hosts - beef61351b240967b49169d27a9a19565cf3c4af enabled the use of MO_Add/MO_Sub for 64-bit operations in the C and LLVM backends - 6755d833af8c21bbad6585144b10e20ac4a0a1ab did the same for the x86 NCG backend However we store some literal values as `Int` in the compiler. As a result, some Cmm optimizations transformed target 64-bit literals into compiler `Int`. If the compiler is 32-bit, this leads to computing with wrong literals (see #24893 and #24700). This patch disables these Cmm optimizations for 32-bit compilers. This is unsatisfying (optimizations shouldn't be compiler-word-size dependent) but it fixes the bug and it makes the patch easy to backport. A proper fix would be much more invasive but it shall be implemented in the future. Co-authored-by: amesgen <amesgen at amesgen.de> - - - - - d59faaf2 by Vladislav Zavialov at 2024-08-07T11:51:11-04:00 docs: Update info on RequiredTypeArguments Add a section on "types in terms" that were implemented in 8b2f70a202 and remove the now outdated suggestion of using `type` for them. - - - - - 39fd6714 by Sylvain Henry at 2024-08-07T11:51:52-04:00 JS: fix minor typo in base's jsbits - - - - - e7764575 by Sylvain Henry at 2024-08-07T11:51:52-04:00 RTS: remove hack to force old cabal to build a library with only JS sources Need to extend JSC externs with Emscripten RTS definitions to avoid JSC_UNDEFINED_VARIABLE errors when linking without the emcc rts. Fix #25138 Some recompilation avoidance tests now fail. This is tracked with the other instances of this failure in #23013. My hunch is that they were working by chance when we used the emcc linker. Metric Decrease: T24602_perf_size - - - - - d1a40233 by Brandon Chinn at 2024-08-07T11:53:08-04:00 Support multiline strings in type literals (#25132) - - - - - 610840eb by Sylvain Henry at 2024-08-07T11:53:50-04:00 JS: fix callback documentation (#24377) Fix #24377 - - - - - 6ae4b76a by Zubin Duggal at 2024-08-13T13:36:57-04:00 haddock: Build haddock-api and haddock-library using hadrian We build these two packages as regular boot library dependencies rather than using the `in-ghc-tree` flag to include the source files into the haddock executable. The `in-ghc-tree` flag is moved into haddock-api to ensure that haddock built from hackage can still find the location of the GHC bindist using `ghc-paths`. Addresses #24834 This causes a metric decrease under non-release flavours because under these flavours libraries are compiled with optimisation but executables are not. Since we move the bulk of the code from the haddock executable to the haddock-api library, we see a metric decrease on the validate flavours. Metric Decrease: haddock.Cabal haddock.base haddock.compiler - - - - - 51ffba5d by Arnaud Spiwack at 2024-08-13T13:37:50-04:00 Add an extension field to HsRecFields This is the Right Thing to Doâ„¢. And it prepares for storing a multiplicity coercion there. First step of the plan outlined here and below https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12947#note_573091 - - - - - 4d2faeeb by Arnaud Spiwack at 2024-08-13T13:37:50-04:00 Add test for #24961 - - - - - 623b4337 by Arnaud Spiwack at 2024-08-13T13:37:50-04:00 Ensures that omitted record fields in pattern have multiplicity Many Omitted fields were simply ignored in the type checker and produced incorrect Core code. Fixes #24961 Metric Increase: RecordUpdPerf - - - - - c749bdfd by Sylvain Henry at 2024-08-13T13:38:41-04:00 AARCH64 linker: skip NONE relocations This patch is part of the patches upstreamed from haskell.nix. See https://github.com/input-output-hk/haskell.nix/pull/1960 for the original report/patch. - - - - - 682a6a41 by Brandon Chinn at 2024-08-13T13:39:17-04:00 Support multiline strings in TH - - - - - ee0a9c18 by Matthew Pickering at 2024-08-14T14:27:39-04:00 Extend -reexported-module flag to support module renaming The -reexported-module flag now supports renaming -rexported-modules. ``` -rexported-module "A as B" ``` This feature is only relevant to multi-component sessions. Fixes #25139 - - - - - e9496000 by Arnaud Spiwack at 2024-08-14T14:28:20-04:00 Don't restrict eta-reduction of linear functions This commit simply removes code. All the supporting implementation has been done as part of !12883. Closes #25129 - - - - - 2bb4156e by sheaf at 2024-08-14T14:28:56-04:00 Allow @ character in C labels Generated symbol names can include the '@' character, for example when using `__attribute__((vectorcall))`. - - - - - 7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00 Linker: replace blind tuple with a datatype + docs - - - - - bdd77b9e by sheaf at 2024-08-16T12:47:11-04:00 isIrrefutableHsPat: look up ConLikes in the HscEnv At GhcRn stage, in isIrrefutableHsPat we only looked up data constructors in the RdrEnv, which meant that we lacked fallibility information for out-of-scope constructors (which can arise from Template Haskell splices). Instead, we use 'lookupGREInfo', which looks up the information in the type environment. This was the correct function to call all along, but was not used in 572fbc44 due to import cycle reasons. The appropriate functions, 'irrefutableConLike{Rn,Tc}' have been moved to 'GHC.Rename.Env', which avoids import cycles. Fixes #25164 - - - - - 4bee377c by Sylvain Henry at 2024-08-16T12:47:53-04:00 Linker: some refactoring to prepare for #24886 - Rename LoadedBCOs into LazyBCOs - Bundle SptEntries with CompiledByteCode and removed [SptEntry] field from the BCOs constructor - Rename Linkable's LM constructor into Linkable: in the past we had LM and LP for Module and Package, now we only have the former. - Rename Unlinked into LinkablePart (and linkableUnlinked into linkableParts) - Use NonEmpty to encode invariant in Linkable's linkableParts type - Add helpers: linkableLibs, linkableBCOs, etc. - Add documentation - Remove partial nameOfObject - Rename nameOfObject_maybe into linkablePartPath - Rename byteCodeOfObject into linkablePartAllBCOs. - Refactor linkablePartAllBCOs to avoid a panic if a LazyBCO has a C stub. Document the fact that LazyBCOs are returned in this case (contrary to linkableBCOs which only returns non-lazy ones) Refactoring done while trying to understand how to adapt the linker code to support the JS backend too (cf #24886). - - - - - fa0dbaca by Mario Blažević at 2024-08-17T03:31:32+00:00 Implements the Exportable Named Default proposal (#24305) This squashed commit adds support for exportable named defaults, the accepted GHC proposal at https://github.com/ghc-proposals/ghc-proposals/pull/409 The proposal extends the Haskell '98 declarations default (Int, Double) which were implicitly always applying to Num class alone, to allow specifying an arbitrary single-parameter class: default IsString (Text, String) The effect of this declaration would be to eliminate the ambiguous type errors around string literals when OverloadedStrings extension is active. The declaration by itself has effect only in its module, so the proposal also adds the ability to export class defaults: module MyModule (default IsIstring) Once the language extension is published and established, we can consider using it in base and other libraries. See Note [Named default declarations] in GHC.Tc.Gen.Default for implementation details. - - - - - 1deba6b2 by Simon Peyton Jones at 2024-08-17T13:58:13-04:00 Make kick-out more selective This MR revised the crucial kick-out criteria in the constraint solver. Ticket #24984 showed an example in which * We were kicking out unnecessarily * That gave rise to extra work, of course * But it /also/ led to exponentially-sized coercions due to lack of sharing in coercions (something we want to fix separately #20264) This MR sharpens up the kick-out criteria; specifially in (KK2) we look only under type family applications if (fs>=fw). This forced me to understand the existing kick-out story, and I ended up rewriting many of the careful Notes in GHC.Tc.Solver.InertSet. Especially look at the new `Note [The KickOut Criteria]` The proof of termination is not air-tight, but it is better than before, and both Richard and I think it's correct :-). - - - - - 88488847 by Cheng Shao at 2024-08-18T04:44:01+02:00 testsuite: remove undesired -fasm flag from test ways This patch removes the -fasm flag from test ways, except ways like optasm that explicitly state they are meant to be compiled with NCG backend. Most test ways should use the default codegen backend, and the precense of -fasm can cause stderr mismatches like this when GHC is configured with the unregisterised backend: ``` --- /dev/null +++ /tmp/ghctest-3hydwldj/test spaces/testsuite/tests/profiling/should_compile/prof-late-cc.run/prof-late-cc.comp.stderr.normalised @@ -0,0 +1,2 @@ +when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)] + Target platform uses unregisterised ABI, so compiling via C *** unexpected failure for prof-late-cc(prof_no_auto) ``` This has been breaking the wasm unreg nightly job since !12595 landed. - - - - - 3a145315 by Cheng Shao at 2024-08-18T13:05:45-04:00 ghci: fix isMinTTY.h casing for Windows targets This commit fixes isMinTTY.h casing in isMinTTY.c that's compiled for Windows targets. While this looks harmless given Windows filesystems are case-insensitive by default, it does cause a compilation warning with recent versions of clang, so we might as well fix the casing: ``` driver\ghci\isMinTTY.c:10:10: error: warning: non-portable path to file '"isMinTTY.h"'; specified path differs in case from file name on disk [-Wnonportable-include-path] | 10 | #include "isMINTTY.h" | ^ #include "isMINTTY.h" ^~~~~~~~~~~~ "isMinTTY.h" 1 warning generated. ``` - - - - - 5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00 compiler: Fix pretty printing of ticked prefix constructors (#24237) - - - - - ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00 Fix #15773 Clarify further -rtsopts 'defaults' in docs - - - - - 05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00 Improve efficiency of `assertError` (#24625) ... by moving `lazy` to the exception-throwing branch. It's all documented in `Note [Strictness of assertError]`. - - - - - c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00 GHCi debugger: drop record name spaces for Ids When binding new local variables at a breakpoint, we should create Ids with variable namespace, and not record field namespace. Otherwise the rest of the compiler falls over because the IdDetails are wrong. Fixes #25109 - - - - - bd82ac9f by Hécate Kleidukos at 2024-08-21T13:12:12-04:00 base: Final deprecation of GHC.Pack The timeline mandated by #21461 has come to its term and after two years and four minor releases, we are finally removing GHC.Pack from base. Closes #21536 - - - - - 5092dbff by Sylvain Henry at 2024-08-21T13:12:54-04:00 JS: support rubbish static literals (#25177) Support for rubbish dynamic literals was added in #24664. This patch does the same for static literals. Fix #25177 - - - - - b5a2c061 by Phil de Joux at 2024-08-21T13:13:33-04:00 haddock docs: prefix comes before, postfix comes after - - - - - 6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00 haddock: include package info with --show-interface - - - - - 7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00 Document the (x86) SIMD macros. Fixes #25021. - - - - - 05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00 ghc-internal: Derive version from ghc's version Fixes #25005 - - - - - 73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00 base: Deprecate GHC.Desugar See https://github.com/haskell/core-libraries-committee/issues/216. This will be removed in GHC 9.14. - - - - - 821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00 compiler: Store ForeignStubs and foreign C files in interfaces This data is used alongside Core bindings to reconstruct intermediate build products when linking Template Haskell splices with bytecode. Since foreign stubs and files are generated in the pipeline, they were lost with only Core bindings stored in interfaces. The interface codec type `IfaceForeign` contains a simplified representation of `ForeignStubs` and the set of foreign sources that were manually added by the user. When the backend phase writes an interface, `mkFullIface` calls `encodeIfaceForeign` to read foreign source file contents and assemble `IfaceForeign`. After the recompilation status check of an upstream module, `initWholeCoreBindings` calls `decodeIfaceForeign` to restore `ForeignStubs` and write the contents of foreign sources to the file system as temporary files. The restored foreign inputs are then processed by `hscInteractive` in the same manner as in a regular pipeline. When linking the stub objects for splices, they are excluded from suffix adjustment for the interpreter way through a new flag in `Unlinked`. For details about these processes, please consult Note [Foreign stubs and TH bytecode linking]. Metric Decrease: T13701 - - - - - f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00 git: remove a.out and include it in .gitignore a.out is a configure script byproduct. It was mistakenly checked into the tree in !13118. This patch removes it, and include it in .gitignore to prevent a similar error in the future. - - - - - 1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00 docs: Fix code-block syntax on old sphinx version This code-block directive breaks the deb9 sphinx build. Fixes #25201 - - - - - 27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00 JS: add basic support for POSIX *at functions (#25190) openat/fstatat/unlinkat/dup are now used in the recent release of the `directory` and `file-io` packages. As such, these functions are (indirectly) used in the following tests one we'll bump the `directory` submodule (see !13122): - openFile008 - jsOptimizer - T20509 - bkpcabal02 - bkpcabal03 - bkpcabal04 - - - - - c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00 Update directory submodule to latest master The primary reason for this bump is to fix the warning from `ghc-pkg check`: ``` Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory ``` This also requires adding the `file-io` package as a boot library (which is discussed in #25145) Fixes #23594 #25145 - - - - - 4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00 Fix aarch64-alpine target platform description We are producing bindists where the target triple is aarch64-alpine-linux when it should be aarch64-unknown-linux This is because the bootstrapped compiler originally set the target triple to `aarch64-alpine-linux` which is when propagated forwards by setting `bootstrap_target` from the bootstrap compiler target. In order to break this chain we explicitly specify build/host/target for aarch64-alpine. This requires a new configure flag `--enable-ignore-` which just switches off a validation check that the target platform of the bootstrap compiler is the same as the build platform. It is the same, but the name is just wrong. These commits can be removed when the bootstrap compiler has the correct target triple (I looked into patching this on ci-images, but it looked hard to do correctly as the build/host platform is not in the settings file). Fixes #25200 - - - - - e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00 Bump nixpkgs commit for gen_ci script - - - - - 63a27091 by doyougnu at 2024-08-26T20:39:30-04:00 rts: win32: emit additional debugging information -- migration from haskell.nix - - - - - aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00 Only export defaults when NamedDefaults are enabled (#25206) This is a reinterpretation of GHC Proposal #409 that avoids a breaking change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal" Consider a module M that has no explicit export list: module M where default (Rational) Should it export the default (Rational)? The proposal says "yes", and there's a test case for that: default/DefaultImport04.hs However, as it turns out, this change in behavior breaks existing programs, e.g. the colour-2.3.6 package can no longer be compiled, as reported in #25206. In this patch, we make implicit exports of defaults conditional on the NamedDefaults extension. This fix is unintrusive and compliant with the existing proposal text (i.e. it does not require a proposal amendment). Should the proposal be amended, we can go for a simpler solution, such as requiring all defaults to be exported explicitly. Test case: testsuite/tests/default/T25206.hs - - - - - 3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00 simplifier: Fix space leak during demand analysis The lazy structure (a list) in a strict field in `DmdType` is not fully forced which leads to a very large thunk build-up. It seems there is likely still more work to be done here as it seems we may be trading space usage for work done. For now, this is the right choice as rather than using all the memory on my computer, compilation just takes a little bit longer. See #25196 - - - - - c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00 Add missing parenthesizeHsType in cvtp's InvisP case We need to ensure that when we convert an `InvisP` (invisible type pattern) to a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as `@(a :: k)` will parse correctly when roundtripped back through the parser. Fixes #25209. - - - - - 1499764f by Sjoerd Visscher at 2024-08-29T16:52:56+02:00 Haddock: Add no-compilation flag This flag makes sure to avoid recompilation of the code when generating documentation by only reading the .hi and .hie files, and throw an error if it can't find them. - - - - - 768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00 Add functions to check for weakly pinned arrays. This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops. These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved by the user via compaction but won't be moved by the RTS. This moves us one more stop closer to nailing down #22255. - - - - - b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00 ghc-toolchain: Don't leave stranded a.outs when testing for -g0 This happened because, when ghc-toolchain tests for -g0, it does so by compiling an empty program. This compilation creates an a.out. Since we create a temporary directory, lets place the test program compilation in it also, so that it gets cleaned up. Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74 Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203 - - - - - 83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00 Build foreign objects for TH with interpreter's way when loading from iface Fixes #25211 When linking bytecode for TH from interface core bindings with `-fprefer-byte-code`, foreign sources are loaded from the interface as well and compiled to object code in an ad-hoc manner. The results are then loaded by the interpreter, whose way may differ from the current build's target way. This patch ensures that foreign objects are compiled with the interpreter's way. - - - - - 0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00 rts: fix checkClosure error message This patch fixes an error message in checkClosure() when the closure has already been evacuated. The previous logic was meant to print the evacuated closure's type in the error message, but it was completely wrong, given info was not really an info table, but a tagged pointer that points to the closure's new address. - - - - - fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00 MO_AcquireFence: Less restrictive barrier GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)` to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which also implies stores.) - - - - - a45f1488 by Fendor at 2024-09-04T20:22:00-04:00 testsuite: Add support to capture performance metrics via 'perf' Performance metrics collected via 'perf' can be more accurate for run-time performance than GHC's rts, due to the usage of hardware counters. We allow performance tests to also record PMU events according to 'perf list'. - - - - - ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00 gitlab-ci: Add nightly job for running the testsuite with perf profiling support - - - - - 6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00 Enable perf profiling for compiler performance tests - - - - - da306610 by sheaf at 2024-09-04T20:22:41-04:00 RecordCon lookup: don't allow a TyCon This commit adds extra logic when looking up a record constructor. If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to the logic explained in Note [Pattern to type (P2T) conversion]), we emit an error saying that the data constructor is not in scope. This avoids the compiler falling over shortly thereafter, in the call to 'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc', because the record constructor would not have been a ConLike. Fixes #25056 - - - - - 9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00 Use deterministic names for temporary files When there are multiple threads they can race to create a temporary file, in some situations the thread will create ghc_1.c and in some it will create ghc_2.c. This filename ends up in the debug info for object files after compiling a C file, therefore contributes to object nondeterminism. In order to fix this we store a prefix in `TmpFs` which serves to namespace temporary files. The prefix is populated from the counter in TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked outside the thread which consumes it, in a deterministic order, so each thread always receives a TmpFs with the same prefix. This assumes that after the initial TmpFs is created, all other TmpFs are created from forking the original TmpFs. Which should have been try anyway as otherwise there would be file collisions and non-determinism. Fixes #25224 - - - - - 59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00 Silence x-partial in Haddock.Backends.Xhtml This is an unfortunate consequence of two mechanisms: * GHC provides (possibly-empty) lists of names * The functions that retrieve those names are not equipped to do error reporting, and thus accept these lists at face value. They will have to be attached an effect for error reporting in a later refactoring - - - - - 8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00 hadrian: Support loading haddock in ghci There is one tricky aspect with wired-in packages where the boot package is built with `-this-unit-id ghc` but the dependency is reported as `-package-id ghc-9.6...`. This has never been fixed in GHC as the situation of loading wired-in packages into the multi-repl seems like quite a niche feature that is always just easier to workaround. - - - - - 6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00 hadrian/multi: Load all targets when ./hadrian/ghci-multi is called This seems to make a bit more sense than just loading `ghc` component (and dependencies). - - - - - 7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00 ci: Beef up determinism interface test There have recently been some determinism issues with the simplifier and documentation. We enable more things to test in the ABI test to check that we produce interface files deterministically. - - - - - 5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00 Transform some StgRhsClosure into StgRhsCon after unarisation (#25166) Before unarisation we may have code like: Test.foo :: Test.D [GblId, Unf=OtherCon []] = \u [] case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] { __DEFAULT -> Test.D [GHC.Types.True sat_sAw]; }; After unarisation we get: Test.foo :: Test.D [GblId, Unf=OtherCon []] = {} \u [] Test.D [GHC.Types.True 2#]; Notice that it's still an Updatable closure for no reason anymore. This patch transforms appropriate StgRhsClosures into StgRhsCons after unarisation, allowing these closures to be statically allocated. Now we get the expected: Test.foo :: Test.D [GblId, Unf=OtherCon []] = Test.D! [GHC.Types.True 2#]; Fix #25166 To avoid duplicating code, this patch refactors the mk(Top)StgRhs functions and put them in a GHC.Stg.Make module alongside the new mk(Top)StgRhsCon_maybe functions. - - - - - 958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00 haddock: Add missing requirements.txt for the online manual - - - - - 573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00 AArch64: Implement takeRegRegMoveInstr This has likely been forgotten. - - - - - 20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00 haddock: Configuration fix for ReadTheDocs - - - - - 03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00 JS: fake support for native adjustors (#25159) The JS backend doesn't support adjustors (I believe) and in any case if it ever supports them it will be a native support, not one via libffi. - - - - - 5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00 JS: remove redundant h$lstat It was introduced a second time by mistake in 27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190) - - - - - ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Refactor only newSysLocalDs * Change newSysLocalDs to take a scaled type * Add newSysLocalMDs that takes a type and makes a ManyTy local Lots of files touched, nothing deep. - - - - - 7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Don't introduce 'nospec' on the LHS of a RULE This patch address #25160. The main payload is: * When desugaring the LHS of a RULE, do not introduce the `nospec` call for non-canonical evidence. See GHC.Core.InstEnv Note [Coherence and specialisation: overview] The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it on the LHS of a RULE (that's what caused #25160). So now `dsHsWrapper` takes a flag to say if it's on the LHS of a RULE. See wrinkle (NC1) in `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds. But I think this flag will go away again when I have finished with my (entirely separate) speciaise-on-values patch (#24359). All this meant I had to re-understand the `nospec` stuff and coherence, and that in turn made me do some refactoring, and add a lot of new documentation The big change is that in GHC.Core.InstEnv, I changed the /type synonym/ `Canonical` into a /data type/ `CanonicalEvidence` and documented it a lot better. That in turn made me realise that CalLStacks were being treated with a bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`. - - - - - 663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Add defaulting of equalities This MR adds one new defaulting strategy to the top-level defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver. This resolves #25029 and #25125, which showed that users were accidentally relying on a GHC bug, which was fixed by commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4 Author: Simon Peyton Jones <simon.peytonjones at gmail.com> Date: Wed Jun 12 17:44:59 2024 +0100 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. This fix gave rise to a number of user complaints; but the improved defaulting story of this MR largely resolves them. On the way I did a bit of refactoring, of course * Completely restructure the extremely messy top-level defaulting code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much, much, much esaier to grok. - - - - - e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00 Don't name a binding pattern It's a keyword when PatternSynonyms are set. - - - - - b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00 Do not use an error thunk for an absent dictionary In worker/wrapper we were using an error thunk for an absent dictionary, but that works very badly for -XDictsStrict, or even (as #24934 showed) in some complicated cases involving strictness analysis and unfoldings. This MR just uses RubbishLit for dictionaries. Simple. No test case, sadly because our only repro case is rather complicated. - - - - - 8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00 haddock: Remove support for applehelp format in the Manual - - - - - 9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00 RTS linker: add support for hidden symbols (#25191) Add linker support for hidden symbols. We basically treat them as weak symbols. Patch upstreamed from haskell.nix Co-authored-by: Sylvain Henry <sylvain at haskus.fr> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00 Fix C warnings (#25237) GCC 14 treats the fixed warnings as errors by default. I.e. we're gaining GCC 14 compatibility with these fixes. - - - - - 05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00 JS: fix codegen of static string data Before this patch, when string literals are made trivial, we would generate `h$("foo")` instead of `h$str("foo")`. This was introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091. - - - - - 949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Re-organise cross-OS compatibility layer - - - - - 84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Remove CPP for obsolete GHC and Cabal versions - - - - - 370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file - - - - - cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00 Add ZonkAny and document it This MR fixed #24817 by adding ZonkAny, which takes a Nat argument. See Note [Any types] in GHC.Builtin.Types, especially wrinkle (Any4). - - - - - 0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00 hadrian: Make sure ffi headers are built before using a compiler When we are using ffi adjustors then we rely on `ffi.h` and `ffitarget.h` files during code generation when compiling stubs. Therefore we need to add this dependency to the build system (which this patch does). Reproducer, configure with `--enable-libffi-adjustors` and then build "_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o". Observe that this fails before this patch and works afterwards. Fixes #24864 Co-authored-by: Sylvain Henry <sylvain at haskus.fr> - - - - - 0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00 base: Deprecate BCO primops exports from GHC.Exts See https://github.com/haskell/core-libraries-committee/issues/212. These reexports will be removed in GHC 9.14. - - - - - cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00 EPA: Remove Anchor = EpaLocation synonym This just causes confusion. - - - - - 8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00 Bump submodule deepseq to 1.5.1.0 - - - - - aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00 User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250) Fixes #25250. - - - - - 1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add Native Code Generator (NCG) This architecture wasn't supported before. Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00 Adjust test timings for slower computers Increase the delays a bit to be able to run these tests on slower computers. The reference was a Lichee Pi 4a RISCV64 machine. - - - - - a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add RTS linker This architecture wasn't supported before. Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Ignore divbyzero test The architecture's behaviour differs from the test's expectations. See comment in code why this is okay. - - - - - abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Enable MulMayOflo_full test It works and thus can be tested. - - - - - 38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: LibffiAdjustor: Ensure code caches are flushed RISCV64 needs a specific code flushing sequence (involving fence.i) when new code is created/loaded. - - - - - 7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add additional linker symbols for builtins We're relying on some GCC/Clang builtins. These need to be visible to the linker (and not be stripped away.) - - - - - 92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add GHCi support As we got a RTS linker for this architecture now, we can enable GHCi for it. - - - - - a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Set codeowners of the NCG - - - - - 8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00 Add test for C calling convention Ensure that parameters and return values are correctly processed. A dedicated test (like this) helps to get the subtleties of calling conventions easily right. The test is failing for WASM32 and marked as fragile to not forget to investigate this (#25249). - - - - - fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00 finder: Add `IsBootInterface` to finder cache keys - - - - - cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00 EPA: Sync ghc-exactprint to GHC - - - - - 1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00 DmdAnal: Fast path for `multDmdType` (#25196) This is in order to counter a regression exposed by SpecConstr. Fixes #25196. - - - - - 80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00 Bump submodule array to 0.5.8.0 - - - - - 49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00 Linker: add support for extra built-in symbols (#25155) See added Note [Extra RTS symbols] and new user guide entry. Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00 GNU/Hurd: Add getExecutablePath support GNU/Hurd exposes it as /proc/self/exe just like on Linux. - - - - - d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00 RTS: expose closure_sizeW_ (#25252) C code using the closure_sizeW macro can't be linked with the RTS linker without this patch. It fails with: ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_ Fix #25252 Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00 HsExpr: Inline `HsWrap` into `WrapExpr` This nice refactoring was suggested by Simon during review: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374 Fixes #25264. - - - - - 7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00 Pmc: Improve Desugaring of overloaded list patterns (#25257) This actually makes things simpler. Fixes #25257. - - - - - e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00 configure: Correctly report when subsections-via-symbols is disabled As noted in #24962, currently subsections-via-symbols is disabled on AArch64/Darwin due to alleged breakage. However, `configure` reports to the user that it is enabled. Fix this. - - - - - 9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00 Modified the default export implementation to match the amended spec - - - - - 35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00 FFI: don't ppr Id/Var symbols with debug info (#25255) Even if `-dpp-debug` is enabled we should still generate valid C code. So we disable debug info printing when rendering with Code style. - - - - - 9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00 Demand: Combine examples into Note (#25107) Just a leftover from !13060. Fixes #25107. - - - - - 21aaa34b by sheaf at 2024-09-21T17:48:36-04:00 Use x86_64-unknown-windows-gnu target for LLVM on Windows - - - - - 992a7624 by sheaf at 2024-09-21T17:48:36-04:00 LLVM: use -relocation-model=pic on Windows This is necessary to avoid the segfaults reported in #22487. Fixes #22487 - - - - - c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00 compiler: Use type abstractions when deriving For deriving newtype and deriving via, in order to bring type variables needed for the coercions into scope, GHC generates type signatures for derived class methods. As a simplification, drop the type signatures and instead use type abstractions to bring method type variables into scope. - - - - - f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00 driver: Ensure we run driverPlugin for staticPlugins (#25217) driverPlugins are only run when the plugin state changes. This meant they were never run for static plugins, as their state never changes. We need to keep track of whether a static plugin has been initialised to ensure we run static driver plugins at least once. This necessitates an additional field in the `StaticPlugin` constructor as this state has to be bundled with the plugin itself, as static plugins have no name/identifier we can use to otherwise reference them - - - - - 620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00 Allow unknown fd device types for setNonBlockingMode. This allows fds with a unknown device type to have blocking mode set. This happens for example for fds from the inotify subsystem. Fixes #25199. - - - - - c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00 Use Hackage version of Cabal 3.14.0.0 for Hadrian. We remove the vendored Cabal submodule. Also update the bootstrap plans Fixes #25086 - - - - - 6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00 ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh ci.sh sets up the toolchain environment, including paths for the cabal directory, the toolchain binaries etc. If we run any commands outside of ci.sh, unless we source ci.sh we will use the wrong values for these environment variables. In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was using an old index state despite `ci.sh setup` updating and setting the correct index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which is where the index was downloaded to, but we were using the default cabal directory outside ci.sh The solution is to source the correct environment `ci.sh` using `. ci.sh setup` - - - - - 9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00 ghc-toolchain: Set -fuse-ld even for ld.bfd This reflects the behaviour of the autoconf scripts. - - - - - d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00 Parser: be more careful when lexing extended literals (#25258) Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3]. A side-effect of this patch is that we now allow negative unsigned extended literals. They trigger an overflow warning later anyway. - - - - - ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00 rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog. To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID, and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new cost centres up to the one we already dumped in DUMPED_CC_ID. Fixes #24148 - - - - - c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00 EPA: Replace AnnsModule am_main with EpTokens Working towards removing `AddEpAnn` - - - - - 2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30 ci: Run abi-test on test-abi label - - - - - ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 testsuite: Add a test for object determinism Extends the abi_test with an object determinism check Also includes a standalone test to be run by developers manually when debugging issues with determinism. - - - - - d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Sampling uniques in the CG To achieve object determinism, the passes processing Cmm and the rest of the code generation pipeline musn't create new uniques which are non-deterministic. This commit changes occurrences of non-deterministic unique sampling within these code generation passes by a deterministic unique sampling strategy by propagating and threading through a deterministic incrementing counter in them. The threading is done implicitly with `UniqDSM` and `UniqDSMT`. Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded through all passes to guarantee uniques in different passes are unique amongst them altogether. Specifically, the same `DUniqSupply` must be threaded through the CG Streaming pipeline, starting with Driver.Main calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and `codeOutput` in sequence. To thread resources through the `Stream` abstraction, we use the `UniqDSMT` transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will thread the `DUniqSupply` through every pass applied to the `Stream`, for every element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in code generation which that carries through the deterministic unique supply. See Note [Deterministic Uniques in the CG] - - - - - 3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Cmm unique renaming pass To achieve object determinism, we need to prevent the non-deterministic uniques from leaking into the object code. We can do this by deterministically renaming the non-external uniques in the Cmm groups that are yielded right after StgToCmm. The key to deterministic renaming is observing that the order of declarations, instructions, and data in the Cmm groups are already deterministic (modulo other determinism bugs), regardless of the uniques. We traverse the Cmm AST in this deterministic order and rename the uniques, incrementally, in the order they are found, thus making them deterministic. This renaming is guarded by -fobject-determinism which is disabled by default for now. This is one of the key passes for object determinism. Read about the overview of object determinism and a more detailed explanation of this pass in: * Note [Object determinism] * Note [Renaming uniques deterministically] Significantly closes the gap to #12935 - - - - - 8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: DCmmGroup vs CmmGroup Part of our strategy in producing deterministic objects, namely, renaming all Cmm uniques in order, depend on the object code produced having a deterministic order (say, A_closure always comes before B_closure). However, the use of LabelMaps in the Cmm representation invalidated this requirement because the LabelMaps elements would already be in a non-deterministic order (due to the original uniques), and the renaming in sequence wouldn't work because of that non-deterministic order. Therefore, we now start off with lists in CmmGroup (which preserve the original order), and convert them into LabelMaps (for performance in the code generator) after the uniques of the list elements have been renamed. See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935. Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Don't print unique in pprFullName This unique was leaking as part of the profiling description in info tables when profiling was enabled, despite not providing information relevant to the profile. - - - - - 340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: UDFM for distinct-constructor-tables In order to produce deterministic objects when compiling with -distinct-constructor-tables, we also have to update the data constructor map to be backed by a deterministic unique map (UDFM) rather than a non-deterministic one (UniqMap). - - - - - 282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: InfoTableMap uniques in generateCgIPEStub Fixes object determinism when using -finfo-table-map Make sure to also deterministically rename the IPE map (as per Note [Renaming uniques deterministically]), and to use a deterministic unique supply when creating new labels for the IPE information to guarantee deterministic objects when IPE information is requested. Note that the Cmm group produced in generateCgIPEStub must /not/ be renamed because renaming uniques is not idempotent, and the references to the previously renamed code in the IPE Cmm group would be renamed twice and become invalid references to non-existent symbols. We do need to det-rename the InfoTableMap that is created in the conversion from Core to Stg. This is not a problem since that map won't refer any already renamed names (since it was created before the renaming). - - - - - 7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30 ci: Allow abi-test to fail. We are not fully deterministic yet, see #12935 for work that remains to be done. - - - - - a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00 Add Given injectivity for built-in type families Ticket #24845 asks (reasonably enough) that if we have [G] a+b ~ 0 then we also know [G] a ~ 0, b ~ 0 and similar injectivity-like facts for other built-in type families. The status quo was that we never generate evidence for injectivity among Givens -- but it is quite reasonnable to do so. All we need is to have /evidence/ for the new constraints This MR implements that goal. I also took the opportunity to * Address #24978: refactoring UnivCo * Fix #25248, which was a consequences of the previous formulation of UnivCo As a result this MR touches a lot of code. The big things are: * Coercion constructor UnivCo now takes a [Coercion] as argument to express the coercions on which the UnivCo depends. A nice consequence is that UnivCoProvenance now has no free variables, simpler in a number of places. * Coercion constructors AxiomInstCo and AxiomRuleCo are combined into AxiomCo. The new AxiomCo, carries a (slightly oddly named) CoAxiomRule, which itself is a sum type of the various forms of built-in axiom. See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom A merit of this is that we can separate the case of open and closed type families, and eliminate the redundant `BranchIndex` in the former case. * Much better representation for data BuiltInSynFamily, which means we no longer need to enumerate built-in axioms as well as built-in tycons. * There is a massive refactor in GHC.Builtin.Types.Literals, which contains all the built-in axioms for type-level operations (arithmetic, append, cons etc). A big change is that instead of redundantly having (a) a hand-written matcher, and (b) a template-based "proves" function, which were hard to keep in sync, the two are derive from one set of human-supplied info. See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends. * Significant changes in GHC.Tc.Solver.Equality to account for the new opportunity for Given/Given equalities. Smaller things * Improve pretty-printing to avoid parens around atomic coercions. * Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`. Looks like a bug, Richard agrees. * coercionLKind and coercionRKind are hot functions. I refactored the implementation (which I had to change anyway) to increase sharing. See Note [coercionKind performance] in GHC.Core.Coercion * I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan names * I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid calling tyConsOfType. I forget exactly why I did this, but it's definitely better now. * I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc - - - - - dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00 Resolve ambiguous method-bound type variables in vanilla defaults and GND When defining an instance of a class with a "vanilla" default, such as in the following example (from #14266): ```hs class A t where f :: forall x m. Monoid x => t m -> m f = <blah> instance A [] ``` We have to reckon with the fact that the type of `x` (bound by the type signature for the `f` method) is ambiguous. If we don't deal with the ambiguity somehow, then when we generate the following code: ```hs instance A [] where f = $dmf @[] -- NB: the type of `x` is still ambiguous ``` Then the generated code will not typecheck. (Issue #25148 is a more recent example of the same problem.) To fix this, we bind the type variables from the method's original type signature using `TypeAbstractions` and instantiate `$dmf` with them using `TypeApplications`: ```hs instance A [] where f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous ``` Note that we only do this for vanilla defaults and not for generic defaults (i.e., defaults using `DefaultSignatures`). For the full details, see `Note [Default methods in instances] (Wrinkle: Ambiguous types from vanilla method type signatures)`. The same problem arose in the code generated by `GeneralizedNewtypeDeriving`, as we also fix it here using the same technique. This time, we can take advantage of the fact that `GeneralizedNewtypeDeriving`-generated code _already_ brings method-bound type variables into scope via `TypeAbstractions` (after !13190), so it is very straightforward to visibly apply the type variables on the right-hand sides of equations. See `Note [GND and ambiguity]`. Fixes #14266. Fixes #25148. - - - - - 0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00 Document primitive string literals and desugaring of string literals Fixes #17474 and #17974 Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00 rts: Fix segfault when using non-moving GC with profiling `nonMovingCollect()` swaps out the `static_flag` value used as a sentinel for `gct->scavenged_static_objects`, but the subsequent call `resetStaticObjectForProfiling()` sees the old value of `static_flag` used as the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()` before calling `nonMovingCollect()` as otherwise it looks for the incorrect sentinel value Fixes #25232 and #23958 Also teach the testsuite driver about nonmoving profiling ways and stop disabling metric collection when nonmoving GC is enabled. - - - - - e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00 Fix interaction between fork and kqueue (#24672) A kqueue file descriptor isn't inherited by a child created with fork. As such we mustn't try to close this file descriptor as we would close a random one, e.g. the one used by timerfd. Fix #24672 - - - - - 6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00 Improve GHC.Tc.Solver.defaultEquality This MR improves GHC.Tc.Solver.defaultEquality to solve #25251. The main change is to use checkTyEqRhs to check the equality, so that we do promotion properly. But within that we needed a small enhancement to LC_Promote. See Note [Defaulting equalites] (DE4) and (DE5) The tricky case is (alas) hard to trigger, so I have not added a regression test. - - - - - 97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00 JS: fix h$withCStringOnHeap helper (#25288) strlen returns the length of the string without the \0 terminating byte, hence CString weren't properly allocated on the heap (ending \0 byte was missing). - - - - - 5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00 base: Propagate `error` CallStack to thrown exception Previously `errorCallWithCallStackException` failed to propagate its `CallStack` argument, which represents the call-chain of the preceding `error` call, to the exception that it returned. Consequently, the call-stack of `error` calls were quite useless. Unfortunately, this is the second time that I have fixed this but it seems the first must have been lost in rebasing. Fixes a bug in the implementation of CLC proposal 164 <https://github.com/haskell/core-libraries-committee/issues/164> Fixes #24807. - - - - - c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00 driver: Fix -working-dir for foreign files -working-dir definitely needs more serious testing, there are some easy ways to test this. * Modify Cabal to call ghc using -working-dir rather than changing directory. * Modify the testsuite to run ghc using `-working-dir` rather than running GHC with cwd = temporary directory. However this will have to wait until after 9.12. Fixes #25150 - - - - - 88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: reuse predError, succError, toEnumError Reuse predError, succError, and toEnumError when deriving Enum instances to avoid generating different error strings per instance. E.g. before this patch for every instance for a type FOO we would generate a string: "pred{FOO}: tried to take `pred' of first tag in enumeration"# - - - - - e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: generate better code (#16364) Generate better code for Enum.toEnum: check both the lower and the upper bounds at once with an unsigned comparison. Initially I've used a type ascription with a call to 'fromIntegral', hence the slight refactoring of nlAscribe. Using 'fromIntegral' was problematic (too low in the module hierarchy) so 'enumIntToWord' was introduced instead. Combined with the previous commit, T21839c ghc/alloc decrease by 5% Metric Decrease: T21839c - - - - - 383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00 Core: add absorb rules for binary or/and (#16351) Rules: x or (x and y) ==> x x and (x or y) ==> x - - - - - 783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Don't compile `asBox` with -fprof-late The `asBox` function is intended to store exactly the closure which the user passes to it. Placing a cost centre on asBox introduces a thunk, which violates this expectation and can change the result of using asBox when profiling is enabled. See #25212 for more details and ample opportunity to discuss if this is a bug or not. - - - - - 0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Fix normalisation of .prof files Fix 1: If a cost centre contained CAF then the normalisation was corrupted, now only check if CAF is at the start of a line. Fix 2: "no location info" contain a space, which messed up the next normalisation logic which assumed that columns didn't have spaced in. - - - - - 9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00 testsuite: Fix normalisation of prof_files removing newlines These normalisation steps were collapsing lines together, which made subsequent normalisation steps fail. ``` foo x y z CAF x y z qux x y z ``` was getting normalised to ``` foo x y z qux x y z ``` which means that subsequent line based filters would not work correctly. - - - - - 2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00 packaging: Enable late-ccs for release flavour This enables late cost centres when building profiled libraries and subsequently greatly improves the resolution of cost centre stacks when profiling. This patch also introduces the `grep_prof` test modifier which is used to apply a further filter to the .prof file before they are compared. Fixes #21732 ------------------------- Metric Increase: libdir ------------------------- - - - - - bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00 Replace manual string lexing (#25158) Metric Increase: MultilineStringsPerf This commit replaces the manual string lexing logic with native Alex lexing syntax. This aligns the lexer much closer to the Haskell Report, making it easier to see how the implementation and spec relate. This slightly increases memory usage when compiling multiline strings because we now have two distinct phases: lexing the multiline string with Alex and post-processing the string afterwards. Before, these were done at the same time, but separating them allows us to push as much logic into normal Alex lexing as possible. Since multiline strings are a new feature, this regression shouldn't be too noticeable. We can optimize this over time. - - - - - 16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import This behaviour is problematic for the principle reason that `import Prelude` may not refer to the `base` package, and in which case importing an entirely unrelated module causing your implicit prelude to leave the scope is extremely surprising. See the added test for this example. Discussion on #17045. The secondary reason for reverting this patch is that "base" can't be a wired in package any more (see #24903), so we have to remove special logic which singles out base from the compiler. The rule for implicit shadowing is now simply: * If you write import Prelude (..) then you don't get an implicit prelude import * If you write import "foobar" Prelude (..) for all pkgs foobar, you get an implicit import of prelude. If you want to write a package import of Prelude, then you can enable `NoImplicitPrelude` for the module in question to recover the behaviour of ghc-9.2-9.10. Fixes #17045 - - - - - 57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE The COMPILING_BASE_PACKAGE macro is concerned with issues defining symbols and using symbols in the same compilation unit. However, these symbols now exist in ghc-internal rather than base, so we should rename the macro accordingly. The code is guards is likely never used as we never produce windows DLLs but it is simpler to just perform the renaming for now. These days there is little doubt that this macro defined in this ad-hoc manner would be permitted to exist, but these days are not those days. Fixes #25221 - - - - - 70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Preload ghc-internal rather than base This occurence of baseUnitId was missed when moving the bulk of internal definitions into `ghc-internal`. We need to remove this preloading of `base` now because `base` should not be wired in. Towards #24903 - - - - - 12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Remove Data.List compat warning There is currently a warning implemented in -Wcompat which warns you when importing Data.List in a non-qualified manner. ``` A.hs:3:8: warning: [-Wcompat-unqualified-imports] To ensure compatibility with future core libraries changes imports to Data.List should be either qualified or have an explicit import list. | 3 | import Data.List | ^^^^^^^^^ Ok, one module loaded. ``` GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244 CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E This warning was implemented as part of the migration to making Data.List monomorphic again (and to be used like Data.Set, Data.Map etc). That doesn't seem like it happened, and I imagine that the current CLC would require a new proposal anyway in order to do that now. It's not clear in any case what "future core libraries changes" we are waiting to happen before this warning can be removed. Given the first phase of the proposal has lasted 5 years it doesn't seem that anyone is motivated to carry the proposal to completion. It does seem a bit unnecessary to include a warning in the compiler about "future changes to the module" when there's no timeline or volunteer to implement these changes. The removal of this warning was discussed again at: https://github.com/haskell/core-libraries-committee/issues/269 During the discussion there was no new enthusiasm to move onto the next stages of the proposal so we are removing the warning to unblock the reinstallable "base" project (#24903) Fixes #24904 - - - - - d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Move Control.Monad.Zip into ghc-internal mzip is wired in and therefore needs to be in ghc-internal. Fixes #25222 Towards #24903 - - - - - d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00 Unwire the base package This patch just removes all the functions related to wiring-in the base package and the `-this-unit-id=base` flag from the cabal file. After this commit "base" becomes just like any other package and the door is opened to moving base into an external repo and releasing base on a separate schedule to the rest of ghc. Closes #24903 - - - - - 1b39363b by Patrick at 2024-09-27T06:10:19-04:00 Add entity information to HieFile #24544 Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details. Work have been done: * Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`. * Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile` to store the mapping from entity name to corresponding entity infos in `GHC.Iface.Ext.Types`. * Compute `EntityInfo` for each entity name in the HieAst from `TyThing, Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`. * Add test T24544 to test the generation of `EntityInfo`. - - - - - 4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00 The X86 SIMD patch. This commit adds support for 128 bit wide SIMD vectors and vector operations to GHC's X86 native code generator. Main changes: - Introduction of vector formats (`GHC.CmmToAsm.Format`) - Introduction of 128-bit virtual register (`GHC.Platform.Reg`), and removal of unused Float virtual register. - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector` (for registers that can be used for scalar floating point values as well as vectors). - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track of which format each register is used at, so that the register allocator can know if it needs to spill the entire vector register or just the lower 64 bits. - Modify spill/load/reg-2-reg code to account for vector registers (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`). - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate the format we are storing in any given register, for instance changing `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`. - Add logic to lower vector `MachOp`s to X86 assembly (see `GHC.CmmToAsm.X86.CodeGen`) - Minor cleanups to genprimopcode, to remove the llvm_only attribute which is no longer applicable. Tests for this feature are provided in the "testsuite/tests/simd" directory. Fixes #7741 Keeping track of register formats adds a small memory overhead to the register allocator (in particular, regUsageOfInstr now allocates more to keep track of the `Format` each register is used at). This explains the following metric increases. ------------------------- Metric Increase: T12707 T13035 T13379 T3294 T4801 T5321FD T5321Fun T783 ------------------------- - - - - - 10e431ef by sheaf at 2024-09-27T06:10:57-04:00 Use xmm registers in genapply This commit updates genapply to use xmm, ymm and zmm registers, for stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively. It also updates the Cmm lexer and parser to produce Cmm vectors rather than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128, bits256 and bits512 in favour of vectors. The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86) it is okay to use a single vector register to hold multiple different types of data, and we don't know just from seeing e.g. "XMM1" how to interpret the 128 bits of data within. Fixes #25062 - - - - - 8238fb2d by sheaf at 2024-09-27T06:10:57-04:00 Add vector fused multiply-add operations This commit adds fused multiply add operations such as `fmaddDoubleX2#`. These are handled both in the X86 NCG and the LLVM backends. - - - - - 2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00 Add vector shuffle primops This adds vector shuffle primops, such as ``` shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4# ``` which shuffle the components of the input two vectors into the output vector. NB: the indices must be compile time literals, to match the X86 SHUFPD instruction immediate and the LLVM shufflevector instruction. These are handled in the X86 NCG and the LLVM backend. Tested in simd009. - - - - - 0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00 Add Broadcast MachOps This adds proper MachOps for broadcast instructions, allowing us to produce better code for broadcasting a value than simply packing that value (doing many vector insertions in a row). These are lowered in the X86 NCG and LLVM backends. In the LLVM backend, it uses the previously introduced shuffle instructions. - - - - - e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00 Fix treatment of signed zero in vector negation This commit fixes the handling of signed zero in floating-point vector negation. A slight hack was introduced to work around the fact that Cmm doesn't currently have a notion of signed floating point literals (see get_float_broadcast_value_reg). This can be removed once CmmFloat can express the value -0.0. The simd006 test has been updated to use a stricter notion of equality of floating-point values, which ensure the validity of this change. - - - - - f496ff7f by sheaf at 2024-09-27T06:10:57-04:00 Add min/max primops This commit adds min/max primops, such as minDouble# :: Double# -> Double# -> Double# minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# These are supported in: - the X86, AArch64 and PowerPC NCGs, - the LLVM backend, - the WebAssembly and JavaScript backends. Fixes #25120 - - - - - 5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00 Add test for C calls & SIMD vectors - - - - - f824e1ee by sheaf at 2024-09-27T06:10:58-04:00 Add test for #25169 - - - - - d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00 Fix #25169 using Plan A from the ticket We now compile certain low-level Cmm functions in the RTS multiple times, with different levels of vector support. We then dispatch at runtime in the RTS, based on what instructions are supported. See Note [realArgRegsCover] in GHC.Cmm.CallConv. Fixes #25169 ------------------------- Metric Increase: T10421 T12425 T18730 T1969 T9198 ------------------------- - - - - - d5f8778a by sheaf at 2024-09-27T06:10:58-04:00 Fix C calls with SIMD vectors This commit fixes the code generation for C calls, to take into account the calling convention. This is particularly tricky on Windows, where all vectors are expected to be passed by reference. See Note [The Windows X64 C calling convention] in GHC.CmmToAsm.X86.CodeGen. - - - - - f64bd564 by sheaf at 2024-09-27T06:10:58-04:00 X86 CodeGen: refactor getRegister CmmLit This refactors the code dealing with loading literals into registers, removing duplication and putting all the code in a single place. It also changes which XOR instruction is used to place a zero value into a register, so that we use VPXOR for a 128-bit integer vector when AVX is supported. - - - - - ab12de6b by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall: promote arg before calling evalArgs The job of evalArgs is to ensure each argument is put into a temporary register, so that it can then be loaded directly into one of the argument registers for the C call, without the generated code clobbering any other register used for argument passing. However, if we promote arguments after calling evalArgs, there is the possibility that the code used for the promotion will clobber a register, defeating the work of evalArgs. To avoid this, we first promote arguments, and only then call evalArgs. - - - - - 8fd12429 by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall64: simplify loadArg code This commit simplifies the argument loading code by making the assumption that it is safe to directly load the argument into register, because doing so will not clobber any previous assignments. This assumption is borne from the use of 'evalArgs', which evaluates any arguments which might necessitate non-trivial code generation into separate temporary registers. - - - - - 12504a9f by sheaf at 2024-09-27T06:10:58-04:00 LLVM: propagate GlobalRegUse information This commit ensures we keep track of how any particular global register is being used in the LLVM backend. This informs the LLVM type annotations, and avoids type mismatches of the following form: argument is not of expected type '<2 x double>' call ccc <2 x double> (<2 x double>) (<4 x i32> arg) - - - - - 2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00 Link bytecode from interface-stored core bindings in oneshot mode !13042 Part of #T25090 If the flag `-fprefer-byte-code` is given when compiling a module containing TH, GHC will use Core bindings stored in interfaces to compile and link bytecode for splices. This was only implemented for `--make` mode initially, so this commit adds the same mechanism to oneshot mode (`-c`). When an interface is loaded into the EPS in `loadInterface` that has dehydrated Core bindings, an entry is added to the new field `eps_iface_bytecode`, containing an IO action that produces a bytecode `Linkable`, lazily processing the `mi_extra_decls` by calling `loadIfaceByteCode`. When Template Haskell dependencies are resolved in `getLinkDeps`, this action is looked up after loading a module's interface. If it exists, the action is evaluated and the bytecode is added to the set of `Linkable`s used for execution of the splice; otherwise it falls back on the traditional object file. Metric Decrease: MultiLayerModules T13701 - - - - - 7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00 ci: Fix variable inheritence for ghcup-metadata testing job Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine how to setup all the different jobs. On the downstream trigger this was being inherited from the default setting in .gitlab.yml file. Therefore this led to job failures as the necessary CONFIGURE_ARGS were not being passed to the configure script when installing the bindist. See docs: * https://docs.gitlab.com/ee/ci/yaml/#inherit * https://docs.gitlab.com/ee/ci/yaml/#triggerforward 1. inherit:variables:fals - This stops the global variables being inherited into the job and hence forwarded onto the downstream job. 2. trigger:forward:* - yaml_variables: true (default) pass yaml variables to downstream, this is important to pass the upstream pipeline id to downstream. - pipeline_variables: false (default) but don't pass pipeline variables (normal environment variables). Fixes #25294 - - - - - 9ffd6163 by Leo at 2024-09-27T16:26:01+05:30 Fix typo in Prelude doc for (>>=) Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude. - - - - - 5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30 Wildcard binders in type declarations (#23501) Add support for wildcard binders in type declarations: type Const a b = a -- BEFORE: the `b` had to be named -- even if unused on the RHS type Const a _ = a -- AFTER: the compiler accepts -- a wildcard binder `_` The new feature is part of GHC Proposal #425 "Invisible binders in type declarations", and more specifically its amendment #641. Just like a named binder, a wildcard binder `_` may be: * plain: _ * kinded: (_ :: k -> Type) * invisible, plain: @_ * invisible, kinded: @(_ :: k -> Type) Those new forms of binders are allowed to occur on the LHSs of data, newtype, type, class, and type/data family declarations: data D _ = ... newtype N _ = ... type T _ = ... class C _ where ... type family F _ data family DF _ (Test case: testsuite/tests/typecheck/should_compile/T23501a.hs) However, we choose to reject them in forall telescopes and type family result variable binders (the latter being part of the TypeFamilyDependencies extension): type family Fd a = _ -- disallowed (WildcardBndrInTyFamResultVar) fn :: forall _. Int -- disallowed (WildcardBndrInForallTelescope) (Test case: testsuite/tests/rename/should_fail/T23501_fail.hs) See the new Notes: * Note [Type variable binders] * Note [Wildcard binders in disallowed contexts] To accommodate the new forms of binders, HsTyVarBndr was changed as follows (demonstrated without x-fields for clarity) -- BEFORE (ignoring x-fields and locations) data HsTyVarBndr flag = UserTyVar flag Name | KindedTyVar flag Name HsKind -- AFTER (ignoring x-fields and locations) data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind data HsBndrVar = HsBndrVar Name | HsBndrWildCard data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind The rest of the patch is downstream from this change. To avoid a breaking change to the TH AST, we generate fresh names to replace wildcard binders instead of adding a dedicated representation for them (as discussed in #641). And to put a cherry on top of the cake, we now allow wildcards in kind-polymorphic type variable binders in constructor patterns, see Note [Type patterns: binders and unifiers] and the tyPatToBndr function in GHC.Tc.Gen.HsType; example: fn (MkT @(_ :: forall k. k -> Type) _ _) = ... (Test case: testsuite/tests/typecheck/should_compile/T23501b.hs) - - - - - ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30 ci: Push perf notes from wasm jobs It was observed in #25299 that we were failing to push performance numbers from the wasm jobs. In future we might want to remove this ad-hoc check but for now it's easier to add another special case. Towards #25299 - - - - - 4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30 Bump GHC version to 9.12 - - - - - e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30 Bump GHC version to 9.13 - - - - - da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00 base: Add `HasCallStack` constraint to `ioError` As proposed in core-libraries-committee#275. - - - - - 9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00 Fix toException method for ExceptionWithContext Fixes #25235 - - - - - ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00 testsuite: remove accidentally checked in debug print logic - - - - - 68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00 Deprecation for WarnCompatUnqualifiedImports Fixes #25330 - - - - - 4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00 Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86 - - - - - ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00 driver: fix runWorkerLimit on wasm This commit fixes link-time unresolved symbol errors for sem_open etc on wasm, by making runWorkerLimit always behave single-threaded. This avoids introducing the jobserver logic into the final wasm module and thus avoids referencing the posix semaphore symbols. - - - - - 135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00 Parallelize getRootSummary computations in dep analysis downsweep This reuses the upsweep step's infrastructure to process batches of modules in parallel. I benchmarked this by running `ghc -M` on two sets of 10,000 modules; one with a linear dependency chain and the other with a binary tree. Comparing different values for the number of modules per thread suggested an optimum at `length targets `div` (n_cap * 2)`, with results similar to this one (6 cores, 12 threads): ``` Benchmark 1: linear 1 jobs Time (mean ± σ): 1.775 s ± 0.026 s [User: 1.377 s, System: 0.399 s] Range (min … max): 1.757 s … 1.793 s 2 runs Benchmark 2: linear 6 jobs Time (mean ± σ): 876.2 ms ± 20.9 ms [User: 1833.2 ms, System: 518.6 ms] Range (min … max): 856.2 ms … 898.0 ms 3 runs Benchmark 3: linear 12 jobs Time (mean ± σ): 793.5 ms ± 23.2 ms [User: 2318.9 ms, System: 718.6 ms] Range (min … max): 771.9 ms … 818.0 ms 3 runs ``` Results don't differ much when the batch size is reduced to a quarter of that, but there's significant thread scheduling overhead for a size of 1: ``` Benchmark 1: linear 1 jobs Time (mean ± σ): 2.611 s ± 0.029 s [User: 2.851 s, System: 0.783 s] Range (min … max): 2.591 s … 2.632 s 2 runs Benchmark 2: linear 6 jobs Time (mean ± σ): 1.189 s ± 0.007 s [User: 2.707 s, System: 1.103 s] Range (min … max): 1.184 s … 1.194 s 2 runs Benchmark 3: linear 12 jobs Time (mean ± σ): 1.097 s ± 0.006 s [User: 2.938 s, System: 1.300 s] Range (min … max): 1.093 s … 1.101 s 2 runs ``` Larger batches also slightly worsen performance. - - - - - 535a2117 by Daniel DÃaz at 2024-10-06T09:51:46-04:00 Clarify the meaning of "exactly once" in LinearTypes Solves documentaion issue #25084. - - - - - 92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00 Only allow (a => b) :: Constraint rather than CONSTRAINT rep Fixes #25243 - - - - - 4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00 EPA: Remove unused hsCaseAnnsRest We never populate it, so remove it. - - - - - 5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00 rts: Fix invocation of __ieee_set_fp_control() on alpha-linux Fixes the following error when building GHC on alpha-linux: rts/posix/Signals.c: In function ‘initDefaultHandlers’: rts/posix/Signals.c:709:5: error: error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration] 709 | ieee_set_fp_control(0); | ^~~~~~~~~~~~~~~~~~~ | 709 | ieee_set_fp_control(0); | - - - - - c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00 Add changelog entries for !12479 - - - - - bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00 javascript: Read fields of ObjectBlock lazily When linking a module with a large dependency footprint too much of the object files were forced during linking. This lead to a large amount of memory taken up by thunks which would never be forced On the PartialDownsweep test this halves the memory required (from 25G to 13G). Towards #25324 ------------------------- Metric Increase: size_hello_obj ------------------------- - - - - - 571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00 ci: Run the i386 validation job when i386 label is set This is helpful when making changes to base and must update the javascript and i386 base exports files. - - - - - e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00 Rewrite partitionByWorkerSize to avoid pattern match checker bug With `-g3` the pattern match checker would warn about these incomplete patterns. This affects the debug_info builds on CI. ``` Pattern match(es) are non-exhaustive In an equation for ‘go’: Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched: (_:_) _ _ | 2514 | go [] small warnings = (small, warnings) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... ``` Workaround for #25338 - - - - - d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00 Remove the wrapper/coercion-passing logic for submultiplicity checks Instead, we use a dedicated DelayedError, which is emitted systematically on submultiplicity checks, but is suppressed if we can indeed solve the submultiplicity constraint with a reflexivity coercion. This way, we don't have to return anything from `tcSubMult`, which now looks like a regular constraint check, the rest is implementation detail. This removes all of the strange boilerplate that I'd been struggling with under the previous implementation. Even if submultiplicity checks are not properly constraints, this way it's contained entirely within a `WantedConstraint`. Much more pleasant. Closes #25128. - - - - - 1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00 AArch64: Implement switch/jump tables (#19912) This improves the performance of Cmm switch statements (compared to a chain of if statements.) - - - - - 3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00 Fixes #25256, missing parens inside TH-printed pattern type signature - - - - - ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00 Better documentation for floatRange function Closes #16479 - - - - - ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00 Adjust progress message for hadrian to include cwd. Fixes #25335 - - - - - 5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00 CCallConv test: Align argument types The C calling convention / standard requires that arguments and their values are of the same type. - - - - - c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00 hadrian: remove unused ghciWithDebugger field from flavour config This patch removes the ghciWithDebugger field from flavour config since it's actually not used anywhere. - - - - - 9c9c790d by sheaf at 2024-10-07T19:27:23-04:00 user's guide: update docs for X86 CPU flags This commit updates the section of the user's guide pertaining to X86 feature flags with the following changes: - the NCG backend now supports SIMD, so remove all text that says the contrary, - the LLVM backend does not "automatically detect" features, so remove any text that makes that claim. - - - - - a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00 ci: RISCV64 cross-compile testing This adds a validation job which tests that we can build a riscv64 cross compiler and build a simple program using it. We do not currently run the whole testsuite. Towards #25254 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00 Remove unused accumulators in partition_errors - - - - - 55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00 Fix typo in the @since annotation of annotateIO - - - - - ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00 EPA: Remove [AddEpAnn] from (most of) HsExpr EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA` from `Parser.y`, it is the same as `glR` EPA: Remove unused annotation from XOpApp EPA: Use EpToken for XNPat and XNegApp EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens. EPA: Use specific annotation for MultiIf EPA: Move annotations into FunRhs EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig EPA: Remove [AddEpAnn] from ArithSeq EPA: Remove [AddEpAnn] from HsProc EPA: Remove [AddEpAnn] from HsStatic EPA: Remove [AddEpAnn] from BindStmt EPA: Remove [AddEpAnn] from TransStmt EPA: Remove [AddEpAnn] from HsTypedSplice EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr - - - - - 69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00 Handle exceptions from IO manager backend If an IO manager backend throws, it will not actually have registered the file descriptor. However, at that point, the IO manager state was already updated to assume the file descriptor is being tracked, leading to errors and an eventual deadlock down the line as documented in the issue #21969. The fix for this is to undo the IO manager state change in case the backend throws (just as we already do when the backend signals that the file type is not supported). The exception then bubbles up to user code. That way we make sure that 1. the bookkeeping state of the IO manager is consistent with the actions taken by the backend, even in the presence of unexpected failures, and 2. the error is not silent and visible to user code, making failures easier to debug. - - - - - 1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00 Put RdrName in the foExt field of FieldOcc The main purpose of this commit is to rip RdrName out of FieldOcc, in accordance with #21592, and as a side note it has simplified the method we use to deal with ambiguity somewhat. To do the first, we make FieldOccs store (LIdP p) instead of always storing Located RdrName, and moved the readername to the extension points where necessary. For the second, well, we just turn an ambiguous RdrName into a unbound Name through mkUnboundName. Later during disambiguateRecordBinds of the type checking phase, we will try and do type-directed disambiguation based on the rdrName field (for now), so this hack works out fine. See Note [Ambiguous FieldOcc in record updates] for more details. There are two additional minor changes in this commit: * The HsRecSel constructor of HsExpr has been moved to the extension constuctors, since its really GHC specific. * HsProjection no longer has a Located DotFieldOcc as a field, but just a regular DotFieldOcc, since DotFieldOcc already wraps a located FieldLabelString co-authored by: @Jade <Jade512 at proton.me> @alt-romes <rodrigo.m.mesquita at gmail.com> - - - - - 2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00 driver: bail out when -fllvm is passed to GHC not configured with LLVM This patch makes GHC bail out with an proper error message when it's not configured with LLVM but users attempt to pass -fllvm, see #25011 and added comment for details. Fixes #25011 Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - 78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00 configure: Find C++ probing when GCC version is the latest but G++ is old #23118 - - - - - 083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00 Consider Wanteds with rewriters as insoluble This MR fixes #25325 See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2) There is a small change in the error message for T14172, but it looks entirely acceptable to me. - - - - - 0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00 Wibbles - - - - - 09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00 Spelling errors - - - - - 694489ed by sheaf at 2024-10-11T03:55:14-04:00 LLVM: use sse4.2 instead of sse42 LLVM expects the former instead of the latter since version 3.4. Fixes #25019 - - - - - 06ae8507 by sheaf at 2024-10-11T03:55:14-04:00 LLVM: make SSE4.2 imply +popcnt For consistency with the NCG as well as with Clang and GCC, we make the SSE4.2 feature flag imply +popcnt when using the LLVM backend. Fixes #25353 - - - - - 3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00 Drop obsolete libffi Makefile This patch drops obsolete libffi Makefile from the tree, given it's completely unused since removal of make build system in !7094. - - - - - df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00 ghc-internal: Fix incomplete matches on IOError As noted in #25362, these incomplete matches were previously not being warned about. They were easily addressed by use of `GHC.Internal.Event.Windows.withException`. Closes #25362. - - - - - 8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00 compiler: Fix orientation of GHC.Hs.Doc boot file We should be free to import things from Language.Haskell.Syntax in GHC modules. Therefore the the boot file for the loop between ImpExp and GHC.Hs.Doc was in the wrong place. Issue #21592 - - - - - d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00 testsuite: Normalise trailing digits from hole fits output The type variables in the holes fit output from `abstract_refinement_hole_fits` is quite sensitive to compiler configuration. Specifically, a slight change in the inlining behavior of `throw` changes type variable naming in `(>>=)` and a few others. Ideally we would make hole fits output more deterministic but in the meantime we simply normalise this difference away as it not relevant to the test's goal. - - - - - da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00 base: Add test for #25066 - - - - - eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00 base: Fix #25066 As noted in #25066, the exception backtrace proposal introduced a rather subtle performance regression due to simplification producing Core which the demand analyser concludes may diverge with a precise exception. The nature of the problem is more completely described in the new Note [Hiding precise exception signature in throw]. The (rather hacky) solution we use here hides the problematic optimisation through judicious use of `noinline`. Ultimately however we will want a more principled solution (e.g. #23847). Fixes #255066 CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290 Metric Decrease: T9872d - - - - - 0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00 base: Improve documentation of Control.Exception.Backtrace - - - - - 18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00 Bump process submodule to v1.6.25.0 - - - - - a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00 Move HsInteger and HsRat to an extension constructor These constructors were only used during the TC stage, or during template haskell. It seemed clear that it was independent of the source syntax represented in L.H.S, and thus we removed it according to #21592. - - - - - 4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00 Docs: Linear types: link Strict Patterns subsection Also, fix a bug in RST with missing newline before a listing. Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net> - - - - - adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00 users guide: Address remaining TODOs in eventlog format docs Closes #25296. - - - - - 9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00 Fix z-encoding of tuples (#25364) Tuples with prefix/suffix strings weren't always properly encoded with their shortcut notations. Fix this. - - - - - c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00 Delete constants that can be deduced There are macros in MachRegs.h to figure those out. - - - - - 8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00 hadrian: Handle broken symlinks properly when creating source dist directories If we have a broken symlink in the repository, don't try to `need` the symlink or the target of the symlink. Attempting to do so has `shake` attempt to read the target to compute its hash, which fails because the target doesn't exist. - - - - - 16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00 hadrian: exclude cabal.project.symlink.broken from source archives Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately, this broke our source distribution as we use use `tar --dereference` to avoid issues with symlink compatibility on windows, and `tar --dereference` chokes when it encounters any broken symlinks. We can't get rid of `--dereference` because symlinks are generally broken on windows, so the only option is to exclude this file from source archives. see also https://github.com/haskell/cabal/issues/10442 - - - - - f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00 Bump Cabal submodule to 3.14 Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: haddock.Cabal - - - - - 745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00 users-guide: Document GHCi :where command Resolve #24509. - - - - - e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00 EPA: Remove [AddEpAnn] from IE, Pat and some Tys EPA: Remove [AddEpAnn] from LazyPat EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat EPA: Remove [AddEpAnn] from HsFieldBind EPA: Remove [AddEpAnn] from PatSynBind EPA: Remove [AddEpAnn] from IPBind EPA: Remove [AddEpAnn] from FixSig EPA: Remove [AddEpAnn] from activation rules EPA: Remove [AddEpann] from SpecInstSig EPA: Remove [AddEpAnn] from MinimalSig EPA: Remove [AddEpAnn] from SCCFunSig EPA: Remove [AddEpAnn] from CompleteMatchSig EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig EPA: Remove [AddEpAnn] from IEThingAbs EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith EPA: Remove [AddEpAnn] from IEModuleContents EPA: Remove [AddEpAnn] from HsOpTy EPA: Remove [AddEpAnn] for various binders EPA: Remove [AddEpAnn] for HsIParamTy - - - - - 81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00 Desugaring, plus -Wincomplete-record-selectors This commit does several related things: * Major refactor of the handling of applications in the desugarer. Now all applications are handled in `dsApp`, `ds_app` and related functions. This dramatically simplifies the code and removes complicated cruft that had accumulated. Hooray. Fixes #25281. * Improve the handling of -Wincomplete-record-selectors. We now incorporate the result type of unsaturated record selector applications as well as consider long-distance information in getField applications. Plus, the implmentation now builds the improved `dsApp` stuff above, so it is much easier to understand. Plus, incorporates improved error message wording suggested by Adam Gundry in !12685. Fixes #24824, #24891 See the long Note [Detecting incomplete record selectors] * Add -Wincomplete-record-selectors to -Wall, as specified in GHC Proposal 516. To do this, I also had to add -Wno-incomplete-record-selectors to the build flags for Cabal in GHC's CI. See hadrian/src/Settings/Warnings.hs. We can remove this when Cabal is updated so that it doesn't trigger the warning: https://github.com/haskell/cabal/issues/10402 2.6% decrease in compile time allocation in RecordUpPerf Metric Decrease: RecordUpdPerf - - - - - ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00 Elmininate incomplete record selectors This patch is a pure refactor of GHC's source code, to avoid the use of partial record selectors. It was provoked by adding -Wincomplete-record-selectors to -Wall (as the GHC Proposal specified), which in turn showed up lots of places where GHC was using incomplete record selectors. This patch does mostly-simple refactoring to make it clear to the pattern match checker that there is in fact no partiality. There is one externally-visible change: I changed the data type HoleFit to split out the two cases data HoleFit = TcHoleFit TcHoleFit | RawHoleFit SDoc data TcHoleFit = HoleFit { ...lots of fields } There are large swathes of code that just deal with `TcHoleFit`, and having it as a separate data types makes it apparent that `RawHoleFit` can't occur. This makes it much better -- but the change is visible in the HolePlugin interface. I decided that there are so few clients of this API that it's worth the change. I moved several functions from Language.Haskell.Syntax to GHC.Hs. Reason, when instantiated at (GhcPass _), the extension data construtcor is guaranteed unused, and that justifies omitted patterns in these functions. By putting them in GHC.Hs.X I can specialise the type for (GhcPass _) and thereby make the function total. An interesting side-light is that there were a few local function definitions without a type signature, like this one in GHC.Parser.Header convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i) This is fully closed, and so is generalised; but that generalises it to any old pass, not (GhcPass _), so GHC rightly complains about the use of the selector `ideclPkgQual`. I added a type signature to `i`, thus convImport (L _ (i::ImportDecl GhcPs)) = (ideclPkgQual i, reLoc $ ideclName i) which specialised the function enough to make the record selector complete. Quite a surprising consequence of local let-generalisation! - - - - - 6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00 Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi In the main MR, -Wall now includes -Wincomplete-record-selectors. However `hadrian-multi` has many, many warnings about incomplete record selectors, so this patch stops those warnings being treated as errors. (See discussion on !13308.) A better fix would be to remove the use of incomplete record selectors, since each of them represents a potential crash. - - - - - edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00 users-guide: Document field coalescence - - - - - 55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00 LLVM backend: Use correct rounding for Float literals Fixes #22033 - - - - - e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00 Changed import from Ghc. module to L.H.S module Progresses #21592 For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for - - - - - ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00 Add a release-notes entry for -Wincomplete-record-selectors - - - - - 6f0a62db by ur4t at 2024-10-16T15:33:43+00:00 GHCi: fix improper location of ghci_history file Fixes #24266 - - - - - 5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00 EPA: Remove [AddEpAnn] commit 3 EPA: Remove [AddEpAnn] from HsDocTy EPA: Remove [AddEpAnn] from HsBangTy EPA: Remove [AddEpAnn] from HsExplicitListTy EPA: Remove [AddEpAnn] from HsExplicitTupleTy EPA: Remove [AddEpAnn] from HsTypedBracket EPA: Remove [AddEpAnn] from HsUntypedBracket EPA: Remove [AddEpAnn] from PatBuilderOpApp EPA: break out 'EpToken "|"' from ClassDecl anns EPA: Remove [AddEpAnn] from ClassDecl EPA: Remove [AddEpAnn] from SynDecl - - - - - fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00 Expand the haddocks for Control.Category - - - - - 076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00 documentation: more examples for Control.Category - - - - - 90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00 ghci: mitigate host/target word size mismatch in BCOByteArray serialization This patch mitigates a severe host/target word size mismatch issue in BCOByteArray serialization logic introduced since !12142, see added note for detailed explanation. - - - - - 839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00 ghci: use plain malloc for mkConInfoTable on non-TNTC platforms This patch avoids using mmap() to allocate executable memory for mkConInfoTable on platforms without tables-next-to-code, see added comment for explanation. - - - - - a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00 ghc-internal: add missing CPPs for wasm This patch adds some missing CPP guards to ghc-internal, given those functions are non existent on wasm and would cause linking issues. - - - - - 71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00 rts: rename prelude.js to prelude.mjs This commit renames prelude.js to prelude.mjs for wasm backend rts jsbits, and slightly adjusts the jsbits contents. This is for preparing the implementation of dyld.mjs that contains wasm dynamic linker logic, which needs to import prelude.mjs as a proper ESM module. - - - - - 33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00 rts: add __wrapped_freeJSVal This commit wraps imported freeJSVal in a __wrapped_freeJSVal C function for wasm backend RTS. In general, wasm imports are only supposed to be directly called by C; they shouldn't be used as function pointers, which confuses wasm-ld at link-time when generating shared libraries. - - - - - 0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00 rts: correct stale link in comment - - - - - 90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00 rts: drop interpretBCO support from non-dyn ways on wasm This commit drops interpretBCO support from non dynamic rts ways on wasm. The bytecode interpreter is only useful when the RTS linker also works, and on wasm it only works for dynamic ways anyway. An additional benefit of dropping interpretBCO is reduction in code size of linked wasm modules, especially since interpretBCO references ffi_call which is an auto-generated large function in libffi-wasm and unused by most user applications. - - - - - 98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00 rts: don't build predefined GloblRegs for wasm PIC mode This commit wraps the predefined GlobalRegs in Wasm.S under a CPP guard to prevent building for PIC mode. When building dynamic ways of RTS, the wasm globals that represent STG GlobalRegs will be created and supplied by dyld.mjs. The current wasm dylink convention doesn't properly support exporting relocatable wasm globals at all, any wasm global exported by a .so is assumed to be a GOT.mem entry. - - - - - bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00 rts: fix conflicting StgRun definitions on wasm This commit fixes conflicting StgRun definition when building dynamic ways of RTS for wasm in unregisterised mode. - - - - - a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00 hadrian: use targetSupportsRPaths predicate This commit changes the hostSupportsRPaths predicate to targetSupportsRPaths and use that to decide whether to pass RPATH-related link-time options. It's not applied to stage0, we should just use the default link-time options of stageBoot ghc. - - - - - f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00 hadrian: disable internal-interpreter of ghc library when cross compiling This commit disable the internal-interpreter flag of ghc library when cross compiling, only external interpreter works in such cases. - - - - - 577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00 hadrian: enable internal-interpreter for ghc-bin stage0 This commit enables internal-interpreter flag for ghc-bin even when compiling stage0, as long as target supports ghci. It enables ghci functionality for cross targets that support ghci, since cross ghc-bin is really stage0. - - - - - c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00 hadrian: fix CFLAGS for gmp shared objs on wasm This commit adds -fvisibility=default to CFLAGS of gmp when building for wasm. This is required to generate the ghc-bignum shared library without linking errors. Clang defaults to -fvisibility=hidden for wasm targets, which will cause issues when a symbol is expected to be exported in a shared library but without explicit visibility attribute annotation. - - - - - 775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00 hadrian: re-enable PIC for gmp on wasm This commit re-enables --with-pic=yes configuration option of gmp when building for wasm, given we're about to include support for shared libraries, TH and ghci. - - - - - b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00 hadrian: add the host_fully_static flavour transformer This commit adds the host_fully_static flavour transformer to hadrian, which ensures stage0 is fully statically linked while still permitting stage1 libdir to contain shared libraries. This is intended to be used by the wasm backend to build portable linux bindists that contain wasm shared libraries. - - - - - 5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00 ci: update wasm jobs configuration This commit bumps ci-image revision to use updated wasm toolchain, and use host_fully_static instead of fully_static for wasm jobs so to ensure wasm shared libraries can be properly built. - - - - - 2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00 hadrian/testsuite: implement config.cross logic This commit implements the config.cross field in the testsuite driver. It comes from the "cross compiling" ghc info field for both in-tree/out-of-tree GHC, and is an accurate predicate of whether we're cross-compiling or not (compared to the precense of target emulator), and is useful to implement predicates to assert the precense of internal interpreter (only available on non-cross GHC) for tests that do require it (e.g. plugins). - - - - - 8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00 hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs This patch implements the targetRTSLinkerOnlySupportsSharedLibs predicate in hadrian. Its definition in hadrian is the single source of truth, and the information propagates to ghc settings file, ghc driver and testsuite driver. It is used in various places to ensure dynamic dependency is selected when the target RTS linker only supports loading dynamic code. - - - - - b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00 testsuite: don't use host cpu features when testing cross ghc This patch disables CPU feature detection logic when testing cross GHC, since those features don't make sense for the target anyway. - - - - - 3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: implement & use req_plugins predicate This commit implements req_plugins predicate to indicate that the test requires plugin functionality. Currently this means cross GHC is disabled since internal-interpreter doesn't work in cross GHC yet. - - - - - 93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: make use of config.interp_force_dyn This commit takes config.interp_force_dyn into consideration when setting up TH/ghci way flags. - - - - - 94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: bump T17572 timeout - - - - - 2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: bump T22744 pre_cmd timeout - - - - - 45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: skip terminfo_so for cross ghc - - - - - 05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: fix shared library size tests for cross ghc This commit fixes shared library size tests (e.g. array_so in testsuite/tests/perf/size/all.T) when testing cross ghc. Previously, if shared library file extension of host and target differs, those tests will fail with framework errors due to not finding the right files. - - - - - fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: skip ghc api tests that attempt to spawn processes inside wasm This commit skips a few ghc api tests on wasm, since they would attempt to spawn processes inside wasm, which is not supported at all. - - - - - 1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: skip T22840 due to broken -dtag-inference-checks on wasm - - - - - 78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00 testsuite: ensure $(ghciWayFlags) can be overridden This commit revises boilerplate.mk in testsuite as well as a few other places, to ensure the tests that do make use of $(ghciWayFlags) can receive the right $(ghciWayFlags) from testsuite driver config. - - - - - 47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00 testsuite: skip rdynamic on wasm - - - - - fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00 testsuite: skip T2615 on wasm This commit marks T2615 as skip on wasm, given LD_* environment variables aren't supported on wasm anyway. - - - - - 77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00 testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm - - - - - 69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00 testsuite: fix T16180 on wasm This commit fixes T16180 on wasm once TH support is flipped on. The fix is simply adding right asm code for wasm. - - - - - 621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00 driver: fix -fexternal-interpreter flag for JS backend Previously, -fexternal-interpreter is broken for JS backend, since GHC would attempt to launch a non-existent ghc-iserv* executable. This commit fixes it by adjusting pattern matching order in setTopSessionDynFlags. - - - - - 80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00 driver: use interpreterDynamic predicate in preloadLib This commit use the interpreterDynamic predicate in preloadLib to decide if we should do dynLoadObjs instead of loadObj. Previously we used hostIsDynamic which was only written with non-cross internal interpreter in mind. The testsuite is also adjusted to remove hard-wired -fPIC flag for cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and properly pass ghc_th_way_flags to ghc. - - - - - 74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00 compiler: fix Cmm dynamic CLabels for wasm This commit fixes the handling of dynamic CLabels for the wasm backend. Just do the simplest handling: preserve the original CLabel, both unreg/NCG backends can handle them properly without issue. - - - - - f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00 driver: add necessary compile-time flags for wasm PIC mode This commit adds necessary compile-time flags when compiling for wasm PIC mode, see added comment for detailed explanation. - - - - - 9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00 driver: add necessary link-time flags for wasm shared libs This commit adds necessary link-time flags for wasm shared libs, see added comments for detailed explanation. - - - - - 649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00 driver: enforce -fno-use-rpaths for wasm This commit ensures the GHC driver never passes any RPATH-related link-time flags on wasm, which is not supported at all. - - - - - 47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00 driver: ensure static archives are picked when linking static .wasm modules This commit ensures static archives are picked when linking .wasm modules which are supposed to be fully static, even when ghc may be invoked with -dynamic, see added comment for explanation. - - - - - fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00 compiler: fix dynamic_too_enable for targets that require dynamic libraries This commit fixes dynamic_too_enable for targets whose RTS linker can only load dynamic code. - - - - - 94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00 compiler: fix checkNonStdWay for targets that require dynamic libraries This commit fixes checkNonStdWay to ensure that for targets whose RTS linker can only load dynamic code, the dynamic way of object is selected. - - - - - 88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00 ghc-bin: enforce dynamic way when the target requires so This commit makes ghc-bin use dynamic way when it is doing interactive stuff on certain targets whose RTS linker can only handle dynamic code. - - - - - 549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00 hadrian/ghci: add wasm dyld This commit adds the wasm dynamic linker implementation, as well as ghci logic to call it and hadrian logic to install it to the correct location. See the top-level note in utils/jsffi/dyld.mjs for more details. - - - - - b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00 driver: fix getGccSearchDirectory for wasm target This commit fixes getGccSearchDirectory logic for wasm target, ensures the correct search directory containing libc.so etc can be found by GHC. getGccSearchDirectory is also exported so it can be used elsewhere to obtain the wasi-sdk libdir and pass to the dyld script. - - - - - 2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00 driver: add wasm backend iserv logic This commit adds wasm backend iserv logic to the driver, see added comments for explanation. - - - - - 61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00 compiler: add PIC support to wasm backend NCG This commit adds support for generating PIC to the wasm backend NCG. - - - - - 652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00 hadrian/compiler: flip on support for shared libs & ghci for wasm This commit flips on the support for shared libs and ghci for the wasm target, given all required support logic has been added in previous commits. - - - - - 74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00 testsuite: flip on support for shared libs, TH & ghci for wasm This commit flips on support for shared libs, TH & ghci for wasm in the testsuite, given support has been landed in previous commits. - - - - - 525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00 Revert "compiler: start deprecating cmmToRawCmmHook" This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns out the GHC-WPC project does use it to observe Cmm in the pipeline, see #25363. - - - - - 5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00 rts: fix pointer overflow undefined behavior in bytecode interpreter This patch fixes an unnoticed undefined behavior in the bytecode interpreter. It can be caught by building `rts/Interpreter.c` with `-fsanitize=pointer-overflow`, the warning message is something like: ``` rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658 SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13 rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658 SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13 rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0 SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13 ``` Whenever we do something like `SpW(-1)`, the negative argument is implicitly converted to an unsigned integer type and causes pointer arithmetic overflow. It happens to be harmless for most targets since overflowing would wrap the result to desired value, but it's still coincidental and undefined behavior. Furthermore, it causes real damage to the wasm backend, given clang-20 will emit invalid wasm code that crashes at run-time for this kind of C code! (see https://github.com/llvm/llvm-project/issues/108770) The fix here is adding some explicit casts to ensure we always use the signed `ptrdiff_t` type as right hand operand of pointer arithmetic. - - - - - eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00 Bump transformers submodule The svg image files mentioned in transformers.cabal were previously not checked in, which broke sdist generation. - - - - - 366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00 Remove reference to non-existent file in haddock.cabal - - - - - 826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00 Move tests T11462 and T11525 into tests/tcplugins - - - - - dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00 Repair the 'build-cabal' hadrian target Fixes #23117. Fixes #23281. Fixes #23490. This required: * Updating the bit-rotted compiler/Setup.hs and its setup-depends * Listing a few recently-added libraries and utilities in cabal.project-reinstall * Setting allow-boot-library-installs to 'True' since Cabal now considers the 'ghc' package itself a boot library for the purposes of this flag Additionally, the allow-newer block in cabal.project-reinstall was removed. This block was probably added because when the libraries/Cabal submodule is too new relative to the cabal-install executable, solving the setup-depends for any package with a custom setup requires building an old Cabal (from Hackage) against the in-tree version of base, and this can fail un-necessarily due to tight version bounds on base. However, the blind allow-newer can also cause the solver to go berserk and choose a stupid build plan that has no business succeeding, and the failures when this happens are dreadfully confusing. (See #23281 and #24363.) Why does setup-depends solving insist on an old version of Cabal? See: https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410 The right solution here is probably to use the in-tree cabal-install from libraries/Cabal/cabal-install with the build-cabal target rather than whatever the environment happens to provide. But this is left for future work. - - - - - b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00 Revert "CI: Disable the test-cabal-reinstall job" This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255. - - - - - a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00 base: speed up traceEventIO and friends when eventlogging is turned off #17949 Check the RTS flag before doing any work with the given lazy string. Fix #17949 Co-authored-by: Michael Peyton Jones <me at michaelpj.com> Co-authored-by: Sylvain Henry <sylvain at haskus.fr> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00 ci: Add support for ONLY_JOBS variable to trigger any validation pipeline By setting the ONLY_JOBS variable to the name of the job (or multiple jobs), the resulting pipeline will include a validation job for that pipeline. For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate" then a ubuntu22_04 job will be included in the validation pipeline. This is useful for testing specific jobs. Fixes #25332 - - - - - 280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00 rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names (cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45) - - - - - 25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00 EPA: Remove [AddEpAnn] Commit 4 EPA: Remove [AddEpAnn] from DataDecl This is quite a big change. The most important part is moving the annotations into HsDataDefn, using a specific annotation data type. It has a knock-on to everything that uses HsDataDefn EPA: Remove [AddEpAnn] for FunDep EPA: Remove [AddEpann] from FamilyDecl EPA: Remove [AddEpAnn] From InjectivityAnn EPA: Remove [AddEpAnn] from DefaultDecl EPA: Remove [AddEpAnn] from RuleDecls EPA: Remove [AddEpAnn] from Warnings - - - - - d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00 Interpreter: Add locking for communication with external interpreter This adds locking to communication with the external interpreter to prevent concurrent tasks interfering with each other. This fixes Template Haskell with the external interpreter in parallel (-j) builds. Fixes #25083 - - - - - d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00 Use monospace font for "Either a b" in fmap docs The documentation for fmap shows "`Either a b`" in the default font instead of showing "Either a b" in a monospace font. - - - - - 4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00 Parser: remove non-ASCII characters from Parser.y Non-ASCII characters in the source causes a problem with the default Haskell Language Server setup in VSCode. Two characters seems to have been left in by accident. Workaround for #25396 - - - - - 7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00 EPA: Remove [AddEpAnn] Commit 5 EPA: Remove [AddEpAnn] from AnnPragma EPA: Remove [AddEpAnn] From ForeignDecl EPA: Remove [AddEpAnn] from RoleAnnotDecl EPA: Remove [AddEpAnn] from StandaloneKindSig EPA: Remove [AddEpAnn] From HsDeriving EPA: Remove [AddEpAnn] from ConDeclField EPA: Remove [AddEpAnn] from ConDeclGADT EPA: Remove [AddEpAnn] from ConDeclH98 EPA: Remove [AddEpAnn] from ClsInstDecl - - - - - f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00 wasm: bump dyld v8 heap size limit This patch adds `--max-old-space-size=8192` to wasm dyld shebang arguments to bump V8 heap size limit. The default limit (`heap_size_limit` returned by `v8.getHeapStatistics()`) is dynamically determined and a bit too low under certain workloads, and V8 would waste too much CPU time to garbage collect old generation heap more aggressively. Bumping the limit to 8G doesn't imply dyld would really take that much memory at run-time, but it lessens V8 heap stress significantly. - - - - - d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00 Add requestTickyCounterSamples to GHC.Internal.Profiling This allows the user to request ticky counters to be written to the eventlog at specific times. See #24645 - - - - - 71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00 Move defaulting code into a new module GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them are comments. This MR * Adds the new module GHC.Tc.Solver.Default, which has all the complex, but well modularised, defaulting code * Moves a bit of code from GHC.Tc.Solver into the existing GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM, which are called from GHC.Tc.Solver.Default It's a pure refactor. No code changes. - - - - - a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00 Improve the generalisation code in Solver.simplifyInfer The code in `decideQuantification` has become quite complicated. This MR straightens it out, adds a new Note, and on the way fixes #25266. See especially Note [decideAndPromoteTyVars] which is is where all the action happens in this MR. - - - - - 148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00 Adjust catches to properly rethrow exceptions https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception rethrowing proposal, but it didn't adjust `catches`. This fixes it. - - - - - 25121dbc by doyougnu at 2024-10-22T09:38:18-04:00 linker: add --optimistic-linking flag This patch adds: - the --optimistic-linking flag which binds unknown symbols in the runtime linker to 0xDEADBEEF instead of exiting with failure - The test T25240 which tests these flags using dead code in the FFI system. - closes #25240 This patch is part of the upstreaming haskell.nix patches project. - - - - - f19e076d by doyougnu at 2024-10-22T09:38:18-04:00 ghc-internal: hide linkerOptimistic in MiscFlags - - - - - edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00 hadrian: fix bindist executable wrapper logic for cross targets This commit fixes an oversight of hadrian wrapper generation logic: when doing cross compilation, `wrapper` is called on executable names with cross prefix, therefore we must use `isSuffixOf` when matching to take the cross prefix into account. Also add missing cross prefix to ghci wrapper content and fix hsc2hs wrapper logic. - - - - - edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00 mkTick: Push ticks through unsafeCoerce#. unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast for the purpose of mkTick. This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we now push the scope part of the cost centre up to `trivial_expr` at which point we can discard it completely if the expression is trivial enough. This fixes #25212. - - - - - 1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00 hadrian: enable late-CCS for perf flavour as well This patch enables late-CCS for perf flavour so that the testsuite can pass for perf as well. Fixes #25308. - - - - - fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00 hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling This patch disables internal-interpreter flag for stage0 ghc-bin when not cross compiling, see added comment for explanation. Fixes #25406. - - - - - 6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00 Improve heap overflow exception message (#25198) Catch heap overflow exceptions and suggest using `+RTS -M<size>`. Fix #25198 - - - - - b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00 determinism: Interface re-export list det In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for interface file determinism. This commit introduces 'DetOrdAvails', a newtype that should only be constructed by sorting Avails with 'sortAvails' unless the avails are known to be deterministically ordered. This newtype is used by 'DocStructureItem' where 'Avails' was previously used to ensure the list of avails is deterministically sorted by construction. Note: Even though we order the constructors and avails in the interface file, the order of constructors in the haddock output is still determined from the order of declaration in the source. This was also true before, when the list of constructors in the interface file <docs> section was non-deterministic. Some haddock tests such as "ConstructorArgs" observe this (check the order of constructors in out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file) The updated tests are caused by haddock corners where the order in the source is not preserved (and was non-deterministic before this PR): * Module header in the latex backend * Re-export of pattern synonyms associated to a datatype (#25342) Fixes #25304 - - - - - e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00 Revert "ci: Allow abi-test to fail." After #25304, the abi-test with interface and object determinism succeeds. This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00. - - - - - 7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00 EPA: reduce [AddEpann] in AnnList Remove it from the `al_rest` field, and make `AnnList` parameterized on a type to be used in `al_rest`, for the various use cases. - - - - - 4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00 Fix -fobject-determinism flag definition The flag should be defined as an fflag to make sure the -fno-object-determinism flag is also an available option. Fixes #25397 - - - - - 55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00 CorePrep: Attach evaldUnfolding to floats to detect more values See `Note [Pin evaluatedness on floats]`. - - - - - 9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00 Make DataCon workers strict in strict fields (#20749) This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand Analysis so that they exploit and maintain strictness of DataCon workers. See `Note [Strict fields in Core]` for details. Very little needed to change, and it puts field seq insertion done by Tag Inference into a new perspective: That of *implementing* strict field semantics. Before Tag Inference, DataCon workers are strict. Afterwards they are effectively lazy and field seqs happen around use sites. History has shown that there is no other way to guarantee taggedness and thus the STG Strict Field Invariant. Knock-on changes: * I reworked the whole narrative around "Tag inference". It's now called "EPT enforcement" and I recycyled the different overview Notes into `Note [EPT enforcement]`. * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments instead of recursing into `exprIsHNF`. That regressed the termination analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made it call `exprOkForSpeculation`, too. * There's a small regression in Demand Analysis, visible in the changed test output of T16859: Previously, a field seq on a variable would give that variable a "used exactly once" demand, now it's "used at least once", because `dmdTransformDataConSig` accounts for future uses of the field that actually all go through the case binder (and hence won't re-enter the potential thunk). The difference should hardly be observable. * The Simplifier's fast path for data constructors only applies to lazy data constructors now. I observed regressions involving Data.Binary.Put's `Pair` data type. * Unfortunately, T21392 does no longer reproduce after this patch, so I marked it as "not broken" in order to track whether we regress again in the future. Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas in #21497 and #22475). Compiler perf generally improves, sometimes drastically: Baseline Test Metric value New value Change -------------------------------------------------------------------------------- ManyConstructors(normal) ghc/alloc 3,629,760,116 3,711,852,800 +2.3% BAD MultiLayerModulesTH_OneShot(normal) ghc/alloc 2,502,735,440 2,565,282,888 +2.5% BAD T12707(normal) ghc/alloc 804,399,798 791,807,320 -1.6% GOOD T17516(normal) ghc/alloc 964,987,744 1,008,383,520 +4.5% T18140(normal) ghc/alloc 75,381,152 49,860,560 -33.9% GOOD T18698b(normal) ghc/alloc 232,614,457 184,262,736 -20.8% GOOD T18923(normal) ghc/alloc 62,002,368 58,301,408 -6.0% GOOD T20049(normal) ghc/alloc 75,719,168 70,494,368 -6.9% GOOD T3294(normal) ghc/alloc 1,237,925,833 1,157,638,992 -6.5% GOOD T9233(normal) ghc/alloc 686,490,105 635,166,688 -7.5% GOOD geo. mean -0.7% minimum -33.9% maximum +4.5% I looked at T17516. It seems we do a few more simplifier iterations and end up with a larger program. It seems that some things inline more, while other things inline less. I don't see low-hanging fruit. I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that should better call-site inline, but does not. Perhaps with !11492. NoFib does not seem affected much either: +-------------------------------++--+------------+-----------+---------------+-----------+ | || | base/ | std. err. | T20749/ (rel) | std. err. | +===============================++==+============+===========+===============+===========+ | spectral/last-piece || | 7.263e8 | 0.0% | +0.62% | 0.0% | +===============================++==+============+===========+===============+===========+ | geom mean || | +0.00% | | | | +-------------------------------++--+------------+-----------+---------------+-----------+ I had a look at last-piece. Nothing changes in stg-final, but there is a bit of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in stg-final. Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com> Metric Decrease: T12707 T18140 T18698b T18923 T19695 T20049 T3294 T9233 T21839c Metric Increase: ManyConstructors MultiLayerModulesTH_OneShot - - - - - 0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00 Some renaming This is a pure refactor, tidying up some inconsistent naming: isEqPred --> isEqClassPred isEqPrimPred --> isEqPred isReprEqPrimPred --> isReprEqPred mkPrimEqPred --> mkNomEqPred mkReprPrimEqPred --> mkReprEqPred mkPrimEqPredRold --> mkEqPredRole Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek from GHC.Core.Coercion to GHC.Core.Predicate where they belong. That means that Coercion imports Predicate rather than vice versa -- better. - - - - - 15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00 compiler: Fix deriving with method constraints See Note [Inferred contexts from method constraints] Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00 EPA: Remove AddEpann commit 7 EPA: Remove [AddEpAnn] from HYPHEN in Parser.y The return value is never used, as it is part of the backpack configuration parsing. EPA: Remove last [AddEpAnn] usages Remove residual usage in GHC. It is still used - In haddock TTG extension point definitions (to be removed) - Some check-exact residual, to be removed - Comments around DisambECP in PostProcess EPA: Clean up [AddEpAnn] from check-exact There is one left, to be cleaned up when we remove AddEpann itself EPA: Remove [AddEpAnn] from haddock The TTG extension points need a value, it is not critical what that value is, in most cases. EPA: Remove AddEpAnn from HsRuleAnn EPA: Remove AddEpAnn from HsCmdArrApp - - - - - 23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00 Fix optimisation of InstCo It turned out (#25387) that the fix to #15725 was not quite right: commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7 Date: Mon Oct 15 10:25:02 2018 +0200 Fix #15725 with an extra Sym Optimising InstCo is quite subtle, and the invariants surrounding the LiftingContext in the coercion optimiser were not stated explicitly. This patch refactors the InstCo optimisation, and documents these invariants. See * Note [Optimising InstCo] * Note [The LiftingContext in optCoercion] I also did some refactoring of course: * Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag * I added some invariant-checking the coercion-construction functions in GHC.Core.Coercion.Opt. (Sadly these invariants don't hold during typechecking, becuase the types are un-zonked, so I can't put these checks in GHC.Core.Coercion.) - - - - - 589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00 ghcid: use multi repl for ghcid - - - - - d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00 documentation: add motivating section to Control.Monad.Fix - - - - - 301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00 wasm: fix safari console error message related to import("node:timers") This patch fixes the wasm backend JSFFI prelude script to avoid calling `import("node:timers")` on non-deno hosts. Safari doesn't like it and would print an error message to the console. Fixes https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13. - - - - - 9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00 Add a missing tidy in UnivCo We were failing to tidy the argument coercions of a UnivCo, which led directly to #25391. The fix is, happily, trivial. I don't have a small repro case (it came up when building horde-ad, which uses typechecker plugins). It should be possible to make a repro case, by using a plugin (which builds a UnivCo) but I decided it was not worth the bother. The bug is egregious and easily fixed. - - - - - 853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00 Bump text submodule to 2.1.2 - - - - - 90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00 hadrian: allow -Wunused-imports for text package - - - - - 8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00 EPA: Remove AddEpAnn Commit 8/final EPA: Remove AddEpAnn from AnnList EPA: Remove AddEpAnn from GrhsAnn This is the last actual use EPA: Remove NameAdornment from NameAnn Also rework AnnContext to use EpToken, and AnnParen EPA: Remove AddEpAnn. Final removal There are now none left, except for in a large note/comment in PostProcess, describing the historical transition to the disambiguation infrastructure - - - - - d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00 EPA: Remove AnnKeywordId. This was used as part of AddEpAnn, and is no longer needed. Also remove all the haddock comments about which of are attached to the various parts of the AST. This is now clearly captured in the appropriate TTG extension points, and the `ExactPrint.hs` file. - - - - - e08b8370 by Serge S. Gulin at 2024-10-29T23:17:01-04:00 JS: Re-add optimization for literal strings in genApp (fixes #23479) Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/ Co-authored-by: Sylvain Henry <sylvain at haskus.fr> Co-authored-by: Andrei Borzenkov <root at sandwitch.dev> Co-authored-by: Danil Berestov <goosedb at yandex.ru> ------------------------- Metric Decrease: T25046_perf_size_gzip size_hello_artifact size_hello_artifact_gzip size_hello_unicode size_hello_unicode_gzip ------------------------- - - - - - e3496ef6 by Cheng Shao at 2024-10-29T23:17:37-04:00 compiler: remove unused hscDecls/hscDeclsWithLocation This patch removes unused `hscDecls`/`hscDeclsWithLocation` functions from the compiler, to reduce maintenance burden when doing refactorings related to ghci. - - - - - b1eed26f by Cheng Shao at 2024-10-29T23:18:13-04:00 testsuite: add T25414 test case marked as broken This commit adds T25414 test case to demonstrate #25414. It is marked as broken and will be fixed by the next commit. - - - - - e70009bc by Cheng Shao at 2024-10-29T23:18:13-04:00 driver: fix foreign stub handling logic in hscParsedDecls This patch fixes foreign stub handling logic in `hscParsedDecls`. Previously foreign stubs were simply ignored here, so any feature that involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch reuses `generateByteCode` logic and eliminates a large chunk of duplicate logic that implements Core to bytecode generation pipeline here. Fixes #25414. - - - - - 1d7cd7fe by Andreas Klebinger at 2024-10-30T19:14:28-04:00 Add since tag for -fwrite-if-compression in user guide. Partial fix for #25395 - - - - - b349fd1b by Alan Zimmerman at 2024-10-30T19:15:04-04:00 EPA: Remove some unused functions - - - - - f859d61c by Alan Zimmerman at 2024-10-30T19:15:04-04:00 EPA: use explicit vertical bar token for ExplicitSum / SumPat - - - - - 721ac00d by Ben Gamari at 2024-10-31T08:37:38-04:00 rts/Disassembler: Fix encoding of BRK_FUN instruction The offset of the CC field was not updated after the encoding change in b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this. Fixes #25374. - - - - - 0bc94360 by Alan Zimmerman at 2024-10-31T08:38:15-04:00 EPA: Bring in last EpToken usages For import declarations, NameAnnCommas and NPlusKPat. And remove anchor, it is the same as epaLocationRealSrcSpan. - - - - - 0b11cdc0 by sheaf at 2024-10-31T08:38:55-04:00 Assert that ctEvCoercion is called on an equality Calling 'ctEvCoercion' on non-equality constraints is always incorrect. We add an assertion to this function to detect such cases; for example a type-checking plugin might erroneously do this. - - - - - ea458779 by doyougnu at 2024-11-01T18:11:33-04:00 ghc-internal: strict, unboxed src loc ranges - closes: #20449 - See CLC proposal: #55 - - - - - 778ac793 by Kazuki Okamoto at 2024-11-01T18:12:13-04:00 No haddock markup in doctest line - - - - - cf0deeaf by Andreas Klebinger at 2024-11-02T17:54:52-04:00 Reword -fexpose-overloaded-unfoldings docs. This should make them slightly clearer. Fixes #24844 Co-authored-by: Sylvain Henry <sylvain at haskus.fr> - - - - - 1c21e7d4 by Andreas Klebinger at 2024-11-02T17:55:29-04:00 Compile T25062 simd tests even if we can't run them. Helps avoid them being utterly broken. Fixes #25341 - - - - - 573cad4b by Cheng Shao at 2024-11-02T17:56:04-04:00 Remove unused USE_REPORT_PRELUDE code paths from the tree This patch removes unused `USE_REPORT_PRELUDE` code paths from the tree. They have been present since the first git revision 4fb94ae5e5d632748fa2e6c35e259eccc5a1a3f4, and might have been useful for debugging purposes many years ago, but these code paths are never actually built. Removing these ease maintenance of relevant modules in the future, and also allows us to get rid of `CPP` extension in those modules as a nice byproduct. - - - - - 97f600c6 by Hassan Al-Awwadi at 2024-11-04T15:52:12+00:00 Refactored BooleanFormula to be in line with TTG (#21592) There are two parts to this commit. * We moved the definition of BooleanFormula over to L.H.S.BooleanFormula * We parameterized the BooleanFormula over the pass The GHC specific details of BooleanFormula remain in Ghc.Data.BooleanFormula. Because its parameterized over the pass its no longer a functor or traversable, but we defined bfMap and bfTraverse for the cases where we needed fmap and traverse originally. Most other changes are just churn. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - d4fd3580 by Andreas Klebinger at 2024-11-05T07:36:16-05:00 ghc-heap: Fix incomplete selector warnings. Use utility functions instead of selectors to read partial attributes. Part of fixing #25380. - - - - - fdd9f62a by Peter Trommler at 2024-11-05T07:36:51-05:00 PPC NCG: Implement fmin and fmax - - - - - 8e217256 by Mike Pilgrem at 2024-11-07T04:34:20-05:00 Re CLC #293 - Don't specify Data.List.NonEmpty in terms of partial See https://github.com/haskell/core-libraries-committee/issues/293 `List.init` had already been driven out of `tails1` by 21fc180bec93d964a7f4ffdf2429ef6f74b49ab6 but this specification also avoided partial `fromList`, so I preferred it. The `changelog.md` for `base` is updated, with an entry added under `base-4.22.0.0`. - - - - - 346e4cd1 by Zubin Duggal at 2024-11-07T04:34:57-05:00 release: copy zip files into the correct directory Fixes #25446 - - - - - bbdbe225 by Zubin Duggal at 2024-11-07T04:34:57-05:00 release: Sign .gz bindists too Fixes #25447 - - - - - 0c722e14 by Hécate Kleidukos at 2024-11-07T04:35:37-05:00 hadrian: Enforce the usage of GHC >=9.8.1 for ghci-multi GHC 9.6 no good when it comes to multi-repl stuff, despite being well within the range of n-2 releases for bootstrapping, when the script was adapted to load haddock, in !12851 - - - - - d8f8a1c3 by Sylvain Henry at 2024-11-07T19:27:46-05:00 Handle the special ghc-prim:GHC.Prim module in the compiler Before this patch, some custom hacks were necessary in ghc-prim's Setup.hs to register the GHC.Prim (virtual) module and in Hadrian to generate haddocks properly. In this patch we special-case this module in the compiler itself instead (which it already is, see ghcPrimIface in GHC.Iface.Load). From Cabal/Hadrian's perspective GHC.Prim is now just a normal autogenerated module. This simplification is worthwhile on its own. It was found while looking into the work needed for #24453 which aims to merge ghc-prim, ghc-bignum, and ghc-internal. It's also one step closer to remove ghc-prim's custom setup. - - - - - a55adc8e by Cheng Shao at 2024-11-07T19:28:22-05:00 Clean up obsolete CPP guarded code paths from the tree This patch cleans up obsolete CPP guarded code paths from the tree. The minimum supported boot GHC version is 9.6, and all the pre-9.6 era code paths can be removed. - - - - - 9ede97f3 by Cheng Shao at 2024-11-07T19:28:58-05:00 Remove obsolete executable wrappers from the tree The executable wrappers are handled by hadrian and bindist Makefile. The various .wrapper scripts in the tree are unused since removal of Make build system, so this patch removes them all. - - - - - 7d42b2df by tristian at 2024-11-07T19:29:40-05:00 TcRnDuplicateDecls now suggests to use the DuplicateRecordFields extension. Fixes: !24627 - - - - - e56ed179 by Zubin Duggal at 2024-11-11T15:16:35+05:30 testsuite: normalise some versions in callstacks (cherry picked from commit f230e29f30d0c1c566d4dd251807fcab76a2710e) - - - - - a28fc903 by Zubin Duggal at 2024-11-11T15:16:35+05:30 testsuite: use -fhide-source-paths to normalise some backpack tests (cherry picked from commit b19de476bc5ce5c7792e8af1354b94a4286a1a13) - - - - - ed16d303 by Zubin Duggal at 2024-11-11T15:16:36+05:30 testsuite/haddock: strip version identifiers and unit hashes from html tests (cherry picked from commit fbf0889eadc410d43dd5c1657e320634b6738fa5) - - - - - e45e5836 by Zubin Duggal at 2024-11-11T15:16:36+05:30 haddock: oneshot tests can drop files if they share modtimes. Stop this by including the filename in the key. Ideally we would use `ghc -M` output to do a proper toposort Partially addresses #25372 (cherry picked from commit e78c7ef96e395f1ef41f04790aebecd0409b92b9) - - - - - 9104e6eb by Zubin Duggal at 2024-11-11T15:16:36+05:30 testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences (cherry picked from commit a79a587e025d42d34bb30e115fc5c7cab6c1e030) - - - - - 2c31264a by Zubin Duggal at 2024-11-11T15:16:36+05:30 testsuite: normalise windows file seperators (cherry picked from commit f858875e03b9609656b542aaaaff85ad0a83878a) - - - - - 2807f91b by Zubin Duggal at 2024-11-11T15:21:30+05:30 testsuite: Also match <VERSION> placeholders when normalising callsites - - - - - c02add17 by Ben Gamari at 2024-11-12T01:22:11-05:00 configure: Check version number validity Here we verify the previously informal invariant that stable release version numbers must have three components, preventing costly failed releases. Specifically, the check fails in the following scenarios: * `version=9.13` while `RELEASE=YES` since this would imply a release made from an unstable branch * `version=9.13.0` since unstable versions should only have two components * `version=9.12` since this has the wrong number of version components for a stable branch Fixes #25390. - - - - - 747fd322 by Teo Camarasu at 2024-11-12T01:22:49-05:00 docs: link to #14474 in the template-haskell docs - - - - - 6d96bb62 by Zubin Duggal at 2024-11-12T01:23:25-05:00 testsuite: normalise execvp vs exec differences in process tests Fixes #25431 - - - - - 502e6711 by Torsten Schmits at 2024-11-12T01:24:01-05:00 fix test lint that accumulated while the checks were broken I didn't fix the issues flagged by the #ifdef linter because it were so many that it seemed like the rule has become obsolete. - - - - - 223a4cb5 by Torsten Schmits at 2024-11-12T01:24:02-05:00 test driver: fix file collection for regex linters When a testsuite linter is executed with the `tracked` strategy, the driver runs `git ls-tree` to collect eligible files. This appears to have ceased producing any paths – `ls-tree` restricts its results to the current working directory, which is `testsuite/tests/linters` in this case. As a quick fix, this patch changes the working directory to match expectations. - - - - - 9ad9ac63 by Alan Zimmerman at 2024-11-12T01:24:39-05:00 EPA: Capture location of '_' for wild card type binder And keep track of promotion status in HsExplicitTupleTy, so the round-trip ppr test works for it. Updates Haddock output too, using the PromotionFlag in HsExplicitTupleTy. Closes #25454 - - - - - c37b96fa by Cheng Shao at 2024-11-12T01:25:15-05:00 wasm: fix setImmediate() implementation for Cloudflare Workers This patch fixes setImmediate() implementation for Cloudflare Workers in the wasm backend's js prelude script. Cloudflare Workers doesn't support the MessageChannel API, and we use a setTimeout() based fallback implementation in this case. - - - - - bea8ea4c by Cheng Shao at 2024-11-12T01:25:15-05:00 wasm: fix FinalizationRegistry logic for Cloudflare Workers This patch fixes FinalizationRegistry related logic for Cloudflare Workers in wasm backend js post linker. Cloudflare Workers doesn't support FinalizationRegistry, in this case we use a dummy implementation that doesn't do anything. - - - - - 00d551bf by Cheng Shao at 2024-11-13T08:48:21-05:00 Remove obsolete cross-port script This patch removes the obsolete cross-port script in the tree. The script was based on the legacy Make build system which has been pruned from the tree long ago. For hadrian, proper support for two-stage bootstrapping onto a new unsupported platform is a work in progress in !11444. - - - - - 75a2eae4 by Cheng Shao at 2024-11-13T08:48:58-05:00 hadrian: fix bindist makefile for wasm32-wasi target This patch fixes one incoherent place between bindist makefile and hadrian logic: I forgot to include wasi/wasm32 in OsSupportsGHCi/ArchSupportsGHCi as well. And this results in incorrect settings file generated after installing the bindist, and "Use interpreter"/"Have interpreter" fields incorrectly have "NO" values where they should be "YES" like --info output of in-tree version. - - - - - 0614abef by Alan Zimmerman at 2024-11-13T08:49:34-05:00 EPA: Correctly capture leading semis in decl list Closes #25467 - - - - - 00d58ae1 by Sebastian Graf at 2024-11-13T15:21:23-05:00 DmdAnal: Make `prompt#` lazy (#25439) This applies the same treatment to `prompt#` as for `catch#`. See `Note [Strictness for mask/unmask/catch/prompt]`. Fixes #25439. - - - - - 93233a66 by Ben Gamari at 2024-11-13T15:21:59-05:00 boot: Do not attempt to update config.sub While Apple ARM hardware was new we found that the autoconf scripts included in some boot packages were too old. As a mitigation for this, we introduced logic in the `boot` script to update the `config.sub` with that from the GHC tree. However, this causes submodules which have `config.sub` committted to appear to be dirty. This is a considerable headache. Now since `config.sub` with full platform support is more common we can remove `boot`'s `config.sub` logic. Fixes #19574. - - - - - fa66fa64 by Ryan Scott at 2024-11-14T19:05:00-05:00 Add regression test for #16234 Issue #16234 was likely fixed by !9765. This adds a regression test to ensure that it remains fixed. Fixes #16234. - - - - - bfe64df8 by Matthew Pickering at 2024-11-14T19:05:36-05:00 ghc-internal: Update to Unicode 16 This patch updates the automatically generated code for querying unicode properties to unicode 16. Fixes #25402 - - - - - 1fd83f86 by Ben Gamari at 2024-11-14T19:06:13-05:00 configure: Accept happy-2.1.2 happy-2.1 was released in late Oct 2024. I have confirmed that master bootstraps with it. Here we teach configure to accept this tool. Fixes #25438. - - - - - aa58fc5b by Ben Gamari at 2024-11-14T19:06:49-05:00 rts: Tighten up invariants of PACK - - - - - 8aa4c10a by Ben Gamari at 2024-11-14T19:06:49-05:00 testsuite: Fix badly escaped literals Use raw string literals to ensure that `\s` is correctly interpreted as a character class. - - - - - 0e084029 by Ben Gamari at 2024-11-14T19:06:49-05:00 rts: Improve documentation of SLIDE bytecode instruction - - - - - 9bf3663b by Ben Gamari at 2024-11-14T19:06:49-05:00 rts/Interpreter: Assert that TEST*_P discriminators are valid - - - - - 1f668511 by Ben Gamari at 2024-11-14T19:06:49-05:00 rts/Interpreter: Improve documentation of TEST*_P instructions - - - - - 59e0a770 by Cheng Shao at 2024-11-14T19:07:25-05:00 misc: improve clangd compile_flags.txt flags This patch improves the compile_flags.txt config used to power clangd for the rts C codebase. The flags in the file are sampled & deduped from a real stage1 build with clang-19 and vastly improves the IDE accuracy when hacking the rts. For maximum code coverage under the default settings, compile_flags.txt defaults to threaded+profiled+dynamic+debug way. This does not mean profdyn needs to be actually built in _build/stage1 for IDE to work. To activate IDE for other RTS ways, simply remove one of the -D flags at the end of compile_flags.txt and restart clangd. - - - - - c2c562e0 by Ben Gamari at 2024-11-14T19:08:01-05:00 testsuite: Don't consider untracked files in dirtiness check Considering trees containing untracked files as dirty is a bridge too far. The chance of an untracked file significantly affecting measured performanced metrics is quite small whereas not collecting measurements is quite inconvenient for some workflows. We now ignore untracked files in the dirtiness check. Fixes #25471. - - - - - ed2ed6c5 by Cheng Shao at 2024-11-14T19:08:37-05:00 testsuite: add regression test T25473 This commit adds regression test T25473 marked as broken due to #25473. It will be fixed in the subsequent commit. - - - - - bd0a8b7e by Cheng Shao at 2024-11-14T19:08:37-05:00 wasm: fix foreign import javascript "wrapper" in TH/ghci This patch fixes foreign import javascript "wrapper" in wasm backend's TH/ghci by fixing the handling of dyld/finalization_registry magic variables. Fixes T25473 and closes #25473. - - - - - f1b0bc32 by Ben Gamari at 2024-11-14T19:09:13-05:00 rts/linker: Make FreeBSD declarations proper prototypes The iconv declarations for FreeBSD were previously not prototypes, leading to warnings. - - - - - 086cbbc1 by Ben Gamari at 2024-11-14T19:09:13-05:00 base: Drop redundant import in FreeBSD ExecutablePath implementation - - - - - 79ecd199 by Ben Gamari at 2024-11-14T19:09:13-05:00 compiler: Fix partial selector warnings in GHC.Runtime.Heap.Inspect - - - - - 1acb73bf by Andrew Lelechenko at 2024-11-15T06:10:47-05:00 gitlab: mention CLC in MR template - - - - - 8f2e0832 by Ben Gamari at 2024-11-15T06:11:24-05:00 rts: Allow use of GNU-stack notes on FreeBSD Previously we gated use of GNU-style non-executable stack notes to only apply on Linux. However, these are also supported by FreeBSD, which also uses ELF. Fix this. Fixes #25475. - - - - - 2c427cb0 by Ben Gamari at 2024-11-16T05:27:40-05:00 rts: Fix EINTR check in timerfd ticker When `poll` failed we previously checked that `errno == -EINTR` to silence the failure warning. However, this is wrong as `errno` values are generally not negated error codes (in contrast to many system call results, which is likely what the original author had in mind). Fixes #25477. - - - - - a0fa4941 by Ben Gamari at 2024-11-16T05:28:16-05:00 rts: Increase gen_workspace alignment to 128 bytes on AArch64 Increase to match the 128-byte cache-line size of Apple's ARMv8 implementation. Closes #25459. - - - - - 142d8afa by Ben Gamari at 2024-11-16T16:20:47-05:00 rts/RtsFlags: Refactor size parsing This makes a number of improvements mentioned in #20201: * fail if the argument cannot be parsed as a number (`-Mturtles`) * fail if an unrecognized unit is given (e.g. `-M1x`) - - - - - b7a146e5 by Ben Gamari at 2024-11-16T16:20:47-05:00 testsuite: Add tests for RTS flag parsing error handling See #20201. - - - - - ddb7afa6 by Ben Gamari at 2024-11-16T16:21:23-05:00 users guide: Mention language extensions in equality constraints discussion As suggested in #24127, mention the language extensions necessary for usage of equality constriants in their documentation. Closes #24127. - - - - - 36133dac by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide/9.14.1-notes: Fix list syntax - - - - - 888de658 by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide/debug-info: Fix duplicate flag descriptions - - - - - f120e427 by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide: Fix reference to 9.14.1 release notes - - - - - 8e975032 by Ben Gamari at 2024-11-16T16:21:59-05:00 Introduce GHC.Tc.Plugin.lookupTHName This makes it significantly more convenient (and less GHC-version-dependent) to resolve a template-haskell name into a GHC Name. As proposed in #24741. - - - - - a0e168ec by ARATA Mizuki at 2024-11-16T16:22:40-05:00 x86 NCG SIMD: Lower packFloatX4#, insertFloatX4# and broadcastFloatX4# to SSE1 instructions Fixes #25441 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 3936bf1b by sheaf at 2024-11-16T16:23:22-05:00 X86 NCG: allow VXOR at scalar floating-point types The NCG can emit VXOR instructions at scalar floating-point types, but the pretty-printer would panic instead of emitting the appropriate VXORPS/VXORPD instructions. This patch rectifies that oversight. Fixes #25455 - - - - - d9dff93a by Ben Gamari at 2024-11-16T16:23:58-05:00 rts: Fix platform-dependent pointer casts Previously we had unnecessary (and incorrect) platform-dependent casts to turn `OSThreadIds`s into a integer. We now just uniformly cast first to a `uintptr_t` (which is always safe, regardless of whether `OSThreadId` is a pointer), and then cast to the desired integral type. This fixes a warning on musl platforms. - - - - - 6d95cdb8 by Ben Gamari at 2024-11-16T16:24:34-05:00 testsuite: Mark encoding004 as broken on FreeBSD Due to #22003, CP936 fails to roundtrip: ```diff == CP936 +Failed to roundtrip given mutant byte at index 891 (251 /= 123 at index 891) +Failed to roundtrip given mutant byte at index 1605 (197 /= 69 at index 1605) +Failed to roundtrip given mutant byte at index 2411 (235 /= 107 at index 2411) +Failed to roundtrip given mutant byte at index 6480 (208 /= 80 at index 6480) +Failed to roundtrip given mutant byte at index 6482 (210 /= 82 at index 6482) +Failed to roundtrip given mutant byte at index 6484 (212 /= 84 at index 6484) +Failed to roundtrip given mutant byte at index 6496 (224 /= 96 at index 6496) +Failed to roundtrip given mutant byte at index 7243 (203 /= 75 at index 7243) +Failed to roundtrip given mutant byte at index 7277 (237 /= 109 at index 7277) +Failed to roundtrip given mutant byte at index 8027 (219 /= 91 at index 8027) +Failed to roundtrip given mutant byte at index 8801 (225 /= 97 at index 8801) ``` - - - - - 26e86984 by Ben Gamari at 2024-11-18T04:05:31-05:00 hadrian: Allow haddock options to be passed via key-value settings - - - - - 6e68b117 by Matthew Pickering at 2024-11-18T04:06:07-05:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - a4e0d235 by Rodrigo Mesquita at 2024-11-18T04:06:07-05:00 exceptions: Improve the message layout as per #285 This commit fixes the layout of the additional information included when displaying an exception, namely the type of the exception. It also fixes the default handler's heading message to work well together with the improved display message of SomeException. CLC proposal#285 - - - - - 284ffab3 by Rodrigo Mesquita at 2024-11-18T04:06:07-05:00 Display type and callstack of exception on handler This commit changes the Exception instance of SomeException to *simply* display the underlying exception in `displayException`. The augmented exception message that included the type and backtrace of the exception are now only printed on a call to `displayExceptionWithInfo`. At a surface level, existing programs should behave the same since the `uncaughtExceptionHandler`, which is responsible for printing out uncaught exceptions to the user, will use `displayExceptionWithInfo` by default. However, unlike the instance's `displayException` method, the `uncaughtExceptionHandler` can be overriden with `setUncaughtExceptionHandler`. This makes the extra information opt-in without fixing it the instance, which can be valuable if your program wants to display uncaught exceptions to users in a user-facing way (ie without backtraces). This is what was originally agreed for CLC#231 or CLC#261 with regard to the type of the exception information. The call stack also becoming part of the default handler rather than the Exception instance is an ammendment to CLC#164. Discussion of the ammendment is part of CLC#285. - - - - - 36cddd2c by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Remove redundant CallStack from exceptions Before the exception backtraces proposal was implemented, ErrorCall accumulated its own callstack via HasCallStack constraints, but ExceptionContext is now accumulated automatically. The original ErrorCall mechanism is now redundant and we get a duplicate CallStack Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall CLC proposal#285 Fixes #25283 - - - - - 7a74330b by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Freeze call stack in error throwing functions CLC proposal#285 - - - - - 3abf31a4 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 De-duplicate displayContext and displayExceptionContext The former was unused except for one module where it was essentially re-defining displayExceptionContext. Moreover, this commit extends the fix from bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too, which was missing. - - - - - c0d783f8 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Re-export NoBacktrace from Control.Exception This was originally proposed and accepted in section "2.7 Capturing Backtraces on Exceptions" of the CLC proposal for exception backtraces. However, the implementation missed this re-export, which this commit now fixes. - - - - - 802b5c3e by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Fix exception backtraces from GHCi When running the program with `runhaskell`/`runghc` the backtrace should match the backtrace one would get by compiling and running the program. But currently, an exception thrown in a program interpreted with `runhaskell` will: * Not include the original exception backtrace at all * Include the backtrace from the internal GHCi/ghc rethrowing of the original exception This commit fixes this divergence by not annotating the ghc(i) backtrace (with NoBacktrace) and making sure that the backtrace of the original exception is serialized across the boundary and rethrown with the appropriate context. Fixes #25116 The !13301 MR (not this commit in particular) improves performance of MultiLayerModules. Unfortunately, T3294 regresses on aarch64-linux-deb12 by 1% allocations. Since this patch must be merged for 9.12 ASAP, we will not be able to investigate the slight regression on this platform in time. ------------------------- Metric Decrease: MultiLayerModulesRecomp MultiLayerModulesTH_OneShot Metric Increase: T3294 ------------------------- - - - - - 3e89eb65 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 base: Add to changelog.md CLC #285 - - - - - d9326a48 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Bump array and stm submodules for testsuite The testsuites of array and stm had to be updated according to !13301. Updates submodule array and stm. - - - - - 325fcb5d by Ben Gamari at 2024-11-18T04:06:45-05:00 rts/adjustor: Clean up code style of Nativei386 adjustor - - - - - 39bb6e58 by Ben Gamari at 2024-11-18T04:06:45-05:00 rts/adjustor: Fix stack overrun error in Nativei386 adjustor We were reserving the wrong kind of adjustor context (the generic `AdjustorContext` used by other adjustor implementations, rather than the i386-specific `CCallContext`) to return the adjustor context while freeing, resulting in #25485. Fixes #25485. - - - - - 831aab22 by sheaf at 2024-11-18T21:22:36-05:00 Include diagnostic reason in -fdiagnostics-as-json This commit ensures that the -fdiagnostics-as-json output includes the diagnostic reason. This allows the full error message produced by GHC to be re-constructed from the JSON output. Fixes #25403 - - - - - 3e5bfdd3 by Ben Gamari at 2024-11-18T21:23:12-05:00 rts: Introduce printIPE This is a convenience utility for use in GDB. - - - - - 44d909a3 by Sjoerd Visscher at 2024-11-19T14:38:24-05:00 Don't store boot locations in finder cache Partially reverts commit fff55592a7b Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache. Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for. - - - - - 64c95292 by Sjoerd Visscher at 2024-11-19T14:38:24-05:00 Concentrate boot extension logic in Finder With new mkHomeModLocation that takes an extra HscSource to add boot extensions if required. - - - - - 11bad98d by ARATA Mizuki at 2024-11-19T14:39:08-05:00 Better documentation for floating-point min/max and SIMD primitives See #25350 for floating-point min/max Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 791a47b2 by Arnaud Spiwack at 2024-11-20T14:00:05+00:00 Add test for #25185 - - - - - 374e18e5 by Arnaud Spiwack at 2024-11-20T14:09:30+00:00 Quick look: emit the multiplicity of app heads in tcValArgs Otherwise it's not scaled properly by the context, allowing unsound expressions. Fixes #25185. - - - - - 1fc02399 by sheaf at 2024-11-20T18:11:03-05:00 x86 NCG: fix regUsageOfInstr for VMOVU & friends This commit fixes the implementation of 'regUsageOfInstr' for vector operations that take an 'Operand' as the destination, by ensuring that when the destination is an address then the address should be *READ*, and not *WRITTEN*. Getting this wrong is a disaster, as it means the register allocator has incorrect information, which can lead to it discard stores to registers, segfaults ensuing. Fixes #25486 - - - - - 7bd407a6 by Brandon Chinn at 2024-11-21T14:08:15-05:00 Fix CRLF in multiline strings (#25375) - - - - - 7575709b by Rodrigo Mesquita at 2024-11-21T14:08:52-05:00 Improve reachability queries on ModuleGraph Introduces `ReachabilityIndex`, an index constructed from a `GHC.Data.Graph.Directed` `Graph` that supports fast reachability queries (in $O(1)$). This abstract data structure is exposed from `GHC.Data.Graph.Directed.Reachability`. This index is constructed from the module graph nodes and cached in `ModuleGraph`, enabling efficient reachability queries on the module graph. Previously, we'd construct a Map of Set of ModuleGraph nodes which used a lot of memory (`O(n^2)` in the number of nodes) and cache that in the `ModuleGraph`. By using the reachability index we get rid of this space leak in the module graph -- even though the index is still quadratic in the number of modules, it is much, much more space efficient due to its representation using an IntMap of IntSet as opposed to the transitive closure we previously cached. In a memory profile of MultiLayerModules with 100x100 modules, memory usage improved from 6GB residency to 2.8GB, out of which roughly 1.8GB are caused by a second space leak related to ModuleGraph. On the same program, it brings compile time from 7.5s to 5.5s. Note how we simplify `checkHomeUnitsClosed` in terms of `isReachableMany` and by avoiding constructing a second graph with the full transitive closure -- it suffices to answer the reachability query on the full graph without collapsing the transitive closure completely into nodes. Unfortunately, solving this leak means we have to do a little bit more work since we can no longer cache the result of turning vertex indices into nodes. This results in a slight regression in MultiLayerModulesTH_Make, but results in large performance and memory wins when compiling large amounts of modules. ------------------------- Metric Decrease: mhu-perf Metric Increase: MultiLayerModulesTH_Make ------------------------- - - - - - bcbcdaaf by Cheng Shao at 2024-11-21T14:09:28-05:00 driver: fix hpc undefined symbol issue in TH with -fprefer-byte-code This commit fixes an undefined symbol error in RTS linker when attempting to compile home modules with -fhpc and -fbyte-code-and-object-code/-fprefer-byte-code, see #25510 for detailed description and analysis of the bug. Also adds T25510/T25510c regression tests to test make mode/oneshot mode of the bug. - - - - - 970ada5a by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Bump ci-images For introduction of Alpine/i386 image. Thanks to Julian for the base image. Co-Authored-By: Julian Ospald <hasufell at hasufell.de> - - - - - 8115abc2 by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Add release job for i386/Alpine As requested by Mikolaj and started by Julian. Co-Authored-By: Julian Ospald <hasufell at hasufell.de> - - - - - 639f0149 by Ben Gamari at 2024-11-22T23:32:06-05:00 rts/linker/Elf: Resolve _GLOBAL_OFFSET_TABLE_ - - - - - 490d4d0a by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Mark i386 Alpine test breakages Marks the following tests as broken on i386/Alpine: * T22033 due to #25497 * simd009, T25062_V16, T25169, T22187_run due to #25498 - - - - - 536cdf09 by Cheng Shao at 2024-11-22T23:32:42-05:00 compiler: remove unused GHC.Linker.Loader.loadExpr This patch removes the unused `GHC.Linker.Loader.loadExpr` function. It was moved from `GHC.Runtime.Linker.linkExpr` in `ghc-9.0` to `GHC.Linker.Loader.loadExpr` in `ghc-9.2`, and remain completely unused and untested ever since. There's also no third party user of this function to my best knowledge, so let's remove this. Anyone who wants to write their own GHC API function to load bytecode can consult the source code in older release branches. - - - - - 6ee35024 by Drew Fenwick at 2024-11-22T23:33:26-05:00 Fix a non-compiling example in the type abstractions docs This patch adds a missing Show constraint to a code example in the User Guide's type abstractions docs to fix issue #25422. - - - - - d1172e20 by Rodrigo Mesquita at 2024-11-22T23:34:02-05:00 Re-introduce ErrorCallWithLocation with a deprecation pragma With the removal of the duplicate backtrace, part of CLC proposal #285, the constructor `ErrorCallWithLocation` was removed from base. This commit re-introduces it with a deprecation. - - - - - 1187a60a by Ben Gamari at 2024-11-22T23:34:39-05:00 testsuite: Skip tests requiring Hadrian deps in out-of-tree testsuite runs Some testsuite tests require specific tools (e.g. `check-ppr` and `check-exact`) beyond those shipped in the binary distribution. Skip these tests. Fixes #13897. - - - - - c37d7a2e by Ben Gamari at 2024-11-22T23:34:39-05:00 testsuite: Declare exactprint tests' dependency on check-exact - - - - - 454ce957 by Ben Gamari at 2024-11-22T23:35:15-05:00 ghc-internal: Fix a few cases of missing Haddock markup - - - - - a249649b by Ben Gamari at 2024-11-22T23:35:51-05:00 testsuite/GHCiPrimCall : Add missing Makefile includes - - - - - a021a493 by Ben Gamari at 2024-11-22T23:35:51-05:00 testsuite/IpeStats: Use Make rather than shell interpolation - - - - - 6e1fbda7 by Ben Gamari at 2024-11-25T03:55:44-05:00 hadrian-ghci-multi: Pass -this-package-name in unit response files As noted in #25509, the `-this-package-name` must be passed for each package to ensure that GHC can response references to the packages' exposed modules via package-qualified imports. Fix this. Closes #25509. - - - - - a05e4a9b by Simon Hengel at 2024-11-25T03:56:33-05:00 Refactoring: Use `OnOff` more consistently for `Extension` - - - - - 7536181d by Matthew Pickering at 2024-11-25T14:00:07-05:00 driver: Always link against "base" package when one shot linking The default value for base-unit-id is stored in the settings file. At install time, this can be set by using the BASE_UNIT_ID environment variable. At runtime, the value can be set by `-base-unit-id` flag. For whether all this is a good idea, see #25382 Fixes #25382 - - - - - 7f90f319 by Andreas Klebinger at 2024-11-25T14:00:44-05:00 Compacting GC: Handle black holes in large objects. As #14497 showed black holes can appear inside large objects when we capture a computation and later blackhole it like we do for AP_STACK closures. Fixes #24791 - - - - - 291388e1 by Cheng Shao at 2024-11-25T14:01:19-05:00 ci: minor nix-in-docker improvements This patch makes some minor improvements re nix-in-docker logic in the ci configuration: - Update `nixos/nix` to the latest version - Apply $CPUS to `cores`/`max-jobs` to avoid oversubscribing while allowing a reasonable degree of parallelism - Remove redundant `--extra-experimental-features nix-command` in later `nix shell` invocations, it's already configured in `/etc/nix/nix.conf` - - - - - e684c406 by Cheng Shao at 2024-11-25T14:01:57-05:00 ci: avoid depending on stack job for test-bootstrap jobs This patch makes test-bootstrap related ci jobs only depend on hadrian-ghc-in-ghci job to finish, consistent with other jobs in the full-build stage generated by gen_ci.hs. This allows the jobs to be spawned earlier and improve overall pipeline parallelism. - - - - - caaf5388 by Simon Hengel at 2024-11-25T14:02:41-05:00 Refactoring: Remove `pSupportedExts` from `ParserOpts` This is never used for lexing / parsing. It is only used by `GHC.Parser.Header.getOptions`. - - - - - 41f8365c by Arnaud Spiwack at 2024-11-25T14:03:23-05:00 Add test for #25515 - - - - - 9279619f by Arnaud Spiwack at 2024-11-25T14:03:23-05:00 Desugar record notation with correct multiplicities Simply uses the multiplicity as stored in the field. As I'm writing this commit, the only possible multiplicity is 1, but !13525 is changing this. It's actually easier to take !13525 into account. Fixes #25515. - - - - - fcc3ae6e by Andreas Klebinger at 2024-11-26T08:24:58-05:00 Clarify INLINE unfolding optimization docs. Fixes #24660 - - - - - 88c4fe1d by Cheng Shao at 2024-11-26T08:25:34-05:00 rts: remove -Wl,-U,___darwin_check_fd_set_overflow hack This patch bumps macOS minimum SDK version to 11.0 for x86_64-darwin to align it with aarch64-darwin. This allows us to get rid of the horrible -Wl,-U,___darwin_check_fd_set_overflow hack, which is causing linker warnings and testsuite failures on macOS 15. Fixes #25504. - - - - - 53f978c0 by doyougnu at 2024-11-26T16:07:26-05:00 ghc-experimental: expose GHC.RTS.Flags, GHC.Stats See this CLC proposal: - https://github.com/haskell/core-libraries-committee/issues/289 and this CLC proposal for background: - https://github.com/haskell/core-libraries-committee/issues/288 Metric Decrease: MultiLayerModulesTH_OneShot - - - - - e70d4140 by Wang Xin at 2024-11-26T16:08:10-05:00 Add -mcmodel=medium moduleflag to generated LLVM IR on LoongArch platform With the Medium code model, the jump range of the generated jump instruction is larger than that of the Small code model. It's a temporary fix of the problem descriped in https://gitlab.haskell .org/ghc/ghc/-/issues/25495. This commit requires that the LLVM used contains the code of commit 9dd1d451d9719aa91b3bdd59c0c6679 83e1baf05, i.e., version 8.0 and later. Actually we should not rely on LLVM, so the only way to solve this problem is to implement the LoongArch backend. Add new type for codemodel - - - - - df42ba16 by Andreas Klebinger at 2024-11-27T11:40:49-05:00 Cmm constant folding: Narrow results to operations bitwidth. When constant folding ensure the result is still within bounds for the given type by explicitly narrowing the results. Not doing so results in a lot of spurious assembler warnings especially when testing primops. - - - - - bf3db97e by Ben Gamari at 2024-11-27T11:41:26-05:00 ghc-toolchain: Introduce basic flag validation We verify that required flags (currently `--output` and `--triple`) are provided. The implementation is truly awful, but so is getopt. Begins to address #25500. - - - - - a104508d by Ben Gamari at 2024-11-27T11:42:03-05:00 rts: Allow ExecPage to allocate anywhere in address space Currently the ExecPage facility has two users: * GHCi, for constructing info tables, and * the adjustor allocation path Despite neither of these have any spatial locality constraints ExecPage was using the linker's `mmapAnonForLinker`, which tries hard to ensure that mappings end up nearby the executable image. This makes adjustor allocation needlessly subject to fragmentation concerns. We now instead return less constrained mappings, improving the robustness of the mechanism. Addresses #25503. - - - - - c3fc9b86 by Ben Gamari at 2024-11-27T11:42:39-05:00 base: Fix incorrect mentions of GHC.Internal.Numeric These were incorrectly changed by the automated refactoring of the `ghc-internal` migration. Fixes #25521. - - - - - a362b943 by sheaf at 2024-11-27T23:44:28-05:00 Add checkExact to toolTargets This change means that the Hadrian multi target will include exactprint. In particular, this means that HLS will work on exactprint inside the GHC tree. - - - - - e6c957e4 by Arnaud Spiwack at 2024-11-27T23:45:09-05:00 Add test for #25428 - - - - - 52d97f4e by Arnaud Spiwack at 2024-11-27T23:45:09-05:00 Don't bypass MonoLocalBind in empty patterns Fixes #25428 - - - - - 7890f2d8 by Ben Gamari at 2024-11-28T10:26:46-05:00 hadrian: Bump directory bound to >=1.3.9 Earlier versions of `directory` are racy on Windows due to #24382. Also includes necessary Hadrian bootstrap plan bump. Fixes #24382. - - - - - 0fd43ea6 by Adam Sandberg Ericsson at 2024-11-28T10:27:22-05:00 mention -Iw in +RTS -? - - - - - 6cf579b9 by Ben Gamari at 2024-11-28T10:27:59-05:00 gitlab-ci: Set GIT_SUBMODULE_FORCE_HTTPS GitLab recommends using `https://` to clone submodules and provides the `GIT_SUBMODULE_FORCE_HTTPS` variable to force this. Fixes #25528. - - - - - 5b4774f9 by sheaf at 2024-12-03T15:22:07+01:00 Remove TcRnDeprecatedInvisTyArgInConPat mechanism The combination of ScopedTypeVariables + TypeApplications now no longer enables the use of type applications in constructor patterns, as per GHC proposal #448. This completes the deprecation that begun with GHC 9.8. We also remove the -Wdeprecated-type-abstractions flag, which was introduced in GHC 9.10. - - - - - f813c8d7 by sheaf at 2024-12-03T17:10:15-05:00 Hadrian: use / when making filepaths absolute In Hadrian, we are careful to use -/- rather than </>, in order to use / instead of \ in filepaths. However, this gets ruined by the use of makeAbsolute from System.Directory, which, on Windows, changes back forward slashes to backslashes. - - - - - 292ed74e by Ben Gamari at 2024-12-03T17:10:52-05:00 rts/linker: Fix out-of-bounds mapping logic Previously the structure of `mmapInRegion` concealed a subtle bug concerning handling of `mmap` returning mappings below the beginning of the desired region. Specifically, we would reset `p = result + bytes` and then again reset `p = region->start` before looping around for another iteration. This resulted in an infinite loop on FreeBSD. Fixes #25492. - - - - - 20912f5b by Ben Gamari at 2024-12-03T17:10:52-05:00 rts/linker: Clarify debug output - - - - - f98b3ac0 by Simon Hengel at 2024-12-03T17:11:30-05:00 SysTools: Avoid race conditions when processing output (fixes #16450) - - - - - 03851b64 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 mg: Drop unnecessary HasCallStack This HasCallStack was a debugging artifact from a previous commit. - - - - - 01d213b5 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 Improve haddock of graphReachabilityCyclic - - - - - f7cbffe2 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 Refactor ModuleGraph interface The 'ModuleGraph' abstraction represents the relationship and strucutre of the modules being compiled. This structure is meant to be constructed once at the start of compilation, and never changed again. However, it's exposed interface was confusing and exposed too many footguns which led to inneficient usages of the ModuleGraph. This commit improves significantly the exported interface of ModuleGraph, taking into consideration the recent improvements around reachability queries. Since the ModuleGraph graphs and related structures (HPT, EPS) are performance critical in the sense that somewhat simple mistakes can cause bad leaks and non-linear memory usage, we want to have proper APIs that guide efficient usage. This is a good step in that direction. - - - - - b69a7f3c by David Binder at 2024-12-04T18:37:42-05:00 Use consistent capitalization for "GHC Proposal" in user guide - - - - - 18d9500d by David Binder at 2024-12-04T18:37:42-05:00 Fix reference to GHC proposal 193 in user guide - - - - - dd959406 by Ben Gamari at 2024-12-04T18:38:18-05:00 Revert "rts/Interpreter: Assert that TEST*_P discriminators are valid" This assertion was based on the misconception that `GET_TAG` was returning the pointer tag whereas it is actually returning the constructor tag. This reverts commit 9bf3663b9970851e7b5701d68147450272823197. Fixes #25527. - - - - - cad6fede by Ben Gamari at 2024-12-04T18:38:54-05:00 rts/IOManager: Drop dead code This assignment is dead code as it occurs after all branches have returned. Moreover, it can't possibly be relevant since the "available" branch already sets `flag`. Potentially fixes #25542. - - - - - 55d8304e by Ben Gamari at 2024-12-06T16:56:00-05:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - 56b9f484 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 336d392e by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - dd7ca939 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Mention incorrect Data.Enum addition in changelog - - - - - dfd1db48 by Ben Gamari at 2024-12-06T16:56:36-05:00 base: Reintroduce {Show,Enum} IoSubSystem These instances were dropped in !9676 but not approved by the CLC. Addresses #25549. - - - - - 090fc7c1 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements on T25240 T25240 doesn't need RTS linker, GHCi is sufficient and GHCi can also be dynamically linked. - - - - - 3fb5d399 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements for T25155 Loading C objects requires RTS linker. - - - - - 4c58bdf6 by Leary at 2024-12-07T03:42:07-05:00 TH: Add typed variants of dataToExpQ and liftData This commit introduces to template-haskell (via ghc-internal) two functions `dataToCodeQ` and `liftDataTyped`, typed variants of `dataToExpQ` and `liftData` respectively. Tested in: `dataToCodeQUnit`. - - - - - 63027593 by Serge S. Gulin at 2024-12-08T13:52:05+03:00 JS: Basic cleanup for unused stuff to simplify things. 1. Make `staticInitStat`, `staticDeclStat`, `allocUnboxedConStatic`, `allocateStaticList`, `jsStaticArg` local to modules. 2. Remove unused `hdRawStr`, `hdStrStr` from Haskell and JavaScript (`h$pstr`, `h$rstr`, `h$str`). 3. Introduce a special type `StaticAppKind` enumeration and `StaticApp` to represent boxed scalar static applications. Originally, StaticThunk supported to pass Maybe when it became Nothing for initializied thunks in an alternatie way but it is not used anymore. - - - - - a9f8f1fb by Serge S. Gulin at 2024-12-08T14:10:45+03:00 JS: Add trivial optimizations for `unpackCString` and `unpackCStringUtf8`. It became possible due of introduction strings unfloating at Sinker pass (#13185). Earns few more bytes at optimizations. - - - - - b519c06b by Serge S. Gulin at 2024-12-08T15:50:26+03:00 JS: Specialize unpackCString# CAFs (fixes #24744) Code analysis shown that such optimization would be possible out of the box if `cachedIdentForId` allowed to do that for Haskell `Id`s which are represented by few JavaScript `Ident`s. It is a usual for strings which are represented at JavaScript as a pair of 2 values: the string content and the offset where to start reading actual string from the full content. Usually offset is 0 but technically we need to allow such complex structures to be treated as "global". Enabling it there shown that `genToplevelRhs` and `globalOccs` had inaccuracies in their implementations: 1. `globalOccs` operated over JavaScript's `Ident`s but for complex structures it didn't pay attention to the fact that different Idents actually could be pointed to same Id. Now the algo is changed to calculate occurencies for Ids. 2. `genToplevelRhs` didn't assume that different Idents pointed to same Id can have mixed order of occurence. But actually the order is important. Strings are encoded into 2 variables where first is content and second is offset and their order are not interchangeable. It is fixed by regeneration Idents from collected Ids which is fine because all Idents generation is passed through the Cache and they are quasi-stable. - - - - - a8ceccf3 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Fix panic in multiline string with unterminated gap (#25530) - - - - - 9e464ad0 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Add test case for unterminated multiline string - - - - - ed1ed5c6 by Rodrigo Mesquita at 2024-12-09T16:26:19-05:00 Revert mapMG renaming We had previously renamed this function for consistency, but that caused unnecessary breakage - - - - - 158261f7 by Sylvain Henry at 2024-12-09T16:27:01-05:00 RTS: make Cabal flags manual Cabal shouldn't automatically try to set them. We set them explicitly. - - - - - a83b7ed6 by Matthew Stephenson at 2024-12-10T14:01:22-05:00 Add missing @since documentation for (!?) function - - - - - e745e3a3 by Ben Gamari at 2024-12-10T14:01:59-05:00 compiler: Don't attempt to TSAN-instrument SIMD operations TSAN only provides instrumentation for 8, 16, 32, and 64-bit memory loads/stores. Don't attempt to instrument wider operations. Fixes #25563. - - - - - 684c0018 by Ben Gamari at 2024-12-10T14:02:35-05:00 gitlab/ci: Don't clobber RUNTEST_ARGS Previously the logic handling `IGNORE_PERF_FAILURES` clobbered the user's `RUNTEST_ARGS`. Fix this. - - - - - 41dae5b8 by Ben Gamari at 2024-12-10T14:03:11-05:00 hadrian: Mitigate mktexfmt race At least some versions of Texlive's `mktexfmt` utility cannot be invoked concurrently in their initial run since they fail to handle failure of `mkdir` due to racing. Specifically, we see ``` | Run Xelatex: users_guide.tex => /tmp/extra-dir-9616886274866 | Run Xelatex: Haddock.tex => /tmp/extra-dir-9616886274869 This is XeTeX, Version 3.14159265-2.6-0.999992 (TeX Live 2020) (preloaded format=xelatex) restricted \write18 enabled. kpathsea: Running mktexfmt xelatex.fmt mktexfmt: mktexfmt is using the following fmtutil.cnf files (in precedence order): mktexfmt: /usr/share/texlive/texmf-dist/web2c/fmtutil.cnf mktexfmt: mktexfmt is using the following fmtutil.cnf file for writing changes: mktexfmt: /builds/ghc/ghc/tmp-home/.texlive2020/texmf-config/web2c/fmtutil.cnf /usr/bin/mktexfmt: mkdir(/builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c/) failed for tree /builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c: File exists at /usr/share/texlive/tlpkg/TeXLive/TLUtils.pm line 937. I can't find the format file `xelatex.fmt'! ``` That is two `mktexfmt` invocations (for the user's guide and haddock builds) attempted to create `$HOME/texlive2020/texmf-var/web2c` and raced. One of the two `mkdir`'s consequently failed, bringing down the entire build. We avoid this by ensuring that the first `xelatex` invocation is always performed serially. Fixes #25564. - - - - - 9efbc51f by Ben Gamari at 2024-12-10T14:03:48-05:00 rts/CheckUnload: Reset old_objects if unload is skipped Previously `checkUnload` failed to reset `old_objects` when it decided not to unload (e.g. due to heap profiling being enabled). Fixes #24935. - - - - - 5192a75f by Ben Gamari at 2024-12-11T04:28:11-05:00 rts: Annotate BCOs with their Name This introduces a new bytecode instruction, `BCO_NAME`, to aid in debugging bytecode execution. This instruction is injected by `mkProtoBCO` and captures the Haskell name of the BCO. It is then printed by the disassembler, allowing ready correlation with STG dumps. - - - - - 99225996 by Ben Gamari at 2024-12-11T04:28:48-05:00 configure: Implement ld override whitelist Bring `configure` into alignment with `ghc-toolchain`, ensuring that the ld-override logic will only take effect on Linux and Windows. Fixes #25501. - - - - - 4a8fc928 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Unmark T14028 as broken on FreeBSD This now appears to pass on FreeBSD 14. Closes #19723. - - - - - d7c0eb5a by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Migrate FreeBSD runner tag to FreeBSD 14 - - - - - 7246dacc by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Reintroduce FreeBSD 14 job - - - - - 4af936da by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Allow use of newer cabal-install bindists Newer cabal-install bindists have internal directory structure. Here we detect and account for the presence of such structure. - - - - - cbf38c1b by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Enable documentation build on FreeBSD 14 - - - - - d68107fb by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Use system libffi on FreeBSD - - - - - fea3b590 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark linker_unload as broken on FreeeBSD Due to #25491. - - - - - ccf171ee by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Prefer system toolchain on FreeBSD It's not uncommon to find machines with gcc installed via ports. We should be using the system's default clang-based toolchain instead. - - - - - cfb34738 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T21969 as broken on FreeBSD Due to #25512. - - - - - 0b64e37c by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark RestartEventLogging as broken on FreeBSD I am seeing this fail quite reproducibly. Due to #19724. - - - - - 3b412019 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T16180 as "broken" on FreeBSD Sadly we in fact need to skip it as it merely times out during compilation. See #14012. - - - - - 57e3cab5 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Skip T16992 unless in slow speed This test has extraordinary memory requirements and tests a rather niche aspect of the compact region mechanism. It has been suggested multiple times that we shouldn't run it in the default testsuite configuration. Finally implement this. See #21890. See #21892. - - - - - f08a72eb by Ben Gamari at 2024-12-11T19:30:54-05:00 rts(setNumCapabilities): Assert that n_caps < MAX_N_CAPS It was noticed in #25560 that this would previously be allowed, resulting in a segfault. I will add a proper exception in `base` in a future commit. - - - - - e10d31ad by Ben Gamari at 2024-12-11T19:30:55-05:00 ghc-internal: Fix inconsistent FFI import types The foreign imports of `enabled_capabilities` and `getNumberOfProcessors` were declared as `CInt` whereas they are defined as `uint32_t`. - - - - - 06265655 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Mention maximum capability count in users guide Addresses #25560. - - - - - d488470b by Ben Gamari at 2024-12-11T19:30:55-05:00 rts/Capability: Move induction variable declaration into `for`s Just a stylistic change. - - - - - 71f050b7 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Determine max_n_capabilities at RTS startup Previously the maximum number of capabilities supported by the RTS was statically capped at 256. However, this bound is uncomfortably low given the size of today's machine. While supporting unbounded, fully-dynamic adjustment would be nice, it is complex and so instead we do something simpler: Probe the logical core count at RTS startup and use this as the static bound for the rest of our execution. This should avoid users running into the capability limit on large machines while avoiding wasting memory on a large capabilities array for most users and keeping complexity at bay. Addresses #25560. - - - - - 1e84b411 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Introduce req_c_rts As suggested by @hsyl20, this is intended to mark tests that rely on the behavior of the C RTS. - - - - - 683115a4 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Add test for #25560 - - - - - ef2052a8 by Ben Gamari at 2024-12-12T04:42:32-05:00 testsuite: Only run T14497_compact in normal way This test targets the compacting GC so it makes little sense to run it across all ways. Moreover, it outright conflicts with the `nonmoving` way. - - - - - 34d3e8e6 by Ben Gamari at 2024-12-12T04:43:08-05:00 rts/CheckUnload: Don't prepare to unload if we can't unload Previously `prepareUnloadCheck` would move the `objects` list to `old_objects` even when profiling (where we cannot unload). This caused us to vacate the `objects` list during major GCs, losing track of loaded objects. Fix this by ensuring that `prepareUnloadCheck` and `checkUnload` both use the same short-cutting logic. - - - - - 9c53489d by Andrei Borzenkov at 2024-12-12T15:06:42-05:00 Update GHCi :info type declaration printing (#24459) - Do not print result's kind in type families because we have full kind in SAKS and we display invisible arity using @-binders - Do not suppress significant invisible binders An invisible binder is considered significant when it meets at least one of the following two criteria: - It visibly occurs in the declaration's body - It is followed by a significant binder, so it affects positioning For non-generative type declarations (type synonyms and type families) there is one additional criterion: - It is not followed by a visible binder, so it affects the arity of a type synonym See Note [Print invisible binders in interface declarations] for more information about what is "visibly occurs" - - - - - 13fe48d4 by Matthew Pickering at 2024-12-12T15:07:19-05:00 typechecker: Perform type family consistency checks in topological order Consider a module M importing modules A, B and C. We can waste a lot of work depending on the order that the modules are checked for family consistency. Consider that C imports A and B. When compiling C we must have already checked A and B for consistency, therefore if C is processed first then A and B will not need to be checked for consistency again. If A and B are compared first, then the consistency checks will be performed against (wasted as we already performed them for C). At the moment the order which modules are checked is non-deterministic. Clearly we should engineer that C is checked before B and A, but by what scheme? A simple one is to observe that if a module M is in the transitive closure of X then the size of the consistent family set of M is less than or equal to size of the consistent family set of X. Therefore by sorting the imports by the size of the consistent family set and processing the largest first, you make sure to process modules in topological order. In practice we have observed that this strategy has reduced the amount of consistency checks performed. One solution to #25554 - - - - - 62a2b25f by Sylvain Henry at 2024-12-14T04:31:09-05:00 TNTC: set CmmProc entry_label properly (#25565) Before this patch we were renaming the entry label of a CmmProc late in the CmmToAsm pass. It led to inconsistencies and to some labels being used in info tables but not being emitted (#25565). Now we set the CmmProc entry label earlier in the StgToCmm monad and we don't renamed it afterwards. - - - - - b339e7c3 by Simon Hengel at 2024-12-14T04:31:47-05:00 Make filter functionality for system tools line-based This is more efficient as: - All existing filter functions were line-based anyway. They broke up the input into lines and then joined it back together. - We already break up the output from system tools into lines when processing it. Splitting up the output of system tools once and then filtering and processing it reduces both code and runtime complexity. - - - - - 39669077 by Simon Hengel at 2024-12-14T04:31:47-05:00 Refactoring: Don't use a `Chan` when parsing SysTools output - - - - - 64756530 by Simon Peyton Jones at 2024-12-14T22:28:04-05:00 Tidy up the handling of `assert` Fixes #25493 - - - - - 8658fbc1 by Rodrigo Mesquita at 2024-12-14T22:28:41-05:00 base: displayException for SomeAsyncException Provide a better implementation of `SomeException` for `SomeAsyncException`. The previous, implicit, implementation, would not use the `displayException` of the exception wrapped by `SomeAsyncException`. Implements CLC-Proposal#309 Closes #25513 - - - - - 2d3a0a70 by ARATA Mizuki at 2024-12-15T18:35:30-05:00 LLVM: When emitting a vector literal with ppTypeLit, include the type information Fixes #25561 - - - - - bfacc086 by Simon Peyton Jones at 2024-12-15T18:36:05-05:00 Fix signature lookup in instance declarations This fixes a bug introduced by the fix to #16610 - - - - - 80f0e02d by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Improve GHC build times Two small changes * In GHC.Data.Unboxed, never omit interface pragmas. In "fast builds" one might omit them generally, but doing so gives very bad performance for code that imports this module. * In GHC.Hs.Dump don't do type-class specialisation. For some reason it goes mad and generates vast amounts of useless code. See #25463. - - - - - 175a1355 by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Refactor Lint Refactor Lint for two reasons: * To improve performance * To prepare for type-lets The big changes are all in GHC.Core.Lint: * Change the main APIs: * `lintType` returns nothing rather than returning a `LintedType`; * `lintCoercion` return nothing rather than returning a `LintedCoercion` Reason: these functions did a lot of allocation to return a substituted type/coercion that was often discarded, or used only to extract its kind. Instead we now return nothing, and, when needed, extract the kind and substitute. * Applications are treated as a whole, by `lintApp`. By treating multiple arguments all at once we avoid performing multiple substitutions, each substituting a single type variable. This can make an absolutely huge difference. Overall this led to a pretty massive rewrite of Lint, with many smaller changes. Smaller chnages elsewhere * Rename `GHC.Core.TyCo.Subst.getSubstInScope` to `substInScopeSet` for consistency * Define and use `GHC.Core.Type.liftedTypeOrConstraintKind` Performance. This MR someimtes gives gives a very large improvement in compile time, when Lint is on. here is a selection of changes over 5% in perf/compiler (with -dcore-lint) T25196 -97.0% T14766 -89.7% T14683 -74.4% T5631 -60.9% T20261 -56.7% T18923 -17.6% T13035 -15.8% T6048 -15.8% CoOpt_Read -14.4% T9630 -10.9% T5642 -7.3% Eliminating the egregious offenders is a big win. However, in some cases the compiler allocation /increases/. Here ae the changes over 1%: T9961 1.5% T8095 2.8% T14052 3.9% T12545 4.5% T14052Type 5.5% T5030 8.0% T5321Fun 8.3% T3064 12.7% CoOpt_Singletons 15.6% T9198 16.0% LargeRecord 18.1% I looked at the two biggest increases in compile-time bytes allocated. Interestingly, they both show substantial *decreases* in actual compile time, due to much smaller GC times. I'm honestly not sure either why the allocation increases, or why the GC time decreases; but I'm going to take the win! T9198 Baseline With patch No Lint Alloc 44.6M 44.6M Mut time 0.23s 0.22s GC time 0.21s 0.21s With Lint Alloc 309M 360M Mut time 1.51s 0.85s GC time 2.97s 0.25s ------------------- LargeRecord Baseline With patch No Lint Alloc 1.37G 1.37G Mut time 2.33s 2.33s GC time 2.40s 2.42s With Lint Alloc 3.4G 4.0G Mut time 6.02s 5.68s GC time 3.67s 3.03s IMPORTANT NOTE: These changes don't show up in CI because in CI the tests in perf/compiler are all run with -dcore-lint switched off. I gathered this data with some manual runs. - - - - - 8ef2dad6 by Simon Peyton Jones at 2024-12-17T02:48:09-05:00 Add Note [Typechecking overloaded literals] See #25494. - - - - - e86b1b20 by Ben Gamari at 2024-12-17T13:51:39-05:00 testsuite: Use math.inf instead of division-by-zero This both more directly captures the intent and also fixes #25580. - - - - - 430d965a by Ben Gamari at 2024-12-17T13:52:15-05:00 rts: Fix incorrect format specifiers in era profiling Fixes #25581. - - - - - 267098ad by Andreas Klebinger at 2024-12-18T23:43:13-05:00 Document `-prof` and non `-prof` code being incompatible. Fixes #25518. - - - - - 04433916 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: output metadata fragment in CI (cherry picked from commit 52b58a660e735b20961d792d8fa9267f01247a50) - - - - - 7c78804e by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metatdata: use fedora33 for redhat Redhat 9 doesn't have libtinfo.so.5 anymore (cherry picked from commit dc86785eb43afd1bd292287c064fb5ad94fe8c7f) - - - - - 1d72cfb2 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: still use centos for redhat <9 - - - - - 3f7ebc58 by Sylvain Henry at 2024-12-19T20:40:14-05:00 Merge ghc-bignum into ghc-internal (#24453) First step towards merging ghc-bignum and ghc-prim into ghc-internal. After this patch, ghc-bignum is deprecated and is just a shallow package reexporting modules from ghc-internal and base. Use those directly instead. Move `gmp` submodule into ghc-internal directory. - - - - - ee0150c2 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Improve performance of deriving Show Significantly improves performance of deriving Show instances by avoiding using the very polymorphic `.` operator in favour of inlining its definition. We were generating tons of applications of it, each which had 3 type arguments! Improves on #9557 ------------------------- Metric Decrease: InstanceMatching T12707 T3294 ------------------------ - - - - - 8b266671 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Don't eta expand cons when deriving Data This eta expansion was introduced with the initial commit for Linear types. I believe this isn't needed any longer. My guess is it is an artifact from the initial linear types implementation: data constructors are linear, but they shouldn't need to be eta expanded to be used as higher order functions. I suppose in the early days this wasn't true. For instance, this works now: data T x = T x f = \(x :: forall y. y -> T y) -> x True f T -- ok! T is linear, but can be passed where an unrestricted higher order function is expected. I recall there being some magic around to make this work for data constructors... Since this works, there's no need to eta_expand the data constructors in the derived Data instances. - - - - - 1f67ad21 by Andrei Borzenkov at 2024-12-25T01:42:31-05:00 Flip the order of arguments of setField (#24668) GHC Proposal 583 "HasField redesign" specifies the following order of a setField function arguments as this: setField :: forall fld a b. SetField fld a b. b -> a -> a This patch flips the application order to match the spec. - - - - - 3e0c948d by Ben Gamari at 2024-12-25T01:43:08-05:00 rel-eng/upload: Add set_symlink mode This slightly eases updating of the `latest` symlinks. - - - - - 63d63f9d by Simon Peyton Jones at 2024-12-25T01:43:45-05:00 Preserve orientation when unifying kinds This MR fixes yet another manifestation of the trickiness caused by Note [Fundeps with instances, and equality orientation]. I wish there was a more robust way to do this, but this fix is a definite improvement. Fixes #25597 - - - - - 94ba9a6a by ARATA Mizuki at 2024-12-26T10:47:57-05:00 x86 NCG SIMD: Support pack/insert/broadcast/unpack of 128-bit integer vectors - - - - - 6bf0d587 by Andrew Lelechenko at 2024-12-26T10:48:33-05:00 docs: fix haddock formatting in Control.Monad.Fix - - - - - feb14af1 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Remove unnecessary irrefutable patterns from NonEmpty functions Implementation of https://github.com/haskell/core-libraries-committee/issues/107 - - - - - 6a0d91b4 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Make cons, Semigroup, IsList, and Monad instances stricter - - - - - 1249e597 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Restore some laziness in <| and Semigroup instance, improve Monad instance The Monad instance shouldn't produce the outer :| unless f a reduces to WHNF. (Notice that the b :| bs match is implicitly lazy.) - - - - - 8699d826 by Sergey Vinokurov at 2024-12-27T15:12:30+00:00 Add comment outlining Data.List.NonEmpty implementation guiding principles - - - - - 7febe00e by Sergey Vinokurov at 2024-12-27T22:24:43+00:00 Fix tests since location of ‘>>=’ changed - - - - - a928c326 by ARATA Mizuki at 2024-12-28T03:06:14-05:00 Fix LLVM version detection With a recent LLVM, `llc -version` emits the version on the first line if the vendor is set. It emits the version on the second line otherwise. Therefore, we need to check the both lines to detect the version. GHC now emits a warning if it fails to detect the LLVM version, so we can notice if the output of `llc -version` changes in the future. Also, the warning for using LLVM < 10 on s390x is removed, because we assume LLVM >= 13 now. This fixes the definition of __GLASGOW_HASKELL_LLVM__ macro. Fixes #25606 - - - - - 7f79257a by Zubin Duggal at 2024-12-29T13:04:35+00:00 Bump base, ghc-prim and template-haskell versions for 9.12 Also bump various submodules. (cherry picked from commit 6fc1fa3bdc8f53acdb19e47145789274060e498f) Bump base bound to 4.21 for GHC 9.12 (cherry picked from commit 473a201c6b55aea5bf9c9db0836a66ea1b657e04) Bump binary submodule to 0.8.9.2 (cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20) (cherry picked from commit ec2f40b45c1a3d82d17a2fc07e9ddb9218bc3940) Bump exceptions submodule to 0.10.9 (cherry picked from commit f5b5d1dc2d326368e5b173d622630d77f019b629) Bump file-io submodule to 0.1.4 (cherry picked from commit ba786681de6ac5fa49938e2cd71a5988f0f40d1f) bump os-string submodule to 2.0.6 (cherry picked from commit 3a7ffdbb832c045a55fd1ef24f546abdd9d9e30f) bump transformers submodule to 0.6.1.2 (cherry picked from commit 53b46fd437421b9e5a001edc6d1c427439d7714f) Bump directory submodule to v1.3.9.0 (cherry picked from commit 27dc2664c5404bb462092bb216c2c37b418fd1f8) Bump Win32 submodule to v2.14.1.0 (cherry picked from commit 80df88086180f5e39212b2feacf70a9d2b263c6c) Bump filepath submodule to 1.5.3.0 (cherry picked from commit 29bfae2c58a7303a081a6e7956b9f55e5faf3eeb) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 97b0dff223a6c4cc003adec448104c277f214645) Bump unix submodule to 2.8.6.0 (cherry picked from commit a1f56d6d6a99c100f88ef0a8b4d51298cf24a42d) Bump os-string submodule to 2.0.8 (cherry picked from commit 0121b76fd52ea0c0ce5d07085bc195666b63c625) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 962ceb50c8a6fc370e1c0a267f5cd5562a8cf759) Bump filepath submodule to 1.5.4.0 (cherry picked from commit 7bc6877fd5d41c6d5900678ad5e73ed30f366569) Bump file-io submodule to 0.1.5 (cherry picked from commit 9478b5aefe2877d58baf527edcf936dddbb955b7) Bump Cabal submodule to 3.14.1.0 (cherry picked from commit 5c9c3e3f79a79bb6d9a77a17c716dc3a0bcbd2aa) Bump directory submodule to 0.12.2.0 (cherry picked from commit 897906265db37af34ae2aaa016cec417f263407b) Bump array submodule for base bump Bump stm submodule for base bump Bump process submodule for base bump - - - - - f6079408 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix ghc-e005 after HasCallstack changes (cherry picked from commit 77f340a24561cea8a6f2ada296b3ea356ab1823c) - - - - - 3e10fa75 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Add haskeline to stage0Packages Otherwise we link against boot inplace and boot unix as boot haskeline depends on boot unix. (cherry picked from commit 90b493769ebdf3cd7be404d18462dc20ac1044df) - - - - - 4ad6aec4 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix TH changelog - - - - - ea3f7fd5 by Zubin Duggal at 2024-12-29T13:04:35+00:00 release: copy index.html from correct directory (cherry picked from commit cbfd0829cd61928976c9eb17ba4af18272466063) - - - - - fafb70db by Zubin Duggal at 2024-12-29T13:04:35+00:00 hadrian-multi: warn on unused imports os-string has redundant imports (cherry picked from commit dde3796be689ea57543936e22aa5ea4ef7ed995e) - - - - - c02b1e46 by Simon Peyton Jones at 2024-12-29T17:04:30-05:00 Fix in-scope set for CSE Ticket #25468 showed an assertion failure in CSE because a top-level Id was being used before it was defined. Reason: Note [Glomming] in GHC.Core.Opt.OccurAnal. Solution (used in many places): just put all the top-level bindings in scope at the beginning of CSE. Compile-time allocation wobbles up and down a tiny bit; geo mean is zero. But MultiLayerModulesTH_OneShot and hard_hole_fits increase (on some architectures only) by a bit oever 2% . I think these are just a random fluctuations. Metric Increase: MultiLayerModulesTH_OneShot hard_hole_fits - - - - - 559d4f84 by Krzysztof Gogolewski at 2024-12-30T11:53:19-05:00 Add tests for #23883 The issue has been fixed by commit f5d3e03c56ffc63. Only T23883a is the actual regression test, the remaining ones are tricky cases found during development of an independent fix !11313. - - - - - 278a53ee by Sergey Vinokurov at 2024-12-30T11:53:59-05:00 Update changelog for CLC proposal #107 (NonEmpty laziness) - - - - - f56558be by Matthew Pickering at 2025-01-07T13:53:03-05:00 warnings: Find out if a qualified name is in the interactive scope directly There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600 - - - - - 84155cdb by Simon Peyton Jones at 2025-01-07T13:53:40-05:00 Tidy up kcConDecls Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types - - - - - 6c12b6cf by Bryan Richter at 2025-01-07T18:15:02-05:00 Remove tmp files after toolchain check Fixes #25620 - - - - - 42826a89 by Cheng Shao at 2025-01-07T18:15:39-05:00 xxhash: bump to v0.8.3 - - - - - 185f17e4 by sheaf at 2025-01-07T18:16:15-05:00 Fix typo in GHC.Tc.Solver.Solve.runTcPluginsWanted - - - - - 23099752 by Luite Stegeman at 2025-01-08T00:33:33+01:00 Add flags for switching off speculative evaluation. We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284 - - - - - 0161badc by Ben Gamari at 2025-01-09T17:30:05-05:00 rts/printClosure: Print IPE information for thunks and functions This makes it considerably easier to grok the structure of the heap when IPE information is available. - - - - - 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz GoÅ›linowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-â” |---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | â””-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - c8c660f6 by Vladislav Zavialov at 2025-03-06T19:24:36+03:00 Deprecate and disable CUSKs - - - - - 6978 changed files: - .ghcid - + .git-blame-ignore-revs - .gitattributes - .gitignore - .gitlab-ci.yml - + .gitlab/README.md - .gitlab/ci.sh - .gitlab/darwin/nix/sources.json - .gitlab/darwin/toolchain.nix - .gitlab/generate-ci/flake.lock - .gitlab/generate-ci/gen_ci.hs - .gitlab/generate-ci/generate-job-metadata - .gitlab/generate-ci/generate-jobs - .gitlab/hello.hs - − .gitlab/issue_templates/bug.md - + .gitlab/issue_templates/default.md - .gitlab/jobs.yaml - .gitlab/merge_request_templates/Default.md - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/default.nix - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/README.mkd - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - + .gitlab/rel_eng/recompress-all - .gitlab/rel_eng/upload.sh - .gitlab/rel_eng/upload_ghc_libs.py - .gitlab/test-metrics.sh - .gitmodules - CODEOWNERS - README.md - boot - cabal.project-reinstall - compile_flags.txt - compiler/CodeGen.Platform.h - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/PrimOps.hs-boot - compiler/GHC/Builtin/PrimOps/Casts.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/Utils.hs - − compiler/GHC/Builtin/gen_bytearray_addr_access_ops.py - 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/Cmm.hs - compiler/GHC/Cmm/BlockId.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/ContFlowOpt.hs - compiler/GHC/Cmm/Dataflow.hs - − compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Graph.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/Dominators.hs - compiler/GHC/Cmm/Expr.hs - + compiler/GHC/Cmm/GenericOpt.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Lint.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reducibility.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/Switch.hs - compiler/GHC/Cmm/Switch/Implement.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/Cmm/Type.hs - + compiler/GHC/Cmm/UniqueRenamer.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Cond.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/AArch64/RegInfo.hs - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Ppr.hs - + compiler/GHC/CmmToAsm/RV64.hs - + compiler/GHC/CmmToAsm/RV64/CodeGen.hs - + compiler/GHC/CmmToAsm/RV64/Cond.hs - + compiler/GHC/CmmToAsm/RV64/Instr.hs - + compiler/GHC/CmmToAsm/RV64/Ppr.hs - + compiler/GHC/CmmToAsm/RV64/RegInfo.hs - + compiler/GHC/CmmToAsm/RV64/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Linear/PPC.hs - + compiler/GHC/CmmToAsm/Reg/Linear/RV64.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs - compiler/GHC/CmmToAsm/Reg/Linear/State.hs - compiler/GHC/CmmToAsm/Reg/Linear/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/Utils.hs - compiler/GHC/CmmToAsm/Wasm.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/CmmToLlvm/Config.hs - compiler/GHC/CmmToLlvm/Data.hs - compiler/GHC/CmmToLlvm/Regs.hs - + compiler/GHC/CmmToLlvm/Version.hs - + compiler/GHC/CmmToLlvm/Version/Bounds.hs.in - + compiler/GHC/CmmToLlvm/Version/Type.hs - compiler/GHC/Core.hs - compiler/GHC/Core.hs-boot - compiler/GHC/Core/Class.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/ConLike.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FVs.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/LateCC.hs - + compiler/GHC/Core/LateCC/OverloadedCalls.hs - + compiler/GHC/Core/LateCC/TopLevelBinds.hs - + compiler/GHC/Core/LateCC/Types.hs - + compiler/GHC/Core/LateCC/Utils.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/FloatOut.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Inline.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Monad.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/Stats.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Ppr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Reduction.hs - compiler/GHC/Core/RoughMap.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Stats.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon.hs-boot - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/Bag.hs - compiler/GHC/Data/Bitmap.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/EnumSet.hs - compiler/GHC/Data/FastMutInt.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - + compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Collapse.hs - compiler/GHC/Data/Graph/Directed.hs - + compiler/GHC/Data/Graph/Directed/Internal.hs - + compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/Graph/Inductive/PatriciaTree.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/OrdList.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/Stream.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Data/Unboxed.hs - compiler/GHC/Data/Word64Map.hs - compiler/GHC/Data/Word64Map/Internal.hs - compiler/GHC/Data/Word64Map/Lazy.hs - compiler/GHC/Data/Word64Map/Strict.hs - compiler/GHC/Data/Word64Map/Strict/Internal.hs - compiler/GHC/Data/Word64Set.hs - compiler/GHC/Data/Word64Set/Internal.hs - compiler/GHC/Driver/Backend.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CmdLine.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/GHC/Driver/Config/CmmToLlvm.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/Config/Core/Opt/LiberateCase.hs - compiler/GHC/Driver/Config/Core/Opt/Simplify.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Config/CoreToStg/Prep.hs - compiler/GHC/Driver/Config/Diagnostic.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/Config/HsToCore.hs - compiler/GHC/Driver/Config/Linker.hs - compiler/GHC/Driver/Config/Logger.hs - compiler/GHC/Driver/Config/Parser.hs - compiler/GHC/Driver/Config/Stg/Pipeline.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/Config/StgToJS.hs - compiler/GHC/Driver/Config/Tidy.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/GenerateCgIPEStub.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - + compiler/GHC/Driver/Main.hs-boot - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/MakeSem.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Phases.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Pipeline/Phases.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs.hs - + compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Doc.hs - + compiler/GHC/Hs/Doc.hs-boot - compiler/GHC/Hs/DocString.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Pat.hs - + compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Coverage.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Utils.hs - + compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match.hs-boot - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Check.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Pmc/Types.hs - compiler/GHC/HsToCore/Pmc/Utils.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Errors/Types.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Ext/Types.hs - compiler/GHC/Iface/Ext/Utils.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Binary.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Iface/Type.hs-boot - + compiler/GHC/Iface/Warnings.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/IfaceToCore.hs-boot - + compiler/GHC/JS/Ident.hs - + compiler/GHC/JS/JStg/Monad.hs - + compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - + compiler/GHC/JS/Opt/Expr.hs - + compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Optimizer.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/JS/Transform.hs - − compiler/GHC/JS/Unsat/Syntax.hs - − compiler/GHC/Linker.hs - compiler/GHC/Linker/Config.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Dynamic.hs - + compiler/GHC/Linker/External.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/MacOS.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Linker/Types.hs - compiler/GHC/Linker/Unit.hs - compiler/GHC/Llvm.hs - compiler/GHC/Llvm/MetaData.hs - compiler/GHC/Llvm/Ppr.hs - compiler/GHC/Llvm/Syntax.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/CharClass.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - + compiler/GHC/Parser/String.hs - compiler/GHC/Parser/Types.hs - compiler/GHC/Platform.hs - compiler/GHC/Platform/Reg.hs - compiler/GHC/Platform/Reg/Class.hs - + compiler/GHC/Platform/Reg/Class/NoVectors.hs - + compiler/GHC/Platform/Reg/Class/Separate.hs - + compiler/GHC/Platform/Reg/Class/Unified.hs - compiler/GHC/Platform/Wasm32.hs - compiler/GHC/Platform/Ways.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Doc.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Expr.hs-boot - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Splice.hs-boot - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Heap/Layout.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Process.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - + compiler/GHC/Runtime/Interpreter/Wasm.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Runtime/Utils.hs - compiler/GHC/Settings.hs - compiler/GHC/Settings/Constants.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/BcPrep.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Stg/Debug.hs - + compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs - + compiler/GHC/Stg/EnforceEpt/Types.hs - − compiler/GHC/Stg/InferTags.hs - − compiler/GHC/Stg/InferTags/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lift/Types.hs - compiler/GHC/Stg/Lint.hs - + compiler/GHC/Stg/Make.hs - compiler/GHC/Stg/Pipeline.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Subst.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/Stg/Utils.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Env.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/ExtCode.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Heap.hs - compiler/GHC/StgToCmm/Hpc.hs - compiler/GHC/StgToCmm/InfoTableProv.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Sequel.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Types.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/StgToJS.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/Closure.hs - compiler/GHC/StgToJS/CodeGen.hs - compiler/GHC/StgToJS/DataCon.hs - compiler/GHC/StgToJS/Deps.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/ExprCtx.hs - compiler/GHC/StgToJS/FFI.hs - compiler/GHC/StgToJS/Heap.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Opt.hs - compiler/GHC/StgToJS/Linker/Types.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Monad.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/StgToJS/Profiling.hs - compiler/GHC/StgToJS/Regs.hs - compiler/GHC/StgToJS/Rts/Rts.hs - compiler/GHC/StgToJS/Rts/Types.hs - − compiler/GHC/StgToJS/Sinker.hs - + compiler/GHC/StgToJS/Sinker/Collect.hs - + compiler/GHC/StgToJS/Sinker/Sinker.hs - + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs - compiler/GHC/StgToJS/Stack.hs - compiler/GHC/StgToJS/StaticPtr.hs - compiler/GHC/StgToJS/Symbols.hs - compiler/GHC/StgToJS/Types.hs - compiler/GHC/StgToJS/Utils.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/SysTools/Terminal.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Deriv/Utils.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs-boot - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - + compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs-boot - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Match.hs-boot - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Instance/FunDeps.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.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/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Rewrite.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/BasicTypes.hs - compiler/GHC/Tc/Types/Constraint.hs - + compiler/GHC/Tc/Types/CtLoc.hs - − compiler/GHC/Tc/Types/CtLocEnv.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/EvTerm.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/LclEnv.hs - compiler/GHC/Tc/Types/LclEnv.hs-boot - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/Origin.hs-boot - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - + compiler/GHC/Tc/Utils/TcMType.hs-boot - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/TcType.hs-boot - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/Monad.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - − compiler/GHC/Types/BreakInfo.hs - + compiler/GHC/Types/Breakpoint.hs - compiler/GHC/Types/CompleteMatch.hs - compiler/GHC/Types/CostCentre.hs - + compiler/GHC/Types/DefaultEnv.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/FieldLabel.hs - compiler/GHC/Types/Fixity.hs - compiler/GHC/Types/Fixity/Env.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/IPE.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id.hs-boot - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Meta.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Occurrence.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/Name/Set.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/RepType.hs - compiler/GHC/Types/SourceText.hs - + compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Tickish.hs - compiler/GHC/Types/TyThing.hs - compiler/GHC/Types/TyThing/Ppr.hs - compiler/GHC/Types/Unique.hs - compiler/GHC/Types/Unique/DFM.hs - + compiler/GHC/Types/Unique/DSM.hs - compiler/GHC/Types/Unique/DSet.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Unique/Set.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Types/Var/Set.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Finder/Types.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Info.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/Imported.hs - compiler/GHC/Unit/Module/Location.hs - compiler/GHC/Unit/Module/ModDetails.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/Module/Warnings.hs - compiler/GHC/Unit/Module/WholeCoreBindings.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - compiler/GHC/Utils/BufHandle.hs - compiler/GHC/Utils/Containers/Internal/BitUtil.hs - compiler/GHC/Utils/Containers/Internal/StrictPair.hs - compiler/GHC/Utils/Error.hs - compiler/GHC/Utils/FV.hs - compiler/GHC/Utils/Fingerprint.hs - compiler/GHC/Utils/GlobalVars.hs - compiler/GHC/Utils/Lexeme.hs - compiler/GHC/Utils/Logger.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Monad.hs - compiler/GHC/Utils/Monad/State/Strict.hs - compiler/GHC/Utils/Outputable.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Panic/Plain.hs - compiler/GHC/Utils/Ppr.hs - compiler/GHC/Utils/TmpFs.hs - + compiler/GHC/Utils/Touch.hs - compiler/GHC/Utils/Trace.hs - compiler/GHC/Utils/Unique.hs - compiler/GHC/Utils/Word64.hs - compiler/GHC/Wasm/ControlFlow/FromCmm.hs - compiler/Language/Haskell/Syntax.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - + compiler/Language/Haskell/Syntax/BooleanFormula.hs - − compiler/Language/Haskell/Syntax/Concrete.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Expr.hs-boot - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/ImpExp.hs - − compiler/Language/Haskell/Syntax/ImpExp.hs-boot - compiler/Language/Haskell/Syntax/Lit.hs - compiler/Language/Haskell/Syntax/Module/Name.hs - compiler/Language/Haskell/Syntax/Pat.hs - + compiler/Language/Haskell/Syntax/Specificity.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - compiler/Setup.hs - compiler/cbits/genSym.c - − compiler/ghc-llvm-version.h.in - compiler/ghc.cabal.in - compiler/jsbits/genSym.js - config.guess - config.sub - configure.ac - distrib/configure.ac.in - − distrib/cross-port - distrib/mkDocs/mkDocs - docs/coding-style.html - docs/index.html.in - docs/rts/rts.tex - − docs/users_guide/9.10.1-notes.rst - + docs/users_guide/9.14.1-notes.rst - − docs/users_guide/9.6.1-notes.rst - − docs/users_guide/9.8.1-notes.rst - docs/users_guide/bugs.rst - docs/users_guide/conf.py - docs/users_guide/debug-info.rst - docs/users_guide/debugging.rst - + docs/users_guide/diagnostics-as-json-schema-1_0.json - + docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/eventlog-formats.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/extending_ghc.rst - docs/users_guide/exts/applicative_do.rst - docs/users_guide/exts/arrows.rst - docs/users_guide/exts/assert.rst - docs/users_guide/exts/binary_literals.rst - docs/users_guide/exts/constrained_class_methods.rst - docs/users_guide/exts/constraint_kind.rst - docs/users_guide/exts/control.rst - docs/users_guide/exts/data_kinds.rst - docs/users_guide/exts/default_signatures.rst - docs/users_guide/exts/derive_any_class.rst - docs/users_guide/exts/deriving_extra.rst - docs/users_guide/exts/deriving_strategies.rst - docs/users_guide/exts/deriving_via.rst - docs/users_guide/exts/disambiguate_record_fields.rst - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/empty_case.rst - docs/users_guide/exts/empty_data_deriving.rst - docs/users_guide/exts/equality_constraints.rst - docs/users_guide/exts/existential_quantification.rst - docs/users_guide/exts/explicit_forall.rst - docs/users_guide/exts/explicit_namespaces.rst - docs/users_guide/exts/extended_literals.rst - docs/users_guide/exts/ffi.rst - docs/users_guide/exts/field_selectors.rst - docs/users_guide/exts/flexible_contexts.rst - docs/users_guide/exts/functional_dependencies.rst - docs/users_guide/exts/gadt.rst - docs/users_guide/exts/gadt_syntax.rst - docs/users_guide/exts/generalised_list_comprehensions.rst - docs/users_guide/exts/generics.rst - docs/users_guide/exts/hasfield.rst - docs/users_guide/exts/hex_float_literals.rst - docs/users_guide/exts/implicit_parameters.rst - docs/users_guide/exts/import_qualified_post.rst - docs/users_guide/exts/impredicative_types.rst - docs/users_guide/exts/instances.rst - docs/users_guide/exts/intro.rst - docs/users_guide/exts/kind_signatures.rst - docs/users_guide/exts/lambda_case.rst - docs/users_guide/exts/let_generalisation.rst - docs/users_guide/exts/liberal_type_synonyms.rst - docs/users_guide/exts/linear_types.rst - docs/users_guide/exts/literals.rst - docs/users_guide/exts/magic_hash.rst - docs/users_guide/exts/monad_comprehensions.rst - docs/users_guide/exts/monomorphism.rst - docs/users_guide/exts/multi_param_type_classes.rst - + docs/users_guide/exts/multiline_strings.rst - docs/users_guide/exts/multiway_if.rst - + docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/negative_literals.rst - docs/users_guide/exts/newtype_deriving.rst - docs/users_guide/exts/nk_patterns.rst - docs/users_guide/exts/nullary_type_classes.rst - docs/users_guide/exts/nullary_types.rst - docs/users_guide/exts/num_decimals.rst - docs/users_guide/exts/numeric_underscores.rst - + docs/users_guide/exts/or_patterns.rst - docs/users_guide/exts/overloaded_labels.rst - docs/users_guide/exts/overloaded_lists.rst - docs/users_guide/exts/overloaded_record_dot.rst - docs/users_guide/exts/overloaded_record_update.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/package_qualified_imports.rst - docs/users_guide/exts/parallel_list_comprehensions.rst - docs/users_guide/exts/partial_type_signatures.rst - docs/users_guide/exts/pattern_guards.rst - docs/users_guide/exts/pattern_synonyms.rst - docs/users_guide/exts/patterns.rst - docs/users_guide/exts/poly_kinds.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/exts/primitives.rst - docs/users_guide/exts/qualified_do.rst - docs/users_guide/exts/quantified_constraints.rst - docs/users_guide/exts/rank_polymorphism.rst - docs/users_guide/exts/rebindable_syntax.rst - docs/users_guide/exts/record_puns.rst - docs/users_guide/exts/record_wildcards.rst - docs/users_guide/exts/recursive_do.rst - docs/users_guide/exts/representation_polymorphism.rst - + docs/users_guide/exts/required_type_arguments.rst - docs/users_guide/exts/rewrite_rules.rst - docs/users_guide/exts/roles.rst - docs/users_guide/exts/safe_haskell.rst - docs/users_guide/exts/scoped_type_variables.rst - docs/users_guide/exts/standalone_deriving.rst - docs/users_guide/exts/static_pointers.rst - docs/users_guide/exts/stolen_syntax.rst - docs/users_guide/exts/strict.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/exts/template_haskell.rst - docs/users_guide/exts/traditional_record_syntax.rst - docs/users_guide/exts/tuple_sections.rst - docs/users_guide/exts/type_abstractions.rst - docs/users_guide/exts/type_applications.rst - docs/users_guide/exts/type_data.rst - docs/users_guide/exts/type_families.rst - docs/users_guide/exts/type_operators.rst - docs/users_guide/exts/type_signatures.rst - docs/users_guide/exts/types.rst - docs/users_guide/exts/view_patterns.rst - docs/users_guide/flags.py - docs/users_guide/ghc_config.py.in - docs/users_guide/ghci.rst - docs/users_guide/hints.rst - docs/users_guide/javascript.rst - docs/users_guide/packages.rst - docs/users_guide/phases.rst - docs/users_guide/profiling.rst - docs/users_guide/release-notes.rst - docs/users_guide/runtime_control.rst - docs/users_guide/separate_compilation.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using-warnings.rst - docs/users_guide/using.rst - docs/users_guide/utils.py - docs/users_guide/wasm.rst - docs/users_guide/win32-dlls.rst - driver/ghci/ghci-wrapper.cabal.in - driver/utils/isMinTTY.c - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - − ghc/ghc.wrapper - hadrian/.gitignore - hadrian/README.md - hadrian/bindist/Makefile - hadrian/bindist/config.mk.in - hadrian/bootstrap/bootstrap.py - hadrian/bootstrap/generate_bootstrap_plans - hadrian/bootstrap/hadrian-bootstrap-gen.cabal - + hadrian/bootstrap/plan-9_10_1.json - − hadrian/bootstrap/plan-9_2_1.json - − hadrian/bootstrap/plan-9_2_2.json - − hadrian/bootstrap/plan-9_2_3.json - − hadrian/bootstrap/plan-9_2_4.json - − hadrian/bootstrap/plan-9_2_5.json - − hadrian/bootstrap/plan-9_2_6.json - − hadrian/bootstrap/plan-9_2_7.json - − hadrian/bootstrap/plan-9_4_1.json - − hadrian/bootstrap/plan-9_4_2.json - − hadrian/bootstrap/plan-9_4_3.json - − hadrian/bootstrap/plan-9_4_4.json - hadrian/bootstrap/plan-9_6_1.json - + hadrian/bootstrap/plan-9_6_2.json - + hadrian/bootstrap/plan-9_6_3.json - + hadrian/bootstrap/plan-9_6_4.json - + hadrian/bootstrap/plan-9_6_5.json - + hadrian/bootstrap/plan-9_6_6.json - + hadrian/bootstrap/plan-9_8_1.json - + hadrian/bootstrap/plan-9_8_2.json - + hadrian/bootstrap/plan-bootstrap-9_10_1.json - − hadrian/bootstrap/plan-bootstrap-9_2_1.json - − hadrian/bootstrap/plan-bootstrap-9_2_2.json - − hadrian/bootstrap/plan-bootstrap-9_2_3.json - − hadrian/bootstrap/plan-bootstrap-9_2_4.json - − hadrian/bootstrap/plan-bootstrap-9_2_5.json - − hadrian/bootstrap/plan-bootstrap-9_2_6.json - − hadrian/bootstrap/plan-bootstrap-9_2_7.json - − hadrian/bootstrap/plan-bootstrap-9_4_1.json - − hadrian/bootstrap/plan-bootstrap-9_4_2.json - − hadrian/bootstrap/plan-bootstrap-9_4_3.json - − hadrian/bootstrap/plan-bootstrap-9_4_4.json - hadrian/bootstrap/plan-bootstrap-9_6_1.json - + hadrian/bootstrap/plan-bootstrap-9_6_2.json - + hadrian/bootstrap/plan-bootstrap-9_6_3.json - + hadrian/bootstrap/plan-bootstrap-9_6_4.json - + hadrian/bootstrap/plan-bootstrap-9_6_5.json - + hadrian/bootstrap/plan-bootstrap-9_6_6.json - + hadrian/bootstrap/plan-bootstrap-9_8_1.json - + hadrian/bootstrap/plan-bootstrap-9_8_2.json - hadrian/bootstrap/src/Main.hs - hadrian/build-cabal - hadrian/cabal.project - + hadrian/cfg/default.host.target.in - + hadrian/cfg/default.target.in - hadrian/cfg/system.config.in - hadrian/doc/debugging.md - hadrian/doc/flavours.md - hadrian/doc/testsuite.md - hadrian/doc/user-settings.md - hadrian/ghci-cabal.in - hadrian/ghci-multi-cabal.in - hadrian/hadrian.cabal - hadrian/hie-bios - hadrian/hie-bios.bat - hadrian/src/Base.hs - hadrian/src/Builder.hs - hadrian/src/CommandLine.hs - hadrian/src/Context.hs - hadrian/src/Context/Type.hs - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Hadrian/Builder.hs - hadrian/src/Hadrian/Builder/Ar.hs - hadrian/src/Hadrian/Haskell/Cabal.hs - hadrian/src/Hadrian/Haskell/Cabal/Parse.hs - hadrian/src/Hadrian/Haskell/Cabal/Type.hs - hadrian/src/Hadrian/Haskell/Hash.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Hadrian/Oracles/TextFile.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Main.hs - hadrian/src/Oracles/Flag.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Oracles/TestSettings.hs - hadrian/src/Packages.hs - + hadrian/src/Progress.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Clean.hs - + hadrian/src/Rules/Codes.hs - hadrian/src/Rules/Compile.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Docspec.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Libffi.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Lint.hs - hadrian/src/Rules/Program.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/src/Rules/ToolArgs.hs - hadrian/src/Settings.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/Cc.hs - hadrian/src/Settings/Builders/Common.hs - hadrian/src/Settings/Builders/Configure.hs - hadrian/src/Settings/Builders/DeriveConstants.hs - + hadrian/src/Settings/Builders/GenApply.hs - hadrian/src/Settings/Builders/GenPrimopCode.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Builders/Haddock.hs - hadrian/src/Settings/Builders/HsCpp.hs - hadrian/src/Settings/Builders/Hsc2Hs.hs - hadrian/src/Settings/Builders/Ld.hs - hadrian/src/Settings/Builders/MergeObjects.hs - hadrian/src/Settings/Builders/RunTest.hs - hadrian/src/Settings/Builders/SplitSections.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/GhcInGhci.hs - hadrian/src/Settings/Flavours/Performance.hs - hadrian/src/Settings/Flavours/Validate.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Program.hs - hadrian/src/Settings/Warnings.hs - hadrian/src/Way.hs - hadrian/stack.yaml - hadrian/stack.yaml.lock - libffi-tarballs - − libffi/Makefile - − libffi/ln - libraries/Cabal - libraries/Win32 - libraries/array - − libraries/base/.gitignore - − libraries/base/Control/Arrow.hs - − libraries/base/Control/Category.hs - − libraries/base/Control/Concurrent.hs - − libraries/base/Control/Concurrent.hs-boot - − libraries/base/Control/Concurrent/MVar.hs - − libraries/base/Control/Exception.hs - − libraries/base/Control/Exception/Base.hs - − libraries/base/Control/Monad.hs - − libraries/base/Control/Monad/Fail.hs - − libraries/base/Control/Monad/Fix.hs - − libraries/base/Control/Monad/IO/Class.hs - − libraries/base/Control/Monad/Instances.hs - − libraries/base/Control/Monad/ST.hs - − libraries/base/Control/Monad/ST/Imp.hs - − libraries/base/Control/Monad/ST/Lazy.hs - − libraries/base/Control/Monad/ST/Lazy/Imp.hs - − libraries/base/Control/Monad/ST/Lazy/Safe.hs - − libraries/base/Control/Monad/ST/Lazy/Unsafe.hs - − libraries/base/Control/Monad/ST/Safe.hs - − libraries/base/Control/Monad/ST/Strict.hs - − libraries/base/Control/Monad/ST/Unsafe.hs - − libraries/base/Control/Monad/Zip.hs - − libraries/base/Data/Bits.hs - − libraries/base/Data/Bool.hs - − libraries/base/Data/Char.hs - − libraries/base/Data/Coerce.hs - − libraries/base/Data/Data.hs - − libraries/base/Data/Dynamic.hs - − libraries/base/Data/Either.hs - − libraries/base/Data/Eq.hs - − libraries/base/Data/Fixed.hs - − libraries/base/Data/Foldable.hs - − libraries/base/Data/Function.hs - − libraries/base/Data/Functor.hs - − libraries/base/Data/Functor/Classes.hs - − libraries/base/Data/Functor/Const.hs - − libraries/base/Data/Functor/Identity.hs - − libraries/base/Data/Functor/Utils.hs - − libraries/base/Data/IORef.hs - − libraries/base/Data/Int.hs - − libraries/base/Data/Ix.hs - − libraries/base/Data/Kind.hs - − libraries/base/Data/List.hs - − libraries/base/Data/List/NonEmpty.hs - − libraries/base/Data/Maybe.hs - − libraries/base/Data/Monoid.hs - − libraries/base/Data/OldList.hs - − libraries/base/Data/Ord.hs - − libraries/base/Data/Proxy.hs - − libraries/base/Data/STRef.hs - − libraries/base/Data/STRef/Lazy.hs - − libraries/base/Data/STRef/Strict.hs - − libraries/base/Data/Semigroup/Internal.hs - − libraries/base/Data/String.hs - − libraries/base/Data/Traversable.hs - − libraries/base/Data/Tuple.hs - − libraries/base/Data/Type/Bool.hs - − libraries/base/Data/Type/Coercion.hs - − libraries/base/Data/Type/Equality.hs - − libraries/base/Data/Type/Ord.hs - − libraries/base/Data/Typeable.hs - − libraries/base/Data/Typeable/Internal.hs - − libraries/base/Data/Unique.hs - − libraries/base/Data/Version.hs - − libraries/base/Data/Version.hs-boot - − libraries/base/Data/Void.hs - − libraries/base/Data/Word.hs - − libraries/base/Debug/Trace.hs - − libraries/base/Foreign.hs - − libraries/base/Foreign/C.hs - − libraries/base/Foreign/C/ConstPtr.hs - − libraries/base/Foreign/C/Error.hs - − libraries/base/Foreign/C/String.hs - − libraries/base/Foreign/C/Types.hs - − libraries/base/Foreign/Concurrent.hs - − libraries/base/Foreign/ForeignPtr.hs - − libraries/base/Foreign/ForeignPtr/Imp.hs - − libraries/base/Foreign/ForeignPtr/Safe.hs - − libraries/base/Foreign/ForeignPtr/Unsafe.hs - − libraries/base/Foreign/Marshal.hs - − libraries/base/Foreign/Marshal/Alloc.hs - − libraries/base/Foreign/Marshal/Array.hs - − libraries/base/Foreign/Marshal/Error.hs - − libraries/base/Foreign/Marshal/Pool.hs - − libraries/base/Foreign/Marshal/Safe.hs - − libraries/base/Foreign/Marshal/Unsafe.hs - − libraries/base/Foreign/Marshal/Utils.hs - − libraries/base/Foreign/Ptr.hs - − libraries/base/Foreign/Safe.hs - − libraries/base/Foreign/StablePtr.hs - − libraries/base/Foreign/Storable.hs - − libraries/base/GHC/Arr.hs - − libraries/base/GHC/ArrayArray.hs - − libraries/base/GHC/Base.hs - − libraries/base/GHC/Bits.hs - − libraries/base/GHC/ByteOrder.hs - − libraries/base/GHC/Char.hs - − libraries/base/GHC/Clock.hsc - − libraries/base/GHC/Conc.hs - − libraries/base/GHC/Conc/IO.hs - − libraries/base/GHC/Conc/POSIX.hs - − libraries/base/GHC/Conc/Signal.hs - − libraries/base/GHC/Conc/Sync.hs - − libraries/base/GHC/Conc/WinIO.hs - − libraries/base/GHC/Conc/Windows.hs - − libraries/base/GHC/Constants.hs - − libraries/base/GHC/Desugar.hs - − libraries/base/GHC/Encoding/UTF8.hs - − libraries/base/GHC/Enum.hs - − libraries/base/GHC/Enum.hs-boot - − libraries/base/GHC/Environment.hs - − libraries/base/GHC/Err.hs - − libraries/base/GHC/Event.hs - − libraries/base/GHC/Event/Arr.hs - − libraries/base/GHC/Event/Array.hs - − libraries/base/GHC/Event/Internal.hs - − libraries/base/GHC/Event/Internal/Types.hs - − libraries/base/GHC/Event/Thread.hs - − libraries/base/GHC/Event/TimeOut.hs - − libraries/base/GHC/Event/Unique.hs - − libraries/base/GHC/Event/Windows.hsc - − libraries/base/GHC/Event/Windows/Clock.hs - − libraries/base/GHC/Event/Windows/ManagedThreadPool.hs - − libraries/base/GHC/Event/Windows/Thread.hs - − libraries/base/GHC/Exception.hs - − libraries/base/GHC/Exception.hs-boot - − libraries/base/GHC/Exception/Type.hs - − libraries/base/GHC/ExecutionStack.hs - − libraries/base/GHC/Exts.hs - − libraries/base/GHC/Fingerprint.hs - − libraries/base/GHC/Fingerprint/Type.hs - − libraries/base/GHC/Float.hs - − libraries/base/GHC/Float/ConversionUtils.hs - − libraries/base/GHC/Float/RealFracMethods.hs - − libraries/base/GHC/Foreign.hs - − libraries/base/GHC/Foreign/Internal.hs - − libraries/base/GHC/ForeignPtr.hs - − libraries/base/GHC/GHCi.hs - − libraries/base/GHC/GHCi/Helpers.hs - − libraries/base/GHC/Generics.hs - − libraries/base/GHC/IO.hs - − libraries/base/GHC/IO.hs-boot - − libraries/base/GHC/IO/Buffer.hs - − libraries/base/GHC/IO/BufferedIO.hs - − libraries/base/GHC/IO/Device.hs - − libraries/base/GHC/IO/Encoding.hs - − libraries/base/GHC/IO/Encoding.hs-boot - − libraries/base/GHC/IO/Encoding/CodePage.hs - − libraries/base/GHC/IO/Encoding/CodePage/API.hs - − libraries/base/GHC/IO/Encoding/CodePage/Table.hs - − libraries/base/GHC/IO/Encoding/Failure.hs - − libraries/base/GHC/IO/Encoding/Iconv.hs - − libraries/base/GHC/IO/Encoding/Latin1.hs - − libraries/base/GHC/IO/Encoding/Types.hs - − libraries/base/GHC/IO/Encoding/UTF16.hs - − libraries/base/GHC/IO/Encoding/UTF32.hs - − libraries/base/GHC/IO/Encoding/UTF8.hs - − libraries/base/GHC/IO/Exception.hs - − libraries/base/GHC/IO/Exception.hs-boot - − libraries/base/GHC/IO/FD.hs - − libraries/base/GHC/IO/Handle.hs - − libraries/base/GHC/IO/Handle.hs-boot - − libraries/base/GHC/IO/Handle/FD.hs - − libraries/base/GHC/IO/Handle/FD.hs-boot - − libraries/base/GHC/IO/Handle/Internals.hs - − libraries/base/GHC/IO/Handle/Lock.hs - − libraries/base/GHC/IO/Handle/Lock/NoOp.hs - − libraries/base/GHC/IO/Handle/Lock/Windows.hsc - − libraries/base/GHC/IO/Handle/Text.hs - − libraries/base/GHC/IO/Handle/Text.hs-boot - − libraries/base/GHC/IO/Handle/Types.hs - − libraries/base/GHC/IO/Handle/Types.hs-boot - − libraries/base/GHC/IO/Handle/Windows.hs - − libraries/base/GHC/IO/IOMode.hs - − libraries/base/GHC/IO/StdHandles.hs - − libraries/base/GHC/IO/SubSystem.hs - − libraries/base/GHC/IO/Unsafe.hs - − libraries/base/GHC/IO/Windows/Encoding.hs - − libraries/base/GHC/IO/Windows/Paths.hs - − libraries/base/GHC/IOArray.hs - − libraries/base/GHC/IOPort.hs - − libraries/base/GHC/IORef.hs - − libraries/base/GHC/InfoProv.hsc - − libraries/base/GHC/Int.hs - − libraries/base/GHC/Integer.hs - − libraries/base/GHC/Integer/Logarithms.hs - − libraries/base/GHC/IsList.hs - − libraries/base/GHC/Ix.hs - − libraries/base/GHC/JS/Foreign/Callback.hs - − libraries/base/GHC/JS/Prim.hs - − libraries/base/GHC/JS/Prim/Internal.hs - − libraries/base/GHC/JS/Prim/Internal/Build.hs - − libraries/base/GHC/List.hs - − libraries/base/GHC/MVar.hs - − libraries/base/GHC/Maybe.hs - − libraries/base/GHC/Natural.hs - − libraries/base/GHC/Num.hs - − libraries/base/GHC/OldList.hs - − libraries/base/GHC/OverloadedLabels.hs - − libraries/base/GHC/Pack.hs - − libraries/base/GHC/Profiling.hs - − libraries/base/GHC/Ptr.hs - − libraries/base/GHC/Read.hs - − libraries/base/GHC/Real.hs - − libraries/base/GHC/Records.hs - − libraries/base/GHC/ResponseFile.hs - − libraries/base/GHC/ST.hs - − libraries/base/GHC/STRef.hs - − libraries/base/GHC/Show.hs - − libraries/base/GHC/Stable.hs - − libraries/base/GHC/StableName.hs - − libraries/base/GHC/Stack.hs - − libraries/base/GHC/Stack/CCS.hs-boot - − libraries/base/GHC/Stack/CloneStack.hs - − libraries/base/GHC/Stack/Types.hs - − libraries/base/GHC/StaticPtr.hs - − libraries/base/GHC/StaticPtr/Internal.hs - − libraries/base/GHC/Storable.hs - − libraries/base/GHC/TopHandler.hs - − libraries/base/GHC/TypeError.hs - − libraries/base/GHC/TypeLits.hs - − libraries/base/GHC/TypeLits/Internal.hs - − libraries/base/GHC/TypeNats.hs - − libraries/base/GHC/TypeNats/Internal.hs - − libraries/base/GHC/Unicode.hs - − libraries/base/GHC/Unicode/Internal/Bits.hs - − libraries/base/GHC/Unicode/Internal/Char/DerivedCoreProperties.hs - − libraries/base/GHC/Unicode/Internal/Char/UnicodeData/GeneralCategory.hs - − libraries/base/GHC/Unicode/Internal/Version.hs - − libraries/base/GHC/Weak.hs - − libraries/base/GHC/Weak/Finalize.hs - − libraries/base/GHC/Windows.hs - − libraries/base/GHC/Word.hs - − libraries/base/Numeric.hs - − libraries/base/Numeric/Natural.hs - − libraries/base/Prelude.hs - − libraries/base/System/CPUTime/Utils.hs - − libraries/base/System/CPUTime/Windows.hsc - − libraries/base/System/Environment.hs - − libraries/base/System/Exit.hs - − libraries/base/System/IO.hs - − libraries/base/System/IO/Error.hs - − libraries/base/System/IO/Unsafe.hs - − libraries/base/System/Mem.hs - − libraries/base/System/Mem/StableName.hs - − libraries/base/System/Mem/Weak.hs - − libraries/base/System/Posix/Internals.hs - − libraries/base/System/Posix/Types.hs - − libraries/base/Text/ParserCombinators/ReadP.hs - − libraries/base/Text/ParserCombinators/ReadPrec.hs - − libraries/base/Text/Read.hs - − libraries/base/Text/Read/Lex.hs - − libraries/base/Text/Show.hs - − libraries/base/Type/Reflection.hs - − libraries/base/Type/Reflection/Unsafe.hs - − libraries/base/Unsafe/Coerce.hs - − libraries/base/aclocal.m4 - − libraries/base/base.buildinfo.in - − libraries/base/base.cabal - + libraries/base/base.cabal.in - − libraries/base/cbits/CastFloatWord.cmm - − libraries/base/cbits/md5.c - libraries/base/changelog.md - − libraries/base/configure.ac - − libraries/base/include/alignment.h - − libraries/base/include/windows_cconv.h - − libraries/base/prologue.txt - libraries/base/Control/Applicative.hs → libraries/base/src/Control/Applicative.hs - + libraries/base/src/Control/Arrow.hs - + libraries/base/src/Control/Category.hs - + libraries/base/src/Control/Concurrent.hs - libraries/base/Control/Concurrent/Chan.hs → libraries/base/src/Control/Concurrent/Chan.hs - + libraries/base/src/Control/Concurrent/MVar.hs - libraries/base/Control/Concurrent/QSem.hs → libraries/base/src/Control/Concurrent/QSem.hs - libraries/base/Control/Concurrent/QSemN.hs → libraries/base/src/Control/Concurrent/QSemN.hs - + libraries/base/src/Control/Exception.hs - + libraries/base/src/Control/Exception/Annotation.hs - + libraries/base/src/Control/Exception/Backtrace.hs - + libraries/base/src/Control/Exception/Base.hs - + libraries/base/src/Control/Exception/Context.hs - + libraries/base/src/Control/Monad.hs - + libraries/base/src/Control/Monad/Fail.hs - + libraries/base/src/Control/Monad/Fix.hs - + libraries/base/src/Control/Monad/IO/Class.hs - + libraries/base/src/Control/Monad/Instances.hs - + libraries/base/src/Control/Monad/ST.hs - + libraries/base/src/Control/Monad/ST/Lazy.hs - + libraries/base/src/Control/Monad/ST/Lazy/Safe.hs - + libraries/base/src/Control/Monad/ST/Lazy/Unsafe.hs - + libraries/base/src/Control/Monad/ST/Safe.hs - + libraries/base/src/Control/Monad/ST/Strict.hs - + libraries/base/src/Control/Monad/ST/Unsafe.hs - + libraries/base/src/Control/Monad/Zip.hs - libraries/base/Data/Array/Byte.hs → libraries/base/src/Data/Array/Byte.hs - libraries/base/Data/Bifoldable.hs → libraries/base/src/Data/Bifoldable.hs - libraries/base/Data/Bifoldable1.hs → libraries/base/src/Data/Bifoldable1.hs - libraries/base/Data/Bifunctor.hs → libraries/base/src/Data/Bifunctor.hs - libraries/base/Data/Bitraversable.hs → libraries/base/src/Data/Bitraversable.hs - + libraries/base/src/Data/Bits.hs - + libraries/base/src/Data/Bool.hs - + libraries/base/src/Data/Bounded.hs - + libraries/base/src/Data/Char.hs - + libraries/base/src/Data/Coerce.hs - libraries/base/Data/Complex.hs → libraries/base/src/Data/Complex.hs - + libraries/base/src/Data/Data.hs - + libraries/base/src/Data/Dynamic.hs - + libraries/base/src/Data/Either.hs - + libraries/base/src/Data/Enum.hs - + libraries/base/src/Data/Eq.hs - + libraries/base/src/Data/Fixed.hs - + libraries/base/src/Data/Foldable.hs - libraries/base/Data/Foldable1.hs → libraries/base/src/Data/Foldable1.hs - + libraries/base/src/Data/Function.hs - + libraries/base/src/Data/Functor.hs - + libraries/base/src/Data/Functor/Classes.hs - libraries/base/Data/Functor/Compose.hs → libraries/base/src/Data/Functor/Compose.hs - + libraries/base/src/Data/Functor/Const.hs - libraries/base/Data/Functor/Contravariant.hs → libraries/base/src/Data/Functor/Contravariant.hs - + libraries/base/src/Data/Functor/Identity.hs - libraries/base/Data/Functor/Product.hs → libraries/base/src/Data/Functor/Product.hs - libraries/base/Data/Functor/Sum.hs → libraries/base/src/Data/Functor/Sum.hs - + libraries/base/src/Data/IORef.hs - + libraries/base/src/Data/Int.hs - + libraries/base/src/Data/Ix.hs - + libraries/base/src/Data/Kind.hs - + libraries/base/src/Data/List.hs - + libraries/base/src/Data/List/NonEmpty.hs - + libraries/base/src/Data/Maybe.hs - + libraries/base/src/Data/Monoid.hs - + libraries/base/src/Data/Ord.hs - + libraries/base/src/Data/Proxy.hs - libraries/base/Data/Ratio.hs → libraries/base/src/Data/Ratio.hs - + libraries/base/src/Data/STRef.hs - + libraries/base/src/Data/STRef/Lazy.hs - + libraries/base/src/Data/STRef/Strict.hs - libraries/base/Data/Semigroup.hs → libraries/base/src/Data/Semigroup.hs - + libraries/base/src/Data/String.hs - + libraries/base/src/Data/Traversable.hs - + libraries/base/src/Data/Tuple.hs - + libraries/base/src/Data/Type/Bool.hs - + libraries/base/src/Data/Type/Coercion.hs - + libraries/base/src/Data/Type/Equality.hs - + libraries/base/src/Data/Type/Ord.hs - + libraries/base/src/Data/Typeable.hs - + libraries/base/src/Data/Unique.hs - + libraries/base/src/Data/Version.hs - + libraries/base/src/Data/Void.hs - + libraries/base/src/Data/Word.hs - + libraries/base/src/Debug/Trace.hs - + libraries/base/src/Foreign.hs - + libraries/base/src/Foreign/C.hs - + libraries/base/src/Foreign/C/ConstPtr.hs - + libraries/base/src/Foreign/C/Error.hs - + libraries/base/src/Foreign/C/String.hs - + libraries/base/src/Foreign/C/Types.hs - + libraries/base/src/Foreign/Concurrent.hs - + libraries/base/src/Foreign/ForeignPtr.hs - + libraries/base/src/Foreign/ForeignPtr/Safe.hs - + libraries/base/src/Foreign/ForeignPtr/Unsafe.hs - + libraries/base/src/Foreign/Marshal.hs - + libraries/base/src/Foreign/Marshal/Alloc.hs - + libraries/base/src/Foreign/Marshal/Array.hs - + libraries/base/src/Foreign/Marshal/Error.hs - + libraries/base/src/Foreign/Marshal/Pool.hs - + libraries/base/src/Foreign/Marshal/Safe.hs - + libraries/base/src/Foreign/Marshal/Unsafe.hs - + libraries/base/src/Foreign/Marshal/Utils.hs - + libraries/base/src/Foreign/Ptr.hs - + libraries/base/src/Foreign/Safe.hs - + libraries/base/src/Foreign/StablePtr.hs - + libraries/base/src/Foreign/Storable.hs - + libraries/base/src/GHC/Arr.hs - + libraries/base/src/GHC/ArrayArray.hs - + libraries/base/src/GHC/Base.hs - + libraries/base/src/GHC/Bits.hs - + libraries/base/src/GHC/ByteOrder.hs - + libraries/base/src/GHC/Char.hs - + libraries/base/src/GHC/Clock.hs - + libraries/base/src/GHC/Conc.hs - + libraries/base/src/GHC/Conc/IO.hs - + libraries/base/src/GHC/Conc/POSIX.hs - + libraries/base/src/GHC/Conc/POSIX/Const.hs - + libraries/base/src/GHC/Conc/Signal.hs - + libraries/base/src/GHC/Conc/Sync.hs - + libraries/base/src/GHC/Conc/WinIO.hs - + libraries/base/src/GHC/Conc/Windows.hs - + libraries/base/src/GHC/ConsoleHandler.hs - + libraries/base/src/GHC/Constants.hs - + libraries/base/src/GHC/Desugar.hs - + libraries/base/src/GHC/Encoding/UTF8.hs - + libraries/base/src/GHC/Enum.hs - + libraries/base/src/GHC/Environment.hs - + libraries/base/src/GHC/Err.hs - + libraries/base/src/GHC/Event.hs - + libraries/base/src/GHC/Event/TimeOut.hs - + libraries/base/src/GHC/Event/Windows.hs - + libraries/base/src/GHC/Event/Windows/Clock.hs - + libraries/base/src/GHC/Event/Windows/ConsoleEvent.hs - + libraries/base/src/GHC/Event/Windows/FFI.hs - + libraries/base/src/GHC/Event/Windows/ManagedThreadPool.hs - + libraries/base/src/GHC/Event/Windows/Thread.hs - + libraries/base/src/GHC/Exception.hs - + libraries/base/src/GHC/Exception/Type.hs - + libraries/base/src/GHC/ExecutionStack.hs - + libraries/base/src/GHC/ExecutionStack/Internal.hs - + libraries/base/src/GHC/Exts.hs - + libraries/base/src/GHC/Fingerprint.hs - + libraries/base/src/GHC/Fingerprint/Type.hs - + libraries/base/src/GHC/Float.hs - + libraries/base/src/GHC/Float/ConversionUtils.hs - + libraries/base/src/GHC/Float/RealFracMethods.hs - + libraries/base/src/GHC/Foreign.hs - + libraries/base/src/GHC/ForeignPtr.hs - + libraries/base/src/GHC/GHCi.hs - + libraries/base/src/GHC/GHCi/Helpers.hs - + libraries/base/src/GHC/Generics.hs - + libraries/base/src/GHC/IO.hs - + libraries/base/src/GHC/IO/Buffer.hs - + libraries/base/src/GHC/IO/BufferedIO.hs - + libraries/base/src/GHC/IO/Device.hs - + libraries/base/src/GHC/IO/Encoding.hs - + libraries/base/src/GHC/IO/Encoding/CodePage.hs - + libraries/base/src/GHC/IO/Encoding/CodePage/API.hs - + libraries/base/src/GHC/IO/Encoding/CodePage/Table.hs - + libraries/base/src/GHC/IO/Encoding/Failure.hs - + libraries/base/src/GHC/IO/Encoding/Iconv.hs - + libraries/base/src/GHC/IO/Encoding/Latin1.hs - + libraries/base/src/GHC/IO/Encoding/Types.hs - + libraries/base/src/GHC/IO/Encoding/UTF16.hs - + libraries/base/src/GHC/IO/Encoding/UTF32.hs - + libraries/base/src/GHC/IO/Encoding/UTF8.hs - + libraries/base/src/GHC/IO/Exception.hs - + libraries/base/src/GHC/IO/FD.hs - + libraries/base/src/GHC/IO/Handle.hs - + libraries/base/src/GHC/IO/Handle/FD.hs - + libraries/base/src/GHC/IO/Handle/Internals.hs - + libraries/base/src/GHC/IO/Handle/Lock.hs - + libraries/base/src/GHC/IO/Handle/Text.hs - + libraries/base/src/GHC/IO/Handle/Types.hs - + libraries/base/src/GHC/IO/Handle/Windows.hs - + libraries/base/src/GHC/IO/IOMode.hs - + libraries/base/src/GHC/IO/StdHandles.hs - + libraries/base/src/GHC/IO/SubSystem.hs - + libraries/base/src/GHC/IO/Unsafe.hs - + libraries/base/src/GHC/IO/Windows/Encoding.hs - + libraries/base/src/GHC/IO/Windows/Handle.hs - + libraries/base/src/GHC/IO/Windows/Paths.hs - + libraries/base/src/GHC/IOArray.hs - + libraries/base/src/GHC/IOPort.hs - + libraries/base/src/GHC/IORef.hs - + libraries/base/src/GHC/InfoProv.hs - + libraries/base/src/GHC/Int.hs - + libraries/base/src/GHC/Integer.hs - + libraries/base/src/GHC/Integer/Logarithms.hs - + libraries/base/src/GHC/IsList.hs - + libraries/base/src/GHC/Ix.hs - + libraries/base/src/GHC/JS/Foreign/Callback.hs - + libraries/base/src/GHC/JS/Prim.hs - + libraries/base/src/GHC/JS/Prim/Internal.hs - + libraries/base/src/GHC/JS/Prim/Internal/Build.hs - + libraries/base/src/GHC/List.hs - + libraries/base/src/GHC/MVar.hs - + libraries/base/src/GHC/Maybe.hs - + libraries/base/src/GHC/Natural.hs - + libraries/base/src/GHC/Num.hs - + libraries/base/src/GHC/Num/BigNat.hs - + libraries/base/src/GHC/Num/Integer.hs - + libraries/base/src/GHC/Num/Natural.hs - + libraries/base/src/GHC/OldList.hs - + libraries/base/src/GHC/OverloadedLabels.hs - + libraries/base/src/GHC/Profiling.hs - + libraries/base/src/GHC/Ptr.hs - + libraries/base/src/GHC/RTS/Flags.hs - + libraries/base/src/GHC/Read.hs - + libraries/base/src/GHC/Real.hs - + libraries/base/src/GHC/Records.hs - + libraries/base/src/GHC/ResponseFile.hs - + libraries/base/src/GHC/ST.hs - + libraries/base/src/GHC/STRef.hs - + libraries/base/src/GHC/Show.hs - + libraries/base/src/GHC/Stable.hs - + libraries/base/src/GHC/StableName.hs - + libraries/base/src/GHC/Stack.hs - + libraries/base/src/GHC/Stack/CCS.hs - + libraries/base/src/GHC/Stack/CloneStack.hs - + libraries/base/src/GHC/Stack/Types.hs - + libraries/base/src/GHC/StaticPtr.hs - + libraries/base/src/GHC/Stats.hs - + libraries/base/src/GHC/Storable.hs - + libraries/base/src/GHC/TopHandler.hs - + libraries/base/src/GHC/TypeError.hs - + libraries/base/src/GHC/TypeLits.hs - + libraries/base/src/GHC/TypeLits/Internal.hs - + libraries/base/src/GHC/TypeNats.hs - + libraries/base/src/GHC/TypeNats/Internal.hs - + libraries/base/src/GHC/Unicode.hs - + libraries/base/src/GHC/Weak.hs - + libraries/base/src/GHC/Weak/Finalize.hs - rts/version.c → libraries/base/src/GHC/Weak/Finalizehs - + libraries/base/src/GHC/Windows.hs - + libraries/base/src/GHC/Word.hs - + libraries/base/src/Numeric.hs - + libraries/base/src/Numeric/Natural.hs - + libraries/base/src/Prelude.hs - libraries/base/System/CPUTime.hsc → libraries/base/src/System/CPUTime.hsc - libraries/base/System/CPUTime/Javascript.hs → libraries/base/src/System/CPUTime/Javascript.hs - libraries/base/System/CPUTime/Posix/ClockGetTime.hsc → libraries/base/src/System/CPUTime/Posix/ClockGetTime.hsc - libraries/base/System/CPUTime/Posix/RUsage.hsc → libraries/base/src/System/CPUTime/Posix/RUsage.hsc - libraries/base/System/CPUTime/Posix/Times.hsc → libraries/base/src/System/CPUTime/Posix/Times.hsc - libraries/base/System/CPUTime/Unsupported.hs → libraries/base/src/System/CPUTime/Unsupported.hs - + libraries/base/src/System/CPUTime/Utils.hs - + libraries/base/src/System/CPUTime/Windows.hsc - libraries/base/System/Console/GetOpt.hs → libraries/base/src/System/Console/GetOpt.hs - + libraries/base/src/System/Environment.hs - + libraries/base/src/System/Environment/Blank.hs - + libraries/base/src/System/Exit.hs - + libraries/base/src/System/IO.hs - + libraries/base/src/System/IO/Error.hs - + libraries/base/src/System/IO/Unsafe.hs - libraries/base/System/Info.hs → libraries/base/src/System/Info.hs - + libraries/base/src/System/Mem.hs - + libraries/base/src/System/Mem/StableName.hs - + libraries/base/src/System/Mem/Weak.hs - + libraries/base/src/System/Posix/Internals.hs - + libraries/base/src/System/Posix/Types.hs - libraries/base/System/Timeout.hs → libraries/base/src/System/Timeout.hs - + libraries/base/src/Text/ParserCombinators/ReadP.hs - + libraries/base/src/Text/ParserCombinators/ReadPrec.hs - libraries/base/Text/Printf.hs → libraries/base/src/Text/Printf.hs - + libraries/base/src/Text/Read.hs - + libraries/base/src/Text/Read/Lex.hs - + libraries/base/src/Text/Show.hs - libraries/base/Text/Show/Functions.hs → libraries/base/src/Text/Show/Functions.hs - + libraries/base/src/Type/Reflection.hs - + libraries/base/src/Type/Reflection/Unsafe.hs - + libraries/base/src/Unsafe/Coerce.hs - + libraries/base/tests/AtomicModifyIORef.hs - + libraries/base/tests/AtomicModifyIORef.stdout - libraries/base/tests/IO/T21336/T21336a.stderr - libraries/base/tests/IO/T21336/all.T - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/all.T - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/openFile002.stderr-mingw32 - libraries/base/tests/IO/openFile002.stderr-mingw32-2 - + libraries/base/tests/IO/withBinaryFile001.hs - + libraries/base/tests/IO/withBinaryFile001.stderr - + libraries/base/tests/IO/withBinaryFile002.hs - + libraries/base/tests/IO/withBinaryFile002.stderr - + libraries/base/tests/IO/withFile001.hs - + libraries/base/tests/IO/withFile001.stderr - + libraries/base/tests/IO/withFile002.hs - + libraries/base/tests/IO/withFile002.stderr - + libraries/base/tests/IO/withFileBlocking001.hs - + libraries/base/tests/IO/withFileBlocking001.stderr - + libraries/base/tests/IO/withFileBlocking002.hs - + libraries/base/tests/IO/withFileBlocking002.stderr - libraries/base/tests/Makefile - libraries/base/tests/System/all.T - libraries/base/tests/T15349.stderr - libraries/base/tests/T16111.stderr - libraries/base/tests/T19288.stderr - + libraries/base/tests/T23687.hs - + libraries/base/tests/T23697.hsc - + libraries/base/tests/T23697.stdout - + libraries/base/tests/T24807.hs - + libraries/base/tests/T24807.stderr - + libraries/base/tests/T25066.hs - + libraries/base/tests/T25066.stderr - libraries/base/tests/T9586.hs - libraries/base/tests/all.T - libraries/base/tests/assert.stderr - libraries/base/tests/char001.hs - libraries/base/tests/char001.stdout - libraries/base/tests/dynamic002.hs - libraries/base/tests/enum01.stdout - libraries/base/tests/enum01.stdout-alpha-dec-osf3 - libraries/base/tests/enum01.stdout-ws-64 - libraries/base/tests/enum02.stdout - libraries/base/tests/enum02.stdout-alpha-dec-osf3 - libraries/base/tests/enum02.stdout-mips-sgi-irix - libraries/base/tests/enum02.stdout-ws-64 - libraries/base/tests/enum02.stdout-x86_64-unknown-openbsd - libraries/base/tests/enum03.stdout - libraries/base/tests/enum03.stdout-alpha-dec-osf3 - libraries/base/tests/enum03.stdout-mips-sgi-irix - libraries/base/tests/enum03.stdout-ws-64 - libraries/base/tests/enum03.stdout-x86_64-unknown-openbsd - libraries/base/tests/foldableArray.hs - libraries/base/tests/lex001.hs - libraries/base/tests/lex001.stdout - libraries/base/tests/list001.hs - + libraries/base/tests/read-float-double.hs - + libraries/base/tests/read-float-double.stdout - libraries/base/tests/readFloat.stderr - + libraries/base/tests/stimesEndo.hs - + libraries/base/tests/stimesEndo.stdout - − libraries/base/tests/topHandler04.hs - − libraries/base/tests/topHandler04.stderr - libraries/base/tests/unicode002.stdout - libraries/base/tests/unicode003.hs - libraries/base/tests/unicode003.stdout - − libraries/base/tools/ucd2haskell/README.md - − libraries/base/tools/ucd2haskell/exe/Parser/Text.hs - − libraries/base/tools/ucd2haskell/exe/UCD2Haskell.hs - − libraries/base/tools/ucd2haskell/ucd2haskell.cabal - − libraries/base/tools/ucd2haskell/unicode_version - libraries/binary - libraries/bytestring - libraries/containers - libraries/deepseq - libraries/directory - libraries/exceptions - + libraries/file-io - libraries/filepath - − libraries/ghc-bignum/.gitignore - + libraries/ghc-bignum/Dummy.hs - − libraries/ghc-bignum/GMP.rst - − libraries/ghc-bignum/README.rst - − libraries/ghc-bignum/Setup.hs - − libraries/ghc-bignum/aclocal.m4 - libraries/ghc-bignum/changelog.md - − libraries/ghc-bignum/config.mk.in - − libraries/ghc-bignum/configure.ac - − libraries/ghc-bignum/ghc-bignum.buildinfo.in - libraries/ghc-bignum/ghc-bignum.cabal - − libraries/ghc-bignum/gmp/gmp-tarballs - − libraries/ghc-bignum/gmp/gmpsrc.patch - − libraries/ghc-bignum/gmp/ln - − libraries/ghc-bignum/install-sh - − libraries/ghc-bignum/src/GHC/Num/Backend.hs - − libraries/ghc-bignum/src/GHC/Num/Backend/FFI.hs - − libraries/ghc-bignum/src/GHC/Num/Backend/Selected.hs - − libraries/ghc-bignum/src/GHC/Num/BigNat.hs - − libraries/ghc-bignum/src/GHC/Num/Integer.hs - − libraries/ghc-bignum/src/GHC/Num/Natural.hs - − libraries/ghc-bignum/src/GHC/Num/Primitives.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - + libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/GHC/ForeignSrcLang/Type.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - libraries/ghc-boot-th/GHC/Lexeme.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/BaseDir.hs - libraries/ghc-boot/GHC/Data/ShortText.hs - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-boot/GHC/Settings/Utils.hs - libraries/ghc-boot/GHC/Utils/Encoding.hs - libraries/ghc-boot/GHC/Utils/Encoding/UTF8.hs - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/ghc-compact.cabal - + libraries/ghc-compact/tests/T18757.stdout-wasm32-unknown-wasi - libraries/ghc-compact/tests/all.T - libraries/ghc-compact/tests/compact_function.stderr - libraries/ghc-compact/tests/compact_mutable.stderr - libraries/ghc-compact/tests/compact_pinned.stderr - + libraries/ghc-experimental/CHANGELOG.md - + libraries/ghc-experimental/LICENSE - + libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/Data/Sum/Experimental.hs - + libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - + libraries/ghc-experimental/src/GHC/PrimOps.hs - + libraries/ghc-experimental/src/GHC/Profiling/Eras.hs - + libraries/ghc-experimental/src/GHC/RTS/Flags/Experimental.hs - + libraries/ghc-experimental/src/GHC/Stats/Experimental.hs - + libraries/ghc-experimental/src/GHC/TypeLits/Experimental.hs - + libraries/ghc-experimental/src/GHC/TypeNats/Experimental.hs - + libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - + libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Stack.hs - + libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc - + libraries/ghc-heap/GHC/Exts/Stack/Decode.hs - + libraries/ghc-heap/cbits/Stack.cmm - + libraries/ghc-heap/cbits/Stack_c.c - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/stack_big_ret.hs - + libraries/ghc-heap/tests/stack_misc_closures.hs - + libraries/ghc-heap/tests/stack_misc_closures_c.c - + libraries/ghc-heap/tests/stack_misc_closures_prim.cmm - + libraries/ghc-heap/tests/stack_stm_frames.hs - + libraries/ghc-heap/tests/stack_underflow.hs - libraries/base/.authorspellings → libraries/ghc-internal/.authorspellings - + libraries/ghc-internal/.gitignore - libraries/base/.hlint.yaml → libraries/ghc-internal/.hlint.yaml - + libraries/ghc-internal/CHANGELOG.md - + libraries/ghc-internal/LICENSE - libraries/base/Setup.hs → libraries/ghc-internal/Setup.hs - + libraries/ghc-internal/aclocal.m4 - + libraries/ghc-internal/bignum-backend.rst - libraries/base/cbits/DarwinUtils.c → libraries/ghc-internal/cbits/DarwinUtils.c - libraries/base/cbits/IOutils.c → libraries/ghc-internal/cbits/IOutils.c - libraries/base/cbits/PrelIOUtils.c → libraries/ghc-internal/cbits/PrelIOUtils.c - libraries/base/cbits/SetEnv.c → libraries/ghc-internal/cbits/SetEnv.c - libraries/base/cbits/StackCloningDecoding.cmm → libraries/ghc-internal/cbits/StackCloningDecoding.cmm - libraries/base/cbits/Win32Utils.c → libraries/ghc-internal/cbits/Win32Utils.c - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/base/cbits/consUtils.c → libraries/ghc-internal/cbits/consUtils.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-bignum/cbits/gmp_wrappers.c → libraries/ghc-internal/cbits/gmp_wrappers.c - libraries/base/cbits/iconv.c → libraries/ghc-internal/cbits/iconv.c - libraries/base/cbits/inputReady.c → libraries/ghc-internal/cbits/inputReady.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - + libraries/ghc-internal/cbits/md5.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/base/cbits/primFloat.c → libraries/ghc-internal/cbits/primFloat.c - + libraries/ghc-internal/cbits/strerror.c - libraries/base/cbits/sysconf.c → libraries/ghc-internal/cbits/sysconf.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/base/codepages/MakeTable.hs → libraries/ghc-internal/codepages/MakeTable.hs - libraries/base/codepages/Makefile → libraries/ghc-internal/codepages/Makefile - + libraries/ghc-internal/configure.ac - + libraries/ghc-internal/ghc-internal.buildinfo.in - + libraries/ghc-internal/ghc-internal.cabal.in - + libraries/ghc-internal/gmp-backend.rst - libraries/ghc-bignum/gmp/ghc-gmp.h → libraries/ghc-internal/gmp/ghc-gmp.h - + libraries/ghc-internal/gmp/gmp-tarballs - libraries/base/include/CTypes.h → libraries/ghc-internal/include/CTypes.h - libraries/base/include/EventConfig.h.in → libraries/ghc-internal/include/EventConfig.h.in - libraries/base/include/HsBase.h → libraries/ghc-internal/include/HsBase.h - libraries/base/include/HsEvent.h → libraries/ghc-internal/include/HsEvent.h - libraries/ghc-bignum/include/HsIntegerGmp.h.in → libraries/ghc-internal/include/HsIntegerGmp.h.in - libraries/ghc-bignum/include/WordSize.h → libraries/ghc-internal/include/WordSize.h - libraries/base/include/consUtils.h → libraries/ghc-internal/include/consUtils.h - libraries/base/include/ieee-flpt.h → libraries/ghc-internal/include/ieee-flpt.h - libraries/base/include/md5.h → libraries/ghc-internal/include/md5.h - libraries/base/include/winio_structs.h → libraries/ghc-internal/include/winio_structs.h - libraries/base/install-sh → libraries/ghc-internal/install-sh - libraries/base/jsbits/base.js → libraries/ghc-internal/jsbits/base.js - libraries/base/jsbits/errno.js → libraries/ghc-internal/jsbits/errno.js - libraries/base/jsbits/platform.js → libraries/ghc-internal/jsbits/platform.js - + libraries/ghc-internal/prologue.txt - + libraries/ghc-internal/src/GHC/Internal/Arr.hs - + libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - + libraries/ghc-internal/src/GHC/Internal/Base.hs - + libraries/ghc-internal/src/GHC/Internal/Bignum/Backend.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Check.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - + libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Native.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - + libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Selected.hs - + libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-bignum/src/GHC/Num/Integer.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-bignum/src/GHC/Num/Natural.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-bignum/src/GHC/Num/WordArray.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - + libraries/ghc-internal/src/GHC/Internal/Bits.hs - + libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs - libraries/base/GHC/ByteOrder.hs-boot → libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - + libraries/ghc-internal/src/GHC/Internal/Char.hs - + libraries/ghc-internal/src/GHC/Internal/Classes.hs - + libraries/ghc-internal/src/GHC/Internal/Clock.hsc - + libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs - + libraries/ghc-internal/src/GHC/Internal/Conc/Bound.hs - + libraries/ghc-internal/src/GHC/Internal/Conc/IO.hs - + libraries/ghc-internal/src/GHC/Internal/Conc/POSIX.hs - libraries/base/GHC/Conc/POSIX/Const.hsc → libraries/ghc-internal/src/GHC/Internal/Conc/POSIX/Const.hsc - + libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - + libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/base/GHC/Conc/Sync.hs-boot → libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Conc/Windows.hs - libraries/base/GHC/ConsoleHandler.hsc → libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - + libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Category.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Concurrent/MVar.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad/IO/Class.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad/ST.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad/ST/Imp.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad/ST/Lazy.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad/ST/Lazy/Imp.hs - + libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Bits.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Bool.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Dynamic.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Either.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Eq.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Function.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Functor.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Functor/Const.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Functor/Utils.hs - + libraries/ghc-internal/src/GHC/Internal/Data/IORef.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Ix.hs - + libraries/ghc-internal/src/GHC/Internal/Data/List.hs - + libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Maybe.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Monoid.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Ord.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Proxy.hs - + libraries/ghc-internal/src/GHC/Internal/Data/STRef.hs - + libraries/ghc-internal/src/GHC/Internal/Data/STRef/Strict.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Semigroup/Internal.hs - + libraries/ghc-internal/src/GHC/Internal/Data/String.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Type/Bool.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Type/Coercion.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Type/Equality.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Typeable.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Unique.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Version.hs - + libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Data/Void.hs - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - + libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs - libraries/base/Debug/Trace.hs-boot → libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Desugar.hs - + libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - + libraries/ghc-internal/src/GHC/Internal/Enum.hs - + libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Environment.hs - + libraries/ghc-internal/src/GHC/Internal/Err.hs - + libraries/ghc-internal/src/GHC/Internal/Event.hs - + libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - + libraries/ghc-internal/src/GHC/Internal/Event/Array.hs - libraries/base/GHC/Event/Control.hs → libraries/ghc-internal/src/GHC/Internal/Event/Control.hs - libraries/base/GHC/Event/EPoll.hsc → libraries/ghc-internal/src/GHC/Internal/Event/EPoll.hsc - libraries/base/GHC/Event/IntTable.hs → libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/base/GHC/Event/IntVar.hs → libraries/ghc-internal/src/GHC/Internal/Event/IntVar.hs - + libraries/ghc-internal/src/GHC/Internal/Event/Internal.hs - + libraries/ghc-internal/src/GHC/Internal/Event/Internal/Types.hs - libraries/base/GHC/Event/KQueue.hsc → libraries/ghc-internal/src/GHC/Internal/Event/KQueue.hsc - libraries/base/GHC/Event/Manager.hs → libraries/ghc-internal/src/GHC/Internal/Event/Manager.hs - libraries/base/GHC/Event/PSQ.hs → libraries/ghc-internal/src/GHC/Internal/Event/PSQ.hs - libraries/base/GHC/Event/Poll.hsc → libraries/ghc-internal/src/GHC/Internal/Event/Poll.hsc - + libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - + libraries/ghc-internal/src/GHC/Internal/Event/TimeOut.hs - libraries/base/GHC/Event/TimerManager.hs → libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - + libraries/ghc-internal/src/GHC/Internal/Event/Unique.hs - + libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc - + libraries/ghc-internal/src/GHC/Internal/Event/Windows/Clock.hs - libraries/base/GHC/Event/Windows/ConsoleEvent.hsc → libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/base/GHC/Event/Windows/FFI.hsc → libraries/ghc-internal/src/GHC/Internal/Event/Windows/FFI.hsc - + libraries/ghc-internal/src/GHC/Internal/Event/Windows/ManagedThreadPool.hs - + libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs - + libraries/ghc-internal/src/GHC/Internal/Exception.hs - + libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs - + libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs - + libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/base/GHC/Exception/Type.hs-boot → libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - + libraries/ghc-internal/src/GHC/Internal/ExecutionStack.hs - libraries/base/GHC/ExecutionStack/Internal.hsc → libraries/ghc-internal/src/GHC/Internal/ExecutionStack/Internal.hsc - + libraries/ghc-internal/src/GHC/Internal/Exts.hs - + libraries/ghc-internal/src/GHC/Internal/Fingerprint.hs - libraries/base/GHC/Fingerprint.hs-boot → libraries/ghc-internal/src/GHC/Internal/Fingerprint.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Fingerprint/Type.hs - + libraries/ghc-internal/src/GHC/Internal/Float.hs - + libraries/ghc-internal/src/GHC/Internal/Float/ConversionUtils.hs - + libraries/ghc-internal/src/GHC/Internal/Float/RealFracMethods.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/C/ConstPtr.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/C/Error.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/C/String.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/C/Types.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Concurrent.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/ForeignPtr.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/ForeignPtr/Imp.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/ForeignPtr/Unsafe.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Marshal/Alloc.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Marshal/Array.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Marshal/Error.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Marshal/Pool.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Marshal/Safe.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Marshal/Unsafe.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Marshal/Utils.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Ptr.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/StablePtr.hs - + libraries/ghc-internal/src/GHC/Internal/Foreign/Storable.hs - + libraries/ghc-internal/src/GHC/Internal/ForeignPtr.hs - + libraries/ghc-internal/src/GHC/Internal/ForeignSrcLang.hs - + libraries/ghc-internal/src/GHC/Internal/Functor/ZipList.hs - + libraries/ghc-internal/src/GHC/Internal/GHCi.hs - + libraries/ghc-internal/src/GHC/Internal/GHCi/Helpers.hs - + libraries/ghc-internal/src/GHC/Internal/Generics.hs - + libraries/ghc-internal/src/GHC/Internal/IO.hs - + libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - + libraries/ghc-internal/src/GHC/Internal/IO/Buffer.hs - + libraries/ghc-internal/src/GHC/Internal/IO/BufferedIO.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Device.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding.hs-boot - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/API.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Failure.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Latin1.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Types.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/UTF16.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/UTF32.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Encoding/UTF8.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs-boot - + libraries/ghc-internal/src/GHC/Internal/IO/FD.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs-boot - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs-boot - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Internals.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/base/GHC/IO/Handle/Lock/Common.hs → libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Common.hs - libraries/base/GHC/IO/Handle/Lock/Flock.hsc → libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/base/GHC/IO/Handle/Lock/LinuxOFD.hsc → libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/NoOp.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs-boot - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - + libraries/ghc-internal/src/GHC/Internal/IO/Handle/Windows.hs - + libraries/ghc-internal/src/GHC/Internal/IO/IOMode.hs - + libraries/ghc-internal/src/GHC/Internal/IO/StdHandles.hs - libraries/base/GHC/IO/StdHandles.hs-boot → libraries/ghc-internal/src/GHC/Internal/IO/StdHandles.hs-boot - + libraries/ghc-internal/src/GHC/Internal/IO/SubSystem.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Unsafe.hs - + libraries/ghc-internal/src/GHC/Internal/IO/Windows/Encoding.hs - libraries/base/GHC/IO/Windows/Handle.hsc → libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc - + libraries/ghc-internal/src/GHC/Internal/IO/Windows/Paths.hs - + libraries/ghc-internal/src/GHC/Internal/IOArray.hs - + libraries/ghc-internal/src/GHC/Internal/IOPort.hs - + libraries/ghc-internal/src/GHC/Internal/IORef.hs - + libraries/ghc-internal/src/GHC/Internal/InfoProv.hs - + libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - + libraries/ghc-internal/src/GHC/Internal/Int.hs - + libraries/ghc-internal/src/GHC/Internal/Integer.hs - + libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - + libraries/ghc-internal/src/GHC/Internal/IsList.hs - + libraries/ghc-internal/src/GHC/Internal/Ix.hs - + libraries/ghc-internal/src/GHC/Internal/JS/Foreign/Callback.hs - + libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - + libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal.hs - + libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - + libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - + libraries/ghc-internal/src/GHC/Internal/Lexeme.hs - + libraries/ghc-internal/src/GHC/Internal/List.hs - + libraries/ghc-internal/src/GHC/Internal/MVar.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - + libraries/ghc-internal/src/GHC/Internal/Maybe.hs - + libraries/ghc-internal/src/GHC/Internal/Natural.hs - + libraries/ghc-internal/src/GHC/Internal/Num.hs - libraries/base/GHC/Num.hs-boot → libraries/ghc-internal/src/GHC/Internal/Num.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Numeric.hs - + libraries/ghc-internal/src/GHC/Internal/Numeric/Natural.hs - + libraries/ghc-internal/src/GHC/Internal/OverloadedLabels.hs - + libraries/ghc-internal/src/GHC/Internal/Pack.hs - + libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - + libraries/ghc-internal/src/GHC/Internal/Profiling.hs - + libraries/ghc-internal/src/GHC/Internal/Ptr.hs - libraries/base/GHC/RTS/Flags.hsc → libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc - + libraries/ghc-internal/src/GHC/Internal/RTS/Flags/Test.hsc - + libraries/ghc-internal/src/GHC/Internal/Read.hs - + libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/base/GHC/Real.hs-boot → libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - + libraries/ghc-internal/src/GHC/Internal/Records.hs - + libraries/ghc-internal/src/GHC/Internal/ResponseFile.hs - + libraries/ghc-internal/src/GHC/Internal/ST.hs - + libraries/ghc-internal/src/GHC/Internal/STRef.hs - + libraries/ghc-internal/src/GHC/Internal/Show.hs - + libraries/ghc-internal/src/GHC/Internal/Stable.hs - + libraries/ghc-internal/src/GHC/Internal/StableName.hs - + libraries/ghc-internal/src/GHC/Internal/Stack.hs - + libraries/ghc-internal/src/GHC/Internal/Stack.hs-boot - libraries/base/GHC/Stack/CCS.hsc → libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hsc - + libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs - + libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - + libraries/ghc-internal/src/GHC/Internal/StaticPtr.hs - + libraries/ghc-internal/src/GHC/Internal/StaticPtr/Internal.hs - libraries/base/GHC/Stats.hsc → libraries/ghc-internal/src/GHC/Internal/Stats.hsc - + libraries/ghc-internal/src/GHC/Internal/Storable.hs - + libraries/ghc-internal/src/GHC/Internal/System/Environment.hs - libraries/base/System/Environment/Blank.hsc → libraries/ghc-internal/src/GHC/Internal/System/Environment/Blank.hsc - libraries/base/System/Environment/ExecutablePath.hsc → libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc - + libraries/ghc-internal/src/GHC/Internal/System/Exit.hs - + libraries/ghc-internal/src/GHC/Internal/System/IO.hs - + libraries/ghc-internal/src/GHC/Internal/System/IO/Error.hs - + libraries/ghc-internal/src/GHC/Internal/System/Mem.hs - + libraries/ghc-internal/src/GHC/Internal/System/Mem/StableName.hs - + libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs - + libraries/ghc-internal/src/GHC/Internal/System/Posix/Types.hs - + libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - + libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - + libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs - + libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - + libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - + libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadPrec.hs - + libraries/ghc-internal/src/GHC/Internal/Text/Read.hs - + libraries/ghc-internal/src/GHC/Internal/Text/Read/Lex.hs - + libraries/ghc-internal/src/GHC/Internal/Text/Show.hs - + libraries/ghc-internal/src/GHC/Internal/TopHandler.hs - + libraries/ghc-internal/src/GHC/Internal/Tuple.hs - + libraries/ghc-internal/src/GHC/Internal/Type/Reflection.hs - + libraries/ghc-internal/src/GHC/Internal/Type/Reflection/Unsafe.hs - + libraries/ghc-internal/src/GHC/Internal/TypeError.hs - + libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - + libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - + libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - + libraries/ghc-internal/src/GHC/Internal/TypeNats/Internal.hs - + libraries/ghc-internal/src/GHC/Internal/Types.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - libraries/base/GHC/Unicode/Internal/Char/UnicodeData/SimpleLowerCaseMapping.hs → libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs - libraries/base/GHC/Unicode/Internal/Char/UnicodeData/SimpleTitleCaseMapping.hs → libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs - libraries/base/GHC/Unicode/Internal/Char/UnicodeData/SimpleUpperCaseMapping.hs → libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs - + libraries/ghc-internal/src/GHC/Internal/Unsafe/Coerce.hs - + libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - + libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Conc.hs - + libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Conc/Internal.hs - + libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - + libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - + libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - + libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - + libraries/ghc-internal/src/GHC/Internal/Weak.hs - + libraries/ghc-internal/src/GHC/Internal/Weak/Finalize.hs - + libraries/ghc-internal/src/GHC/Internal/Windows.hs - + libraries/ghc-internal/src/GHC/Internal/Word.hs - libraries/base/tools/ucd2haskell/.gitignore → libraries/ghc-internal/tools/ucd2haskell/.gitignore - libraries/base/tools/ucd2haskell/LICENSE → libraries/ghc-internal/tools/ucd2haskell/LICENSE - + libraries/ghc-internal/tools/ucd2haskell/README.md - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/ByteString.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs - libraries/base/tools/ucd2haskell/tests/check_all_chars.py → libraries/ghc-internal/tools/ucd2haskell/tests/check_all_chars.py - libraries/base/tools/ucd2haskell/tests/check_test_data.py → libraries/ghc-internal/tools/ucd2haskell/tests/check_test_data.py - libraries/base/tools/ucd2haskell/tests/export_all_chars.hs → libraries/ghc-internal/tools/ucd2haskell/tests/export_all_chars.hs - libraries/base/tools/ucd2haskell/ucd.sh → libraries/ghc-internal/tools/ucd2haskell/ucd.sh - + libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal - + libraries/ghc-internal/tools/ucd2haskell/unicode_version - + libraries/ghc-platform/Setup.hs - libraries/ghc-platform/ghc-platform.cabal - libraries/ghc-platform/src/GHC/Platform/ArchOS.hs - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/GHC/Classes.hs - − libraries/ghc-prim/GHC/Prim/Exception.hs - − libraries/ghc-prim/GHC/Tuple.hs - − libraries/ghc-prim/GHC/Tuple/Prim.hs - − libraries/ghc-prim/GHC/Types.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - + libraries/ghc-prim/ghc-prim.cabal - − libraries/ghc-prim/ghc-prim.cabal.in - libraries/ghci/GHCi/BinaryArray.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/CreateBCO.hs - libraries/ghci/GHCi/FFI.hsc - libraries/ghci/GHCi/InfoTable.hsc - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/ResolvedBCO.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/Server.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/integer-gmp/changelog.md - libraries/integer-gmp/integer-gmp.cabal - libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs - + libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/Language/Haskell/TH.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - libraries/template-haskell/tests/all.T - + libraries/template-haskell/tests/dataToCodeQUnit.hs - testsuite/tests/stranal/should_run/T14285.stdout → libraries/template-haskell/tests/dataToCodeQUnit.stdout - libraries/template-haskell/vendored-filepath/System/FilePath.hs - libraries/terminfo - libraries/text - libraries/time - libraries/transformers - libraries/unix - + linters/lint-codes/LintCodes/Args.hs - + linters/lint-codes/LintCodes/Coverage.hs - + linters/lint-codes/LintCodes/Static.hs - + linters/lint-codes/Main.hs - + linters/lint-codes/Makefile - + linters/lint-codes/cabal.project - + linters/lint-codes/ghc.mk - + linters/lint-codes/lint-codes.cabal - linters/lint-commit-msg/lint-commit-msg.cabal - linters/lint-notes/Main.hs - linters/lint-submodule-refs/Main.hs - linters/lint-submodule-refs/lint-submodule-refs.cabal - linters/lint-whitespace/lint-whitespace.cabal - linters/linters-common/Linters/Common.hs - linters/linters-common/linters-common.cabal - llvm-passes - llvm-targets - + m4/emsdk_version.m4 - m4/find_ld.m4 - m4/find_llvm_prog.m4 - m4/find_merge_objects.m4 - + m4/fp_armv8_outline_atomics.m4 - m4/fp_bfd_support.m4 - m4/fp_cc_linker_flag_try.m4 - m4/fp_cc_supports__atomics.m4 - m4/fp_cc_supports_target.m4 - m4/fp_check_pthreads.m4 - + m4/fp_cmm_cpp_cmd_with_args.m4 - m4/fp_cpp_cmd_with_args.m4 - m4/fp_find_cxx_std_lib.m4 - m4/fp_find_libdw.m4 - m4/fp_find_libffi.m4 - m4/fp_find_libnuma.m4 - m4/fp_find_libzstd.m4 - m4/fp_find_nm.m4 - m4/fp_gcc_supports_no_pie.m4 - m4/fp_gcc_version.m4 - m4/fp_hs_cpp_cmd_with_args.m4 - + m4/fp_js_cpp_cmd_with_args.m4 - m4/fp_ld_no_fixup_chains.m4 - + m4/fp_ld_no_warn_duplicate_libraries.m4 - m4/fp_leading_underscore.m4 - m4/fp_link_supports_no_as_needed.m4 - m4/fp_prog_ar_args.m4 - m4/fp_prog_ar_needs_ranlib.m4 - + m4/fp_prog_cc_linker_target.m4 - − m4/fp_prog_context_diff.m4 - m4/fp_prog_ld_is_gnu.m4 - m4/fp_prog_ld_no_compact_unwind.m4 - + m4/fp_prog_ld_single_module.m4 - + m4/fp_prog_move_to_flags.m4 - m4/fp_settings.m4 - m4/fp_setup_project_version.m4 - m4/fp_setup_windows_toolchain.m4 - m4/fptools_alex.m4 - m4/fptools_happy.m4 - m4/fptools_set_c_ld_flags.m4 - m4/fptools_set_haskell_platform_vars.m4 - m4/ghc_adjustors_method.m4 - m4/ghc_convert_cpu.m4 - m4/ghc_convert_os.m4 - + m4/ghc_get_power_abi.m4 - + m4/ghc_iomanagers.m4 - m4/ghc_llvm_target.m4 - m4/ghc_select_file_extensions.m4 - + m4/ghc_toolchain.m4 - − m4/library_version.m4 - + m4/prep_target_file.m4 - − m4/xcode_version.m4 - + mk/hsc2hs.in - mk/project.mk.in - mk/relpath.sh - mk/system-cxx-std-lib-1.0.conf.in - nofib - packages - rts/.gitignore - + rts/ARMOutlineAtomicsSymbols.h - − rts/AdjustorAsm.S - rts/Apply.cmm - rts/AutoApply.h - + rts/AutoApplyVecs.h - rts/Capability.c - rts/Capability.h - rts/CheckUnload.c - + rts/CheckVectorSupport.c - + rts/CheckVectorSupport.h - rts/CloneStack.c - rts/CloneStack.h - rts/Compact.cmm - rts/Continuation.c - rts/ContinuationOps.cmm - rts/Disassembler.c - rts/Exception.cmm - rts/ExecPage.c - rts/Hash.c - rts/Heap.c - rts/HeapStackCheck.cmm - rts/Hpc.c - rts/IOManager.c - rts/IOManager.h - + rts/IOManagerInternals.h - rts/IPE.c - rts/IPE.h - rts/Inlines.c - rts/Interpreter.c - rts/Interpreter.h - + rts/Jumps.h - + rts/Jumps_D.cmm - + rts/Jumps_V16.cmm - + rts/Jumps_V32.cmm - + rts/Jumps_V64.cmm - rts/LdvProfile.h - rts/Libdw.c - rts/Linker.c - rts/LinkerInternals.h - rts/Messages.c - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/ProfHeap.c - rts/ProfHeap.h - rts/ProfilerReportJson.c - rts/Profiling.c - rts/Profiling.h - rts/Proftimer.c - rts/RaiseAsync.c - rts/RtsAPI.c - rts/RtsFlags.c - rts/RtsFlags.h - rts/RtsMain.c - rts/RtsMessages.c - rts/RtsStartup.c - rts/RtsSymbols.c - rts/RtsSymbols.h - rts/RtsUtils.c - rts/RtsUtils.h - rts/STM.c - rts/STM.h - rts/Schedule.c - rts/Sparks.c - rts/StableName.c - rts/StgCRun.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStartup.cmm - rts/StgStdThunks.cmm - rts/TSANUtils.c - rts/Task.c - rts/Task.h - rts/ThreadLabels.c - rts/ThreadPaused.c - rts/Threads.c - rts/Ticky.c - rts/Trace.c - rts/Trace.h - rts/TraverseHeap.c - rts/Updates.cmm - rts/Updates.h - rts/Weak.c - rts/adjustor/AdjustorPool.c - rts/adjustor/LibffiAdjustor.c - rts/adjustor/NativeAmd64.c - rts/adjustor/NativeAmd64Asm.S - rts/adjustor/NativeAmd64Mingw.c - rts/adjustor/NativeAmd64MingwAsm.S - − rts/adjustor/NativeIA64.c - − rts/adjustor/NativePowerPC.c - rts/adjustor/Nativei386.c - rts/adjustor/Nativei386Asm.S - rts/configure.ac - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - + rts/external-symbols.list.in - rts/gen_event_types.py - + rts/ghcplatform.h.bottom - + rts/ghcplatform.h.top.in - − rts/ghcversion.h.bottom - − rts/ghcversion.h.top - rts/include/Cmm.h - rts/include/Rts.h - rts/include/RtsAPI.h - rts/include/Stg.h - + rts/include/ghcversion.h.in - rts/include/rts/Adjustor.h - rts/include/rts/Bytecodes.h - rts/include/rts/Config.h - rts/include/rts/Constants.h - rts/include/rts/EventLogFormat.h - rts/include/rts/Flags.h - rts/include/rts/IPE.h - rts/include/rts/Linker.h - rts/include/rts/Messages.h - rts/include/rts/OSThreads.h - rts/include/rts/TSANUtils.h - rts/include/rts/Threads.h - rts/include/rts/Ticky.h - rts/include/rts/ghc_ffi.h - rts/include/rts/prof/CCS.h - rts/include/rts/prof/Heap.h - rts/include/rts/prof/LDV.h - rts/include/rts/storage/Block.h - rts/include/rts/storage/ClosureMacros.h - rts/include/rts/storage/ClosureTypes.h - rts/include/rts/storage/Closures.h - rts/sm/HeapAlloc.h → rts/include/rts/storage/HeapAlloc.h - rts/include/rts/storage/InfoTables.h - rts/include/rts/storage/TSO.h - rts/include/stg/MachRegs.h - + rts/include/stg/MachRegs/arm32.h - + rts/include/stg/MachRegs/arm64.h - + rts/include/stg/MachRegs/loongarch64.h - + rts/include/stg/MachRegs/ppc.h - + rts/include/stg/MachRegs/riscv64.h - + rts/include/stg/MachRegs/s390x.h - + rts/include/stg/MachRegs/wasm32.h - + rts/include/stg/MachRegs/x86.h - rts/include/stg/MachRegsForHost.h - rts/include/stg/MiscClosures.h - rts/include/stg/Prim.h - rts/include/stg/SMP.h - rts/js/arith.js - + rts/js/config.js - rts/js/environment.js - rts/js/gc.js - rts/js/mem.js - rts/js/profiling.js - rts/js/rts.js - rts/js/stableptr.js - rts/js/string.js - rts/js/thread.js - rts/js/time.js - rts/js/verify.js - rts/linker/Elf.c - rts/linker/Elf.h - rts/linker/ElfTypes.h - + rts/linker/LoadNativeObjPosix.c - + rts/linker/LoadNativeObjPosix.h - rts/linker/M32Alloc.c - rts/linker/MMap.c - rts/linker/MMap.h - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/PEi386.h - rts/linker/SymbolExtras.c - rts/linker/SymbolExtras.h - rts/linker/elf_got.c - rts/linker/elf_plt.c - rts/linker/elf_plt.h - + rts/linker/elf_plt_riscv64.c - + rts/linker/elf_plt_riscv64.h - rts/linker/elf_reloc.c - rts/linker/elf_reloc.h - rts/linker/elf_reloc_aarch64.c - rts/linker/elf_reloc_aarch64.h - + rts/linker/elf_reloc_riscv64.c - + rts/linker/elf_reloc_riscv64.h - rts/linker/macho/plt.c - rts/posix/OSMem.c - rts/posix/Select.c - rts/posix/Select.h - rts/posix/Signals.c - rts/posix/ticker/TimerFd.c - + rts/rts.buildinfo.in - + rts/rts.cabal - − rts/rts.cabal.in - rts/sm/BlockAlloc.c - rts/sm/CNF.c - rts/sm/Compact.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - rts/sm/GCAux.c - rts/sm/GCThread.h - rts/sm/MBlock.c - rts/sm/NonMoving.c - rts/sm/NonMoving.h - rts/sm/NonMovingAllocate.c - rts/sm/NonMovingCensus.c - rts/sm/NonMovingMark.c - rts/sm/Sanity.c - rts/sm/Sanity.h - rts/sm/Scav.c - rts/sm/Storage.c - rts/sm/Storage.h - + rts/wasm/JSFFI.c - + rts/wasm/JSFFIGlobals.c - rts/wasm/OSMem.c - rts/wasm/StgRun.c - rts/wasm/Wasm.S - + rts/wasm/blocker.cmm - + rts/wasm/jsval.cmm - + rts/wasm/scheduler.cmm - rts/win32/AsyncMIO.c - rts/win32/AwaitEvent.c - + rts/win32/AwaitEvent.h - rts/win32/ConsoleHandler.c - rts/win32/OSMem.c - rts/win32/OSThreads.c - rts/win32/ThrIOManager.c - − rts/win32/libHSbase.def - + rts/win32/libHSghc-internal.def - rts/win32/libHSghc-prim.def - rts/win32/veh_excn.c - rts/xxhash.h - testsuite/config/ghc - testsuite/driver/cpu_features.py - + testsuite/driver/cpuinfo.py - testsuite/driver/perf_notes.py - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/driver/testutil.py - testsuite/ghc-config/ghc-config.hs - + testsuite/ghc-config/hie.yaml - testsuite/mk/boilerplate.mk - testsuite/mk/test.mk - + testsuite/tests/Win32/HandleConversion.hs - + testsuite/tests/Win32/HandleConversion.stdout - + testsuite/tests/Win32/Makefile - + testsuite/tests/Win32/PokeTZI.hs - + testsuite/tests/Win32/Semaphores.hs - + testsuite/tests/Win32/Semaphores.stdout - + testsuite/tests/Win32/T4452.hs - + testsuite/tests/Win32/all.T - + testsuite/tests/Win32/helloworld.hs - + testsuite/tests/Win32/lasterror.hs - + testsuite/tests/Win32/registry001.hs - + testsuite/tests/Win32/registry001.stdout - + testsuite/tests/ado/OrPatStrictness.hs - + testsuite/tests/ado/OrPatStrictness.stderr - + testsuite/tests/ado/OrPatStrictness.stdout - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/T16135.stderr - testsuite/tests/ado/T22483.stderr - testsuite/tests/ado/ado002.stderr - testsuite/tests/ado/all.T - testsuite/tests/annotations/should_fail/annfail05.stderr - testsuite/tests/annotations/should_fail/annfail08.stderr - testsuite/tests/annotations/should_fail/annfail10.hs - testsuite/tests/annotations/should_fail/annfail10.stderr - testsuite/tests/annotations/should_fail/annfail12.stderr - testsuite/tests/annotations/should_run/all.T - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity13.stderr - testsuite/tests/arityanal/should_compile/T21755.stderr - + testsuite/tests/arityanal/should_compile/T24296b.hs - + testsuite/tests/arityanal/should_compile/T24296b.stderr - testsuite/tests/arityanal/should_compile/all.T - testsuite/tests/arityanal/should_run/T21694a.stderr - + testsuite/tests/arityanal/should_run/T24296.hs - + testsuite/tests/arityanal/should_run/T24296.stderr - testsuite/tests/arityanal/should_run/all.T - testsuite/tests/array/should_run/arr003.stderr - testsuite/tests/array/should_run/arr004.stderr - testsuite/tests/array/should_run/arr007.stderr - testsuite/tests/array/should_run/arr008.stderr - testsuite/tests/arrows/should_compile/T21301.stderr - testsuite/tests/backpack/cabal/T14304/Makefile - testsuite/tests/backpack/cabal/T14304/all.T - testsuite/tests/backpack/cabal/T15594/Makefile - testsuite/tests/backpack/cabal/T15594/all.T - testsuite/tests/backpack/cabal/T16219/Makefile - testsuite/tests/backpack/cabal/T16219/all.T - testsuite/tests/backpack/cabal/T20509/Makefile - testsuite/tests/backpack/cabal/T20509/all.T - testsuite/tests/backpack/cabal/bkpcabal01/Makefile - testsuite/tests/backpack/cabal/bkpcabal01/all.T - testsuite/tests/backpack/cabal/bkpcabal02/Makefile - testsuite/tests/backpack/cabal/bkpcabal02/all.T - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/cabal/bkpcabal03/Makefile - testsuite/tests/backpack/cabal/bkpcabal03/all.T - testsuite/tests/backpack/cabal/bkpcabal04/Makefile - testsuite/tests/backpack/cabal/bkpcabal04/all.T - testsuite/tests/backpack/cabal/bkpcabal05/Makefile - testsuite/tests/backpack/cabal/bkpcabal05/all.T - testsuite/tests/backpack/cabal/bkpcabal06/Makefile - testsuite/tests/backpack/cabal/bkpcabal06/all.T - testsuite/tests/backpack/cabal/bkpcabal07/Makefile - testsuite/tests/backpack/cabal/bkpcabal08/Makefile - testsuite/tests/backpack/cabal/bkpcabal08/all.T - testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/all.T - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp16.bkp - testsuite/tests/backpack/should_compile/bkp16.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/all.T - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail11.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail16.bkp - testsuite/tests/backpack/should_fail/bkpfail16.stderr - testsuite/tests/backpack/should_fail/bkpfail17.stderr - testsuite/tests/backpack/should_fail/bkpfail18.stderr - testsuite/tests/backpack/should_fail/bkpfail19.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail24.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail43.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail49.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail51.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - + testsuite/tests/backpack/should_run/T15379-DataToTag.bkp - + testsuite/tests/backpack/should_run/T15379-DataToTag.stderr - testsuite/tests/backpack/should_run/all.T - testsuite/tests/backpack/should_run/bkprun05.stderr - + testsuite/tests/bytecode/T24634/Hello.hs - + testsuite/tests/bytecode/T24634/Main.hs - + testsuite/tests/bytecode/T24634/Makefile - + testsuite/tests/bytecode/T24634/T24634a.stdout - + testsuite/tests/bytecode/T24634/T24634b.stdout - + testsuite/tests/bytecode/T24634/all.T - + testsuite/tests/bytecode/T24634/hello_c.c - + testsuite/tests/bytecode/T24634/hello_c.h - + testsuite/tests/bytecode/T25090/A.hs - + testsuite/tests/bytecode/T25090/B.hs - + testsuite/tests/bytecode/T25090/C.hs - + testsuite/tests/bytecode/T25090/C.hs-boot - + testsuite/tests/bytecode/T25090/D.hs - + testsuite/tests/bytecode/T25090/Makefile - + testsuite/tests/bytecode/T25090/T25090-debug.stderr - + testsuite/tests/bytecode/T25090/T25090.stdout - + testsuite/tests/bytecode/T25090/all.T - + testsuite/tests/bytecode/T25510/Makefile - + testsuite/tests/bytecode/T25510/T25510A.hs - + testsuite/tests/bytecode/T25510/T25510B.hs - + testsuite/tests/bytecode/T25510/all.T - testsuite/tests/cabal/T12733/Makefile - testsuite/tests/cabal/T12733/all.T - testsuite/tests/cabal/all.T - testsuite/tests/cabal/cabal03/Makefile - testsuite/tests/cabal/cabal03/all.T - testsuite/tests/cabal/cabal04/Makefile - testsuite/tests/cabal/cabal05/Makefile - testsuite/tests/cabal/cabal05/all.T - testsuite/tests/cabal/cabal06/Makefile - testsuite/tests/cabal/cabal06/all.T - testsuite/tests/cabal/cabal08/Makefile - testsuite/tests/cabal/cabal08/all.T - testsuite/tests/cabal/cabal09/Makefile - testsuite/tests/cabal/cabal09/all.T - testsuite/tests/cabal/cabal10/Makefile - testsuite/tests/cabal/cabal10/all.T - + testsuite/tests/cabal/fileStatus.hs - + testsuite/tests/cabal/fileStatus.stdout - testsuite/tests/cabal/ghcpkg03.stderr - testsuite/tests/cabal/ghcpkg03.stderr-mingw32 - testsuite/tests/cabal/ghcpkg05.stderr - testsuite/tests/cabal/ghcpkg05.stderr-mingw32 - testsuite/tests/cabal/sigcabal01/Makefile - testsuite/tests/cabal/sigcabal01/all.T - testsuite/tests/cabal/t18567/Makefile - testsuite/tests/cabal/t18567/all.T - testsuite/tests/cabal/t19518/Makefile - testsuite/tests/cabal/t19518/all.T - testsuite/tests/cabal/t20242/Makefile - testsuite/tests/cabal/t20242/all.T - testsuite/tests/cabal/t22333/Makefile - + testsuite/tests/cmm/opt/T24556.cmm - testsuite/tests/cmm/opt/all.T - testsuite/tests/cmm/should_compile/T20725.hs - + testsuite/tests/cmm/should_compile/T24224.cmm - + testsuite/tests/cmm/should_compile/T24224.stderr - + testsuite/tests/cmm/should_compile/T24474-cmm-gets-c-opts.cmm - + testsuite/tests/cmm/should_compile/T24474-cmm-opt-order.cmm - + testsuite/tests/cmm/should_compile/T24474.cmm - testsuite/tests/cmm/should_compile/all.T - + testsuite/tests/cmm/should_fail/T24474-cmm-override-g0.cmm - + testsuite/tests/cmm/should_fail/T24474-cmm-override-g0.stderr - + testsuite/tests/cmm/should_fail/all.T - testsuite/tests/cmm/should_run/HooplPostorder.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - + testsuite/tests/codeGen/should_compile/T16351.hs - + testsuite/tests/codeGen/should_compile/T16351.stderr - testsuite/tests/codeGen/should_compile/T21710a.stderr - + testsuite/tests/codeGen/should_compile/T24264.hs - + testsuite/tests/codeGen/should_compile/T24264.stderr - + testsuite/tests/codeGen/should_compile/T25166.hs - + testsuite/tests/codeGen/should_compile/T25166.stdout - + testsuite/tests/codeGen/should_compile/T25177.hs - + testsuite/tests/codeGen/should_compile/T25177.stderr - testsuite/tests/codeGen/should_compile/all.T - + testsuite/tests/codeGen/should_compile/callee-no-local.hs - + testsuite/tests/codeGen/should_compile/callee-no-local.stderr - testsuite/tests/codeGen/should_compile/cg006.hs - + testsuite/tests/codeGen/should_gen_asm/T24941.hs - testsuite/tests/codeGen/should_gen_asm/all.T - + testsuite/tests/codeGen/should_run/CCallConv.hs - + testsuite/tests/codeGen/should_run/CCallConv.stdout - + testsuite/tests/codeGen/should_run/CCallConv_c.c - + testsuite/tests/codeGen/should_run/CtzClz0.hs - testsuite/tests/codeGen/should_run/T16846.stderr - testsuite/tests/codeGen/should_run/T17920.cmm - + testsuite/tests/codeGen/should_run/T23034.h - + testsuite/tests/codeGen/should_run/T23034.hs - + testsuite/tests/codeGen/should_run/T23034.stdout - + testsuite/tests/codeGen/should_run/T23034_c.c - testsuite/tests/codeGen/should_run/T23146/all.T - + testsuite/tests/codeGen/should_run/T24264run.hs - + testsuite/tests/codeGen/should_run/T24295a.hs - + testsuite/tests/codeGen/should_run/T24295a.stdout - + testsuite/tests/codeGen/should_run/T24295b.hs - + testsuite/tests/codeGen/should_run/T24507.hs - + testsuite/tests/codeGen/should_run/T24507.stdout - + testsuite/tests/codeGen/should_run/T24507_cmm.cmm - + testsuite/tests/codeGen/should_run/T24664a.hs - + testsuite/tests/codeGen/should_run/T24664a.stdout - + testsuite/tests/codeGen/should_run/T24664b.hs - + testsuite/tests/codeGen/should_run/T24664b.stdout - + testsuite/tests/codeGen/should_run/T24700.hs - + testsuite/tests/codeGen/should_run/T24700.stdin - + testsuite/tests/codeGen/should_run/T24700.stdout - + testsuite/tests/codeGen/should_run/T24809.hs - + testsuite/tests/codeGen/should_run/T24809.stdout - + testsuite/tests/codeGen/should_run/T24893.hs - + testsuite/tests/codeGen/should_run/T24893.stdout - + testsuite/tests/codeGen/should_run/T25364.hs - + testsuite/tests/codeGen/should_run/T25364.stdout - + testsuite/tests/codeGen/should_run/T25374/T25374.hs - + testsuite/tests/codeGen/should_run/T25374/T25374.script - + testsuite/tests/codeGen/should_run/T25374/T25374A.hs - + testsuite/tests/codeGen/should_run/T25374/all.T - testsuite/tests/codeGen/should_run/T5626.stderr - testsuite/tests/codeGen/should_run/T7319.stderr - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/codeGen/should_run/cgrun016.stderr - testsuite/tests/codeGen/should_run/cgrun025.stderr - testsuite/tests/codeGen/should_run/cgrun045.stderr - testsuite/tests/codeGen/should_run/cgrun051.stderr - testsuite/tests/codeGen/should_run/cgrun057.stderr - testsuite/tests/codeGen/should_run/cgrun059.stderr - testsuite/tests/concurrent/should_run/T13330.stderr - + testsuite/tests/concurrent/should_run/T21969.hs - + testsuite/tests/concurrent/should_run/T21969.stdout - testsuite/tests/concurrent/should_run/T3279.hs - testsuite/tests/concurrent/should_run/T4030.stderr - testsuite/tests/concurrent/should_run/T5611.hs - testsuite/tests/concurrent/should_run/T5611.stderr - testsuite/tests/concurrent/should_run/T5611a.hs - testsuite/tests/concurrent/should_run/T5611a.stderr - testsuite/tests/concurrent/should_run/T5866.stderr - testsuite/tests/concurrent/should_run/all.T - testsuite/tests/concurrent/should_run/allocLimit1.stderr - testsuite/tests/concurrent/should_run/allocLimit3.stderr - testsuite/tests/concurrent/should_run/async001.hs - testsuite/tests/concurrent/should_run/conc009.stderr - testsuite/tests/concurrent/should_run/conc020.stderr - testsuite/tests/concurrent/should_run/conc021.stderr - testsuite/tests/concurrent/should_run/conc024.hs - testsuite/tests/concurrent/should_run/conc031.stderr - testsuite/tests/concurrent/should_run/conc036.hs - testsuite/tests/concurrent/should_run/conc037.hs - testsuite/tests/concurrent/should_run/conc038.hs - testsuite/tests/concurrent/should_run/conc040.stderr - testsuite/tests/concurrent/should_run/conc058.stderr - testsuite/tests/concurrent/should_run/conc064.stderr - testsuite/tests/concurrent/should_run/conc068.stderr - testsuite/tests/concurrent/should_run/foreignInterruptible.hs - testsuite/tests/concurrent/should_run/hs_try_putmvar001_c.c - testsuite/tests/concurrent/should_run/hs_try_putmvar002_c.c - + testsuite/tests/core-to-stg/T14895.hs - + testsuite/tests/core-to-stg/T14895.stderr - + testsuite/tests/core-to-stg/T23270.hs - + testsuite/tests/core-to-stg/T23270.stderr - + testsuite/tests/core-to-stg/T23914.hs - + testsuite/tests/core-to-stg/T24124.hs - + testsuite/tests/core-to-stg/T24124.stderr - + testsuite/tests/core-to-stg/T24334.hs - testsuite/tests/stranal/should_run/T22475b.stdout → testsuite/tests/core-to-stg/T24334.stdout - + testsuite/tests/core-to-stg/T24463.hs - + testsuite/tests/core-to-stg/T25284/A.hs - + testsuite/tests/core-to-stg/T25284/B.hs - + testsuite/tests/core-to-stg/T25284/Cls.hs - + testsuite/tests/core-to-stg/T25284/Main.hs - + testsuite/tests/core-to-stg/T25284/T25284.stdout - + testsuite/tests/core-to-stg/T25284/all.T - testsuite/tests/core-to-stg/all.T - testsuite/tests/corelint/T21115b.stderr - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/count-deps/Makefile - testsuite/tests/count-deps/all.T - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/cpranal/should_compile/T18401.stderr - + testsuite/tests/cpranal/should_compile/T23862.hs - + testsuite/tests/cpranal/should_compile/T23862.stderr - testsuite/tests/cpranal/should_compile/all.T - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T13870.hs - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - + testsuite/tests/deSugar/should_compile/T23550.hs - testsuite/tests/deSugar/should_compile/T2431.stderr - + testsuite/tests/deSugar/should_compile/T24489.hs - testsuite/tests/deSugar/should_compile/T3263-2.hs - testsuite/tests/deSugar/should_compile/all.T - testsuite/tests/deSugar/should_fail/DsStrictFail.stderr - testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr - testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr - + testsuite/tests/deSugar/should_run/Or5.hs - + testsuite/tests/deSugar/should_run/Or5.stderr - + testsuite/tests/deSugar/should_run/Or5.stdout - testsuite/tests/deSugar/should_run/T11193.stderr - testsuite/tests/deSugar/should_run/T11572.stderr - testsuite/tests/deSugar/should_run/T11601.stderr - testsuite/tests/deSugar/should_run/T20024.stderr - testsuite/tests/deSugar/should_run/all.T - testsuite/tests/deSugar/should_run/dsrun005.stderr - testsuite/tests/deSugar/should_run/dsrun007.stderr - testsuite/tests/deSugar/should_run/dsrun008.stderr - + testsuite/tests/default/DefaultImport01.hs - + testsuite/tests/default/DefaultImport01.stdout - + testsuite/tests/default/DefaultImport02.hs - + testsuite/tests/default/DefaultImport02.stdout - + testsuite/tests/default/DefaultImport03.hs - + testsuite/tests/default/DefaultImport03.stdout - + testsuite/tests/default/DefaultImport05.hs - + testsuite/tests/default/DefaultImport05.stdout - + testsuite/tests/default/DefaultImport06.hs - + testsuite/tests/default/DefaultImport06.stderr - + testsuite/tests/default/DefaultImport06.stdout - + testsuite/tests/default/DefaultImport07.hs - + testsuite/tests/default/DefaultImport07.stderr - + testsuite/tests/default/DefaultImport08.hs - + testsuite/tests/default/DefaultImport08.stderr - + testsuite/tests/default/DefaultImportFail01.hs - + testsuite/tests/default/DefaultImportFail01.stderr - + testsuite/tests/default/DefaultImportFail02.hs - + testsuite/tests/default/DefaultImportFail02.stderr - + testsuite/tests/default/DefaultImportFail03.hs - + testsuite/tests/default/DefaultImportFail03.stderr - + testsuite/tests/default/DefaultImportFail04.hs - + testsuite/tests/default/DefaultImportFail04.stderr - + testsuite/tests/default/DefaultImportFail05.hs - + testsuite/tests/default/DefaultImportFail05.stderr - + testsuite/tests/default/DefaultImportFail06.hs - + testsuite/tests/default/DefaultImportFail06.stderr - + testsuite/tests/default/DefaultImportFail07.hs - + testsuite/tests/default/DefaultImportFail07.stderr - + testsuite/tests/default/ExportBitsInt.hs - + testsuite/tests/default/ExportImplicitMonoidProduct.hs - + testsuite/tests/default/ExportMonoidProduct.hs - + testsuite/tests/default/ExportMonoidSum.hs - + testsuite/tests/default/ExportShowSum.hs - + testsuite/tests/default/ExportWarn.hs - + testsuite/tests/default/NonExportMonoidSum.hs - + testsuite/tests/default/ReExportMonoidSum.hs - + testsuite/tests/default/ReExportShowSumModule.hs - + testsuite/tests/default/T25206.hs - + testsuite/tests/default/T25206.stderr - + testsuite/tests/default/T25206_helper.hs - + testsuite/tests/default/UnExportMonoidSum.hs - + testsuite/tests/default/all.T - + testsuite/tests/default/default-fail01.hs - + testsuite/tests/default/default-fail01.stderr - + testsuite/tests/default/default-fail02.hs - + testsuite/tests/default/default-fail02.stderr - + testsuite/tests/default/default-fail03.hs - + testsuite/tests/default/default-fail03.stderr - + testsuite/tests/default/default-fail04.hs - + testsuite/tests/default/default-fail04.stderr - + testsuite/tests/default/default-fail05.hs - + testsuite/tests/default/default-fail05.stderr - + testsuite/tests/default/default-fail06.hs - + testsuite/tests/default/default-fail06.stderr - + testsuite/tests/default/default-fail07.hs - + testsuite/tests/default/default-fail07.stderr - + testsuite/tests/default/default-fail08.hs - + testsuite/tests/default/default-fail08.stderr - + testsuite/tests/default/default01.hs - + testsuite/tests/default/default01.stdout - + testsuite/tests/default/default02.hs - + testsuite/tests/default/default02.stdout - + testsuite/tests/default/default03.hs - testsuite/tests/stranal/should_run/T9254.stdout → testsuite/tests/default/default03.stdout - + testsuite/tests/default/default04.hs - + testsuite/tests/default/default04.stdout - + testsuite/tests/default/default05.hs - + testsuite/tests/default/default05.stdout - + testsuite/tests/default/default06.hs - + testsuite/tests/default/default06.stdout - + testsuite/tests/default/default07.hs - + testsuite/tests/default/default07.stdout - + testsuite/tests/default/default08.hs - + testsuite/tests/default/default08.stdout - + testsuite/tests/default/default10.hs - + testsuite/tests/default/default10.stdout - + testsuite/tests/default/default11.hs - + testsuite/tests/default/default11.stdout - testsuite/tests/dependent/ghci/T11549.stdout - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_compile/T14729.stderr - testsuite/tests/dependent/should_compile/T15743.stderr - testsuite/tests/dependent/should_compile/T15743e.stderr - testsuite/tests/dependent/should_compile/T16391a.hs - + testsuite/tests/dependent/should_compile/T25387.hs - testsuite/tests/dependent/should_compile/all.T - testsuite/tests/dependent/should_fail/BadTelescope4.stderr - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14066g.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/T15215.stderr - testsuite/tests/dependent/should_fail/T15591b.stderr - testsuite/tests/dependent/should_fail/T15591c.stderr - testsuite/tests/dependent/should_fail/T15743c.stderr - testsuite/tests/dependent/should_fail/T15743d.stderr - testsuite/tests/dependent/should_fail/T15859.stderr - testsuite/tests/dependent/should_fail/T16326_Fail1.stderr - testsuite/tests/dependent/should_fail/T16326_Fail10.stderr - testsuite/tests/dependent/should_fail/T16326_Fail11.stderr - testsuite/tests/dependent/should_fail/T16326_Fail12.stderr - testsuite/tests/dependent/should_fail/T16326_Fail2.stderr - testsuite/tests/dependent/should_fail/T16326_Fail3.stderr - testsuite/tests/dependent/should_fail/T16326_Fail4.stderr - testsuite/tests/dependent/should_fail/T16326_Fail5.stderr - testsuite/tests/dependent/should_fail/T16326_Fail6.stderr - testsuite/tests/dependent/should_fail/T16326_Fail7.stderr - testsuite/tests/dependent/should_fail/T16326_Fail8.stderr - testsuite/tests/dependent/should_fail/T16326_Fail9.stderr - testsuite/tests/dependent/should_fail/T17687.stderr - testsuite/tests/dependent/should_fail/T18271.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/rename/should_compile/T15798a.hs → testsuite/tests/deriving/should_compile/T15798a.hs - + testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/rename/should_compile/T15798b.hs → testsuite/tests/deriving/should_compile/T15798b.hs - + testsuite/tests/deriving/should_compile/T15798b.stderr - testsuite/tests/rename/should_compile/T15798c.hs → testsuite/tests/deriving/should_compile/T15798c.hs - + testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T16179.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - + testsuite/tests/deriving/should_compile/T20815.hs - + testsuite/tests/deriving/should_compile/T24955a.hs - + testsuite/tests/deriving/should_compile/T24955a.stderr - + testsuite/tests/deriving/should_compile/T24955b.hs - + testsuite/tests/deriving/should_compile/T24955b.stderr - + testsuite/tests/deriving/should_compile/T24955c.hs - + testsuite/tests/deriving/should_compile/T24955c.stderr - + testsuite/tests/deriving/should_compile/T25148c.hs - testsuite/tests/deriving/should_fail/T8851.hs → testsuite/tests/deriving/should_compile/T8851.hs - testsuite/tests/deriving/should_compile/all.T - + testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.hs - + testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - + testsuite/tests/deriving/should_compile/drv023.hs - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10598_fail4.stderr - testsuite/tests/deriving/should_fail/T10598_fail5.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T1133A.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12512.stderr - + testsuite/tests/deriving/should_fail/T12768.hs - + testsuite/tests/deriving/should_fail/T12768.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T1496.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - + testsuite/tests/deriving/should_fail/T20815a.hs - + testsuite/tests/deriving/should_fail/T20815a.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T3833.stderr - testsuite/tests/deriving/should_fail/T3834.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5498.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7148.stderr - testsuite/tests/deriving/should_fail/T7148a.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T8165_fail2.stderr - − testsuite/tests/deriving/should_fail/T8851.stderr - testsuite/tests/deriving/should_fail/T8984.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/T9600.stderr - testsuite/tests/deriving/should_fail/all.T - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail3.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail006.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail008.stderr - testsuite/tests/deriving/should_fail/drvfail009.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail015.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/deriving/should_run/T20371.stdout - testsuite/tests/deriving/should_run/T9576.stderr - + testsuite/tests/determinism/T25304/A.hs - + testsuite/tests/determinism/T25304/B.hs - + testsuite/tests/determinism/T25304/Makefile - + testsuite/tests/determinism/T25304/T25304a.stdout - + testsuite/tests/determinism/T25304/all.T - testsuite/tests/determinism/determ021/all.T - + testsuite/tests/determinism/object/cabal.project - + testsuite/tests/determinism/object/check-standalone.sh - + testsuite/tests/determinism/object/check.sh - + testsuite/tests/diagnostic-codes/Makefile - + testsuite/tests/diagnostic-codes/all.T - + testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/stranal/Makefile → testsuite/tests/dmdanal/Makefile - testsuite/tests/stranal/T10482a.hs → testsuite/tests/dmdanal/T10482a.hs - testsuite/tests/stranal/should_compile/EtaExpansion.hs → testsuite/tests/dmdanal/should_compile/EtaExpansion.hs - testsuite/tests/stranal/should_compile/Makefile → testsuite/tests/dmdanal/should_compile/Makefile - testsuite/tests/stranal/should_compile/T10069.hs → testsuite/tests/dmdanal/should_compile/T10069.hs - + testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/stranal/should_compile/T10482.hs → testsuite/tests/dmdanal/should_compile/T10482.hs - + testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/stranal/should_compile/T10482a.hs → testsuite/tests/dmdanal/should_compile/T10482a.hs - + testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/stranal/should_compile/T10694.hs → testsuite/tests/dmdanal/should_compile/T10694.hs - testsuite/tests/stranal/should_compile/T10694.stderr → testsuite/tests/dmdanal/should_compile/T10694.stderr - testsuite/tests/stranal/should_compile/T11770.hs → testsuite/tests/dmdanal/should_compile/T11770.hs - testsuite/tests/stranal/should_compile/T11770.stderr → testsuite/tests/dmdanal/should_compile/T11770.stderr - testsuite/tests/stranal/should_compile/T13031.hs → testsuite/tests/dmdanal/should_compile/T13031.hs - testsuite/tests/stranal/should_compile/T13031.stdout → testsuite/tests/dmdanal/should_compile/T13031.stdout - testsuite/tests/stranal/should_compile/T13077.hs → testsuite/tests/dmdanal/should_compile/T13077.hs - testsuite/tests/stranal/should_compile/T13077a.hs → testsuite/tests/dmdanal/should_compile/T13077a.hs - testsuite/tests/stranal/should_compile/T13143.hs → testsuite/tests/dmdanal/should_compile/T13143.hs - + testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/stranal/should_compile/T13380b.hs → testsuite/tests/dmdanal/should_compile/T13380b.hs - testsuite/tests/stranal/should_compile/T15627.hs → testsuite/tests/dmdanal/should_compile/T15627.hs - testsuite/tests/stranal/should_compile/T15627.stderr → testsuite/tests/dmdanal/should_compile/T15627.stderr - testsuite/tests/stranal/should_compile/T16029.hs → testsuite/tests/dmdanal/should_compile/T16029.hs - + testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/stranal/should_compile/T17819.hs → testsuite/tests/dmdanal/should_compile/T17819.hs - testsuite/tests/stranal/should_compile/T17819.stderr → testsuite/tests/dmdanal/should_compile/T17819.stderr - testsuite/tests/stranal/should_compile/T17852.hs → testsuite/tests/dmdanal/should_compile/T17852.hs - testsuite/tests/stranal/should_compile/T17852.stdout → testsuite/tests/dmdanal/should_compile/T17852.stdout - testsuite/tests/stranal/should_compile/T18122.hs → testsuite/tests/dmdanal/should_compile/T18122.hs - testsuite/tests/stranal/should_compile/T18122.stderr → testsuite/tests/dmdanal/should_compile/T18122.stderr - testsuite/tests/stranal/should_compile/T18894.hs → testsuite/tests/dmdanal/should_compile/T18894.hs - testsuite/tests/stranal/should_compile/T18894.stderr → testsuite/tests/dmdanal/should_compile/T18894.stderr - testsuite/tests/stranal/should_compile/T18894b.hs → testsuite/tests/dmdanal/should_compile/T18894b.hs - testsuite/tests/stranal/should_compile/T18894b.stderr → testsuite/tests/dmdanal/should_compile/T18894b.stderr - testsuite/tests/stranal/should_compile/T18903.hs → testsuite/tests/dmdanal/should_compile/T18903.hs - testsuite/tests/stranal/should_compile/T18903.stderr → testsuite/tests/dmdanal/should_compile/T18903.stderr - testsuite/tests/stranal/should_compile/T18982.hs → testsuite/tests/dmdanal/should_compile/T18982.hs - + testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/stranal/should_compile/T19180.hs → testsuite/tests/dmdanal/should_compile/T19180.hs - testsuite/tests/stranal/should_compile/T19766.hs → testsuite/tests/dmdanal/should_compile/T19766.hs - testsuite/tests/stranal/should_compile/T19849.hs → testsuite/tests/dmdanal/should_compile/T19849.hs - testsuite/tests/stranal/should_compile/T1988.hs → testsuite/tests/dmdanal/should_compile/T1988.hs - testsuite/tests/stranal/should_compile/T19882a.hs → testsuite/tests/dmdanal/should_compile/T19882a.hs - testsuite/tests/stranal/should_compile/T19882b.hs → testsuite/tests/dmdanal/should_compile/T19882b.hs - testsuite/tests/stranal/should_compile/T20510.hs → testsuite/tests/dmdanal/should_compile/T20510.hs - + testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/stranal/should_compile/T20663.hs → testsuite/tests/dmdanal/should_compile/T20663.hs - + testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/stranal/should_compile/T20817.hs → testsuite/tests/dmdanal/should_compile/T20817.hs - testsuite/tests/stranal/should_compile/T20817.stderr → testsuite/tests/dmdanal/should_compile/T20817.stderr - testsuite/tests/stranal/should_compile/T21128.hs → testsuite/tests/dmdanal/should_compile/T21128.hs - + testsuite/tests/dmdanal/should_compile/T21128.stderr - testsuite/tests/stranal/should_compile/T21128a.hs → testsuite/tests/dmdanal/should_compile/T21128a.hs - testsuite/tests/stranal/should_compile/T21150.hs → testsuite/tests/dmdanal/should_compile/T21150.hs - testsuite/tests/stranal/should_compile/T21150.stderr → testsuite/tests/dmdanal/should_compile/T21150.stderr - testsuite/tests/stranal/should_compile/T21265.hs → testsuite/tests/dmdanal/should_compile/T21265.hs - testsuite/tests/stranal/should_compile/T22039.hs → testsuite/tests/dmdanal/should_compile/T22039.hs - testsuite/tests/stranal/should_compile/T22388.hs → testsuite/tests/dmdanal/should_compile/T22388.hs - testsuite/tests/stranal/should_compile/T22388.stderr → testsuite/tests/dmdanal/should_compile/T22388.stderr - testsuite/tests/stranal/should_compile/T22997.hs → testsuite/tests/dmdanal/should_compile/T22997.hs - testsuite/tests/stranal/should_compile/T23398.hs → testsuite/tests/dmdanal/should_compile/T23398.hs - testsuite/tests/stranal/should_compile/T23398.stderr → testsuite/tests/dmdanal/should_compile/T23398.stderr - + testsuite/tests/dmdanal/should_compile/T24623.hs - + testsuite/tests/dmdanal/should_compile/T25196.hs - + testsuite/tests/dmdanal/should_compile/T25196_aux.hs - testsuite/tests/stranal/should_compile/T8037.hs → testsuite/tests/dmdanal/should_compile/T8037.hs - testsuite/tests/stranal/should_compile/T8467.hs → testsuite/tests/dmdanal/should_compile/T8467.hs - testsuite/tests/stranal/should_compile/T8743.hs → testsuite/tests/dmdanal/should_compile/T8743.hs - testsuite/tests/stranal/should_compile/T8743.hs-boot → testsuite/tests/dmdanal/should_compile/T8743.hs-boot - testsuite/tests/stranal/should_compile/T8743a.hs → testsuite/tests/dmdanal/should_compile/T8743a.hs - testsuite/tests/stranal/should_compile/T9208.hs → testsuite/tests/dmdanal/should_compile/T9208.hs - + testsuite/tests/dmdanal/should_compile/all.T - testsuite/tests/stranal/should_compile/default.hs → testsuite/tests/dmdanal/should_compile/default.hs - testsuite/tests/stranal/should_compile/fact.hs → testsuite/tests/dmdanal/should_compile/fact.hs - testsuite/tests/stranal/should_compile/fun.hs → testsuite/tests/dmdanal/should_compile/fun.hs - testsuite/tests/stranal/should_compile/goo.hs → testsuite/tests/dmdanal/should_compile/goo.hs - testsuite/tests/stranal/should_compile/ins.hs → testsuite/tests/dmdanal/should_compile/ins.hs - testsuite/tests/stranal/should_compile/map.hs → testsuite/tests/dmdanal/should_compile/map.hs - testsuite/tests/stranal/should_compile/newtype.hs → testsuite/tests/dmdanal/should_compile/newtype.hs - testsuite/tests/stranal/should_compile/sim.hs → testsuite/tests/dmdanal/should_compile/sim.hs - testsuite/tests/stranal/should_compile/str001.hs → testsuite/tests/dmdanal/should_compile/str001.hs - testsuite/tests/stranal/should_compile/str001.stderr → testsuite/tests/dmdanal/should_compile/str001.stderr - testsuite/tests/stranal/should_compile/str002.hs → testsuite/tests/dmdanal/should_compile/str002.hs - testsuite/tests/stranal/should_compile/syn.hs → testsuite/tests/dmdanal/should_compile/syn.hs - testsuite/tests/stranal/should_compile/test.hs → testsuite/tests/dmdanal/should_compile/test.hs - testsuite/tests/stranal/should_compile/tst.hs → testsuite/tests/dmdanal/should_compile/tst.hs - testsuite/tests/stranal/should_compile/unu.hs → testsuite/tests/dmdanal/should_compile/unu.hs - testsuite/tests/stranal/should_run/.gitignore → testsuite/tests/dmdanal/should_run/.gitignore - testsuite/tests/stranal/should_run/Makefile → testsuite/tests/dmdanal/should_run/Makefile - testsuite/tests/stranal/should_run/T10148.hs → testsuite/tests/dmdanal/should_run/T10148.hs - testsuite/tests/stranal/should_run/T10148.stderr → testsuite/tests/dmdanal/should_run/T10148.stderr - testsuite/tests/stranal/should_run/T10218.hs → testsuite/tests/dmdanal/should_run/T10218.hs - testsuite/tests/stranal/should_run/T10218.stdout → testsuite/tests/dmdanal/should_run/T10218.stdout - testsuite/tests/stranal/should_run/T11076.hs → testsuite/tests/dmdanal/should_run/T11076.hs - testsuite/tests/stranal/should_run/T11076.stdout → testsuite/tests/dmdanal/should_run/T11076.stdout - testsuite/tests/stranal/should_run/T11076A.hs → testsuite/tests/dmdanal/should_run/T11076A.hs - testsuite/tests/stranal/should_run/T11076_prim.cmm → testsuite/tests/dmdanal/should_run/T11076_prim.cmm - testsuite/tests/stranal/should_run/T11555a.hs → testsuite/tests/dmdanal/should_run/T11555a.hs - testsuite/tests/stranal/should_run/T11555a.stdout → testsuite/tests/dmdanal/should_run/T11555a.stdout - testsuite/tests/stranal/should_run/T12368.hs → testsuite/tests/dmdanal/should_run/T12368.hs - + testsuite/tests/dmdanal/should_run/T12368.stderr - testsuite/tests/stranal/should_run/T12368a.hs → testsuite/tests/dmdanal/should_run/T12368a.hs - + testsuite/tests/dmdanal/should_run/T12368a.stderr - testsuite/tests/stranal/should_run/T13380.hs → testsuite/tests/dmdanal/should_run/T13380.hs - + testsuite/tests/dmdanal/should_run/T13380.stderr - testsuite/tests/stranal/should_run/T13380d.hs → testsuite/tests/dmdanal/should_run/T13380d.hs - + testsuite/tests/dmdanal/should_run/T13380d.stderr - testsuite/tests/stranal/should_run/T13380e.hs → testsuite/tests/dmdanal/should_run/T13380e.hs - + testsuite/tests/dmdanal/should_run/T13380e.stderr - testsuite/tests/stranal/should_run/T14171.hs → testsuite/tests/dmdanal/should_run/T14171.hs - testsuite/tests/stranal/should_run/T14285.hs → testsuite/tests/dmdanal/should_run/T14285.hs - testsuite/tests/stranal/should_run/T22549.stdout → testsuite/tests/dmdanal/should_run/T14285.stdout - testsuite/tests/stranal/should_run/T14285a.hs → testsuite/tests/dmdanal/should_run/T14285a.hs - testsuite/tests/stranal/should_run/T14290.hs → testsuite/tests/dmdanal/should_run/T14290.hs - testsuite/tests/stranal/should_run/T16197.hs → testsuite/tests/dmdanal/should_run/T16197.hs - testsuite/tests/stranal/should_run/T16197.stdout → testsuite/tests/dmdanal/should_run/T16197.stdout - testsuite/tests/stranal/should_run/T17676.hs → testsuite/tests/dmdanal/should_run/T17676.hs - testsuite/tests/stranal/should_run/T19053.hs → testsuite/tests/dmdanal/should_run/T19053.hs - testsuite/tests/stranal/should_run/T21717b.hs → testsuite/tests/dmdanal/should_run/T21717b.hs - testsuite/tests/stranal/should_run/T21717b.stdout → testsuite/tests/dmdanal/should_run/T21717b.stdout - testsuite/tests/stranal/should_run/T22475.hs → testsuite/tests/dmdanal/should_run/T22475.hs - testsuite/tests/stranal/should_run/T22475b.hs → testsuite/tests/dmdanal/should_run/T22475b.hs - + testsuite/tests/dmdanal/should_run/T22475b.stdout - testsuite/tests/stranal/should_run/T22549.hs → testsuite/tests/dmdanal/should_run/T22549.hs - testsuite/tests/stranal/should_run/T8425/T8425.stdout → testsuite/tests/dmdanal/should_run/T22549.stdout - testsuite/tests/stranal/should_run/T23208.hs → testsuite/tests/dmdanal/should_run/T23208.hs - + testsuite/tests/dmdanal/should_run/T23208.stderr - testsuite/tests/stranal/should_run/T23208_Lib.hs → testsuite/tests/dmdanal/should_run/T23208_Lib.hs - + testsuite/tests/dmdanal/should_run/T25439.hs - + testsuite/tests/dmdanal/should_run/T25439.stdout - testsuite/tests/stranal/should_run/T2756b.hs → testsuite/tests/dmdanal/should_run/T2756b.hs - testsuite/tests/stranal/should_run/T7649.hs → testsuite/tests/dmdanal/should_run/T7649.hs - testsuite/tests/stranal/should_run/T7649.stdout → testsuite/tests/dmdanal/should_run/T7649.stdout - testsuite/tests/stranal/should_run/T8425/Arr.hs → testsuite/tests/dmdanal/should_run/T8425/Arr.hs - testsuite/tests/stranal/should_run/T8425/Base.hs → testsuite/tests/dmdanal/should_run/T8425/Base.hs - testsuite/tests/stranal/should_run/T8425/BuggyOpt.hs → testsuite/tests/dmdanal/should_run/T8425/BuggyOpt.hs - testsuite/tests/stranal/should_run/T8425/Good.hs → testsuite/tests/dmdanal/should_run/T8425/Good.hs - testsuite/tests/stranal/should_run/T8425/M.hs → testsuite/tests/dmdanal/should_run/T8425/M.hs - testsuite/tests/stranal/should_run/T8425/Main.hs → testsuite/tests/dmdanal/should_run/T8425/Main.hs - testsuite/tests/stranal/should_run/T8425/Makefile → testsuite/tests/dmdanal/should_run/T8425/Makefile - + testsuite/tests/dmdanal/should_run/T8425/T8425.stdout - testsuite/tests/stranal/should_run/T8425/all.T → testsuite/tests/dmdanal/should_run/T8425/all.T - testsuite/tests/stranal/should_run/T9254.hs → testsuite/tests/dmdanal/should_run/T9254.hs - + testsuite/tests/dmdanal/should_run/T9254.stdout - + testsuite/tests/dmdanal/should_run/all.T - testsuite/tests/stranal/should_run/strun001.hs → testsuite/tests/dmdanal/should_run/strun001.hs - testsuite/tests/stranal/should_run/strun001.stdout → testsuite/tests/dmdanal/should_run/strun001.stdout - testsuite/tests/stranal/should_run/strun002.hs → testsuite/tests/dmdanal/should_run/strun002.hs - + testsuite/tests/dmdanal/should_run/strun002.stderr - testsuite/tests/stranal/should_run/strun003.hs → testsuite/tests/dmdanal/should_run/strun003.hs - testsuite/tests/stranal/should_run/strun003.stdout → testsuite/tests/dmdanal/should_run/strun003.stdout - testsuite/tests/stranal/should_run/strun004.hs → testsuite/tests/dmdanal/should_run/strun004.hs - testsuite/tests/stranal/should_run/strun004.stdout → testsuite/tests/dmdanal/should_run/strun004.stdout - testsuite/tests/stranal/sigs/BottomFromInnerLambda.hs → testsuite/tests/dmdanal/sigs/BottomFromInnerLambda.hs - testsuite/tests/stranal/sigs/BottomFromInnerLambda.stderr → testsuite/tests/dmdanal/sigs/BottomFromInnerLambda.stderr - testsuite/tests/stranal/sigs/DmdAnalGADTs.hs → testsuite/tests/dmdanal/sigs/DmdAnalGADTs.hs - testsuite/tests/stranal/sigs/DmdAnalGADTs.stderr → testsuite/tests/dmdanal/sigs/DmdAnalGADTs.stderr - testsuite/tests/stranal/sigs/FacState.hs → testsuite/tests/dmdanal/sigs/FacState.hs - + testsuite/tests/dmdanal/sigs/FacState.stderr - testsuite/tests/stranal/sigs/HyperStrUse.hs → testsuite/tests/dmdanal/sigs/HyperStrUse.hs - + testsuite/tests/dmdanal/sigs/HyperStrUse.stderr - testsuite/tests/stranal/sigs/Makefile → testsuite/tests/dmdanal/sigs/Makefile - testsuite/tests/stranal/sigs/NewtypeArity.hs → testsuite/tests/dmdanal/sigs/NewtypeArity.hs - + testsuite/tests/dmdanal/sigs/NewtypeArity.stderr - testsuite/tests/stranal/sigs/StrAnalExample.hs → testsuite/tests/dmdanal/sigs/StrAnalExample.hs - + testsuite/tests/dmdanal/sigs/StrAnalExample.stderr - testsuite/tests/stranal/sigs/T12370.hs → testsuite/tests/dmdanal/sigs/T12370.hs - + testsuite/tests/dmdanal/sigs/T12370.stderr - testsuite/tests/stranal/sigs/T13331.hs → testsuite/tests/dmdanal/sigs/T13331.hs - + testsuite/tests/dmdanal/sigs/T13331.stderr - testsuite/tests/stranal/sigs/T13380c.hs → testsuite/tests/dmdanal/sigs/T13380c.hs - + testsuite/tests/dmdanal/sigs/T13380c.stderr - testsuite/tests/stranal/sigs/T13380f.hs → testsuite/tests/dmdanal/sigs/T13380f.hs - testsuite/tests/stranal/sigs/T13380f.stderr → testsuite/tests/dmdanal/sigs/T13380f.stderr - testsuite/tests/stranal/sigs/T16197b.hs → testsuite/tests/dmdanal/sigs/T16197b.hs - testsuite/tests/stranal/sigs/T16197b.stderr → testsuite/tests/dmdanal/sigs/T16197b.stderr - testsuite/tests/stranal/sigs/T16859.hs → testsuite/tests/dmdanal/sigs/T16859.hs - testsuite/tests/stranal/sigs/T16859.stderr → testsuite/tests/dmdanal/sigs/T16859.stderr - testsuite/tests/stranal/sigs/T17932.hs → testsuite/tests/dmdanal/sigs/T17932.hs - + testsuite/tests/dmdanal/sigs/T17932.stderr - testsuite/tests/stranal/sigs/T18086.hs → testsuite/tests/dmdanal/sigs/T18086.hs - + testsuite/tests/dmdanal/sigs/T18086.stderr - testsuite/tests/stranal/sigs/T18907.hs → testsuite/tests/dmdanal/sigs/T18907.hs - testsuite/tests/stranal/sigs/T18907.stderr → testsuite/tests/dmdanal/sigs/T18907.stderr - testsuite/tests/stranal/sigs/T18957.hs → testsuite/tests/dmdanal/sigs/T18957.hs - testsuite/tests/stranal/sigs/T18957.stderr → testsuite/tests/dmdanal/sigs/T18957.stderr - testsuite/tests/stranal/sigs/T19407.hs → testsuite/tests/dmdanal/sigs/T19407.hs - testsuite/tests/stranal/sigs/T19407.stderr → testsuite/tests/dmdanal/sigs/T19407.stderr - testsuite/tests/stranal/sigs/T19871.hs → testsuite/tests/dmdanal/sigs/T19871.hs - testsuite/tests/stranal/sigs/T19871.stderr → testsuite/tests/dmdanal/sigs/T19871.stderr - testsuite/tests/stranal/sigs/T20746.hs → testsuite/tests/dmdanal/sigs/T20746.hs - + testsuite/tests/dmdanal/sigs/T20746.stderr - testsuite/tests/stranal/sigs/T20746b.hs → testsuite/tests/dmdanal/sigs/T20746b.hs - + testsuite/tests/dmdanal/sigs/T20746b.stderr - testsuite/tests/stranal/sigs/T21081.hs → testsuite/tests/dmdanal/sigs/T21081.hs - testsuite/tests/stranal/sigs/T21081.stderr → testsuite/tests/dmdanal/sigs/T21081.stderr - testsuite/tests/stranal/sigs/T21119.hs → testsuite/tests/dmdanal/sigs/T21119.hs - testsuite/tests/stranal/sigs/T21119.stderr → testsuite/tests/dmdanal/sigs/T21119.stderr - testsuite/tests/stranal/sigs/T21717.hs → testsuite/tests/dmdanal/sigs/T21717.hs - + testsuite/tests/dmdanal/sigs/T21717.stderr - testsuite/tests/stranal/sigs/T21737.hs → testsuite/tests/dmdanal/sigs/T21737.hs - testsuite/tests/stranal/sigs/T21737.stderr → testsuite/tests/dmdanal/sigs/T21737.stderr - testsuite/tests/stranal/sigs/T21754.hs → testsuite/tests/dmdanal/sigs/T21754.hs - + testsuite/tests/dmdanal/sigs/T21754.stderr - testsuite/tests/stranal/sigs/T21888.hs → testsuite/tests/dmdanal/sigs/T21888.hs - testsuite/tests/stranal/sigs/T21888.stderr → testsuite/tests/dmdanal/sigs/T21888.stderr - testsuite/tests/stranal/sigs/T21888a.hs → testsuite/tests/dmdanal/sigs/T21888a.hs - testsuite/tests/stranal/sigs/T21888a.stderr → testsuite/tests/dmdanal/sigs/T21888a.stderr - testsuite/tests/stranal/sigs/T22241.hs → testsuite/tests/dmdanal/sigs/T22241.hs - testsuite/tests/stranal/sigs/T22241.stderr → testsuite/tests/dmdanal/sigs/T22241.stderr - testsuite/tests/stranal/sigs/T5075.hs → testsuite/tests/dmdanal/sigs/T5075.hs - testsuite/tests/stranal/sigs/T5075.stderr → testsuite/tests/dmdanal/sigs/T5075.stderr - + testsuite/tests/dmdanal/sigs/T6070.hs - + testsuite/tests/dmdanal/sigs/T6070.stderr - testsuite/tests/stranal/sigs/T8569.hs → testsuite/tests/dmdanal/sigs/T8569.hs - + testsuite/tests/dmdanal/sigs/T8569.stderr - testsuite/tests/stranal/sigs/T8598.hs → testsuite/tests/dmdanal/sigs/T8598.hs - + testsuite/tests/dmdanal/sigs/T8598.stderr - testsuite/tests/stranal/sigs/UnsatFun.hs → testsuite/tests/dmdanal/sigs/UnsatFun.hs - testsuite/tests/stranal/sigs/UnsatFun.stderr → testsuite/tests/dmdanal/sigs/UnsatFun.stderr - + testsuite/tests/dmdanal/sigs/all.T - testsuite/tests/driver/Makefile - testsuite/tests/driver/MergeObjsMode/A.hs - testsuite/tests/driver/MergeObjsMode/B.hs - testsuite/tests/driver/MergeObjsMode/all.T - testsuite/tests/driver/T11381.stderr - testsuite/tests/driver/T13914/T13914.stdout - testsuite/tests/driver/T16167.stdout - testsuite/tests/driver/T16500/all.T - − testsuite/tests/driver/T16737.hs - − testsuite/tests/driver/T16737.stdout - − testsuite/tests/driver/T16737include/T16737.h - testsuite/tests/driver/T1959/test.T - − testsuite/tests/driver/T20316.stderr - testsuite/tests/driver/T20436/T20436.stderr - testsuite/tests/driver/T20459.stderr - testsuite/tests/driver/T20604/T20604.stdout - + testsuite/tests/driver/T20696/T20696-static.stderr-wasm32-unknown-wasi - + testsuite/tests/driver/T21097/Makefile - + testsuite/tests/driver/T21097/T21097.stderr - + testsuite/tests/driver/T21097/Test.hs - + testsuite/tests/driver/T21097/all.T - + testsuite/tests/driver/T21097/pkgdb/a.conf - + testsuite/tests/driver/T21097/pkgdb/b.conf - + testsuite/tests/driver/T21097/pkgdb/c.conf - + testsuite/tests/driver/T21097b/Makefile - + testsuite/tests/driver/T21097b/T21097b.stdout - + testsuite/tests/driver/T21097b/Test.hs - + testsuite/tests/driver/T21097b/all.T - + testsuite/tests/driver/T21097b/pkgdb/a.conf - + testsuite/tests/driver/T21097b/pkgdb/b.conf - + testsuite/tests/driver/T21097b/pkgdb/c.conf - testsuite/tests/driver/T2182.stderr - + testsuite/tests/driver/T23944.hs - + testsuite/tests/driver/T23944.stderr - + testsuite/tests/driver/T23944A.hs - + testsuite/tests/driver/T24196/T24196.stderr - + testsuite/tests/driver/T24196/T24196A.hs - + testsuite/tests/driver/T24196/T24196A.hs-boot - + testsuite/tests/driver/T24196/T24196B.hs - + testsuite/tests/driver/T24196/all.T - + testsuite/tests/driver/T24275/T24275.stderr - + testsuite/tests/driver/T24275/T24275A.hs - + testsuite/tests/driver/T24275/T24275A.hs-boot - + testsuite/tests/driver/T24275/T24275B.hs - + testsuite/tests/driver/T24275/T24275B.hs-boot - + testsuite/tests/driver/T24275/all.T - + testsuite/tests/driver/T24286.cpp - + testsuite/tests/driver/T24839.hs - + testsuite/tests/driver/T24839.stdout - + testsuite/tests/driver/T25382.hs - testsuite/tests/driver/T3007/Makefile - testsuite/tests/driver/T4437.hs - testsuite/tests/driver/T8526/T8526.stdout - testsuite/tests/driver/all.T - + testsuite/tests/driver/boot-target/A.hs - + testsuite/tests/driver/boot-target/A.hs-boot - + testsuite/tests/driver/boot-target/B.hs - + testsuite/tests/driver/boot-target/Makefile - + testsuite/tests/driver/boot-target/all.T - + testsuite/tests/driver/cpp_assertions_ignored/Makefile - + testsuite/tests/driver/cpp_assertions_ignored/all.T - + testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout - + testsuite/tests/driver/cpp_assertions_ignored/main.hs - testsuite/tests/driver/dynamicToo/dynamicToo006/all.T - testsuite/tests/driver/dynamicToo/dynamicTooMake/Makefile - testsuite/tests/driver/fat-iface/Makefile - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/inline-check.stderr - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/json.hs - testsuite/tests/driver/json.stderr - testsuite/tests/driver/json2.stderr - + testsuite/tests/driver/json_dump.hs - + testsuite/tests/driver/json_dump.stderr - + testsuite/tests/driver/json_warn.hs - + testsuite/tests/driver/json_warn.stderr - + testsuite/tests/driver/multipleHomeUnits/T25122/T25122.hs - testsuite/tests/driver/multipleHomeUnits/all.T - testsuite/tests/driver/multipleHomeUnits/different-db/Makefile - testsuite/tests/driver/multipleHomeUnits/different-db/all.T - testsuite/tests/driver/multipleHomeUnits/mhu-closure/Makefile - testsuite/tests/driver/multipleHomeUnits/mhu-closure/all.T - + testsuite/tests/driver/multipleHomeUnits/mhu-perf/Makefile - + testsuite/tests/driver/multipleHomeUnits/mhu-perf/Setup.hs - + testsuite/tests/driver/multipleHomeUnits/mhu-perf/all.T - + testsuite/tests/driver/multipleHomeUnits/mhu-perf/genLargeHMU - + testsuite/tests/driver/multipleHomeUnits/mhu-perf/mhu-perf.stderr - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits_callstack.stderr - + testsuite/tests/driver/multipleHomeUnits/t25139/u1 - + testsuite/tests/driver/multipleHomeUnits/t25139/u1src/A.hs - + testsuite/tests/driver/multipleHomeUnits/t25139/u1src/A1.hs - + testsuite/tests/driver/multipleHomeUnits/t25139/u1src/A2.hs - + testsuite/tests/driver/multipleHomeUnits/t25139/u2 - + testsuite/tests/driver/multipleHomeUnits/t25139/u2src/U.hs - + testsuite/tests/driver/multipleHomeUnits/t25139/u3 - + testsuite/tests/driver/multipleHomeUnits/t25139/u3src/C.hs - + testsuite/tests/driver/multipleHomeUnits/t25139/u4 - + testsuite/tests/driver/multipleHomeUnits/t25139/u4src/U4.hs - testsuite/tests/driver/multipleHomeUnits/unitCFile - + testsuite/tests/driver/multipleHomeUnits/unitSame1 - + testsuite/tests/driver/multipleHomeUnits/unitSame2 - testsuite/tests/driver/objc/all.T - testsuite/tests/driver/objc/objcpp-hi.mm → testsuite/tests/driver/objc/objcxx-hi.mm - testsuite/tests/driver/objc/objcpp-hi.stdout → testsuite/tests/driver/objc/objcxx-hi.stdout - testsuite/tests/driver/package-imports-t20779/Makefile - testsuite/tests/driver/recomp008/all.T - testsuite/tests/driver/recomp011/all.T - testsuite/tests/driver/recomp015/all.T - + testsuite/tests/driver/recomp24656/A.hs - + testsuite/tests/driver/recomp24656/Makefile - + testsuite/tests/driver/recomp24656/all.T - + testsuite/tests/driver/recomp24656/recomp24656.stdout - testsuite/tests/driver/recompChangedPackage/Makefile - testsuite/tests/driver/recompPluginPackage/Makefile - testsuite/tests/driver/recompTHpackage/Makefile - testsuite/tests/driver/should_fail/all.T - + testsuite/tests/driver/should_fail/main-is.hs - + testsuite/tests/driver/should_fail/main-is.stderr - + testsuite/tests/driver/t23724/LICENSE - + testsuite/tests/driver/t23724/Makefile - + testsuite/tests/driver/t23724/README.md - + testsuite/tests/driver/t23724/Setup.hs - + testsuite/tests/driver/t23724/all.T - + testsuite/tests/driver/t23724/cabal.project - + testsuite/tests/driver/t23724/packageA/Setup.hs - + testsuite/tests/driver/t23724/packageA/packageA.cabal - + testsuite/tests/driver/t23724/packageA/src/LibA.hs - + testsuite/tests/driver/t23724/packageA/src/LibA1.hs - + testsuite/tests/driver/t23724/packageA/src/LibA2.hs - + testsuite/tests/driver/t23724/packageB/Setup.hs - + testsuite/tests/driver/t23724/packageB/app/Main.hs - + testsuite/tests/driver/t23724/packageB/packageB.cabal - + testsuite/tests/driver/t23724/packageB/src/LibB.hs - + testsuite/tests/driver/t23724/recompPkgLink.stdout - + testsuite/tests/driver/t24839_sub.S - + testsuite/tests/driver/t25150/dir/Main.hs - + testsuite/tests/driver/t25150/dir/a.c - + testsuite/tests/exceptions/T25052.hs - + testsuite/tests/exceptions/T25052.stdout - + testsuite/tests/exceptions/all.T - + testsuite/tests/ffi/should_compile/T24034.h - + testsuite/tests/ffi/should_compile/T24034.hs - + testsuite/tests/ffi/should_compile/T25255.hs - testsuite/tests/ffi/should_compile/all.T - testsuite/tests/ffi/should_compile/cc004.hs - testsuite/tests/ffi/should_fail/T10461.stderr - testsuite/tests/ffi/should_fail/T20116.stderr - testsuite/tests/ffi/should_fail/ccfail001.stderr - testsuite/tests/ffi/should_run/Makefile - testsuite/tests/ffi/should_run/T1288.hs - testsuite/tests/ffi/should_run/T1288_c.c - testsuite/tests/ffi/should_run/T1288_ghci.hs - testsuite/tests/ffi/should_run/T1288_ghci_c.c - testsuite/tests/ffi/should_run/T22159.hs - testsuite/tests/ffi/should_run/T2276.hs - testsuite/tests/ffi/should_run/T2276_c.c - testsuite/tests/ffi/should_run/T2276_ghci.hs - testsuite/tests/ffi/should_run/T2276_ghci_c.c - + testsuite/tests/ffi/should_run/T24314.hs - + testsuite/tests/ffi/should_run/T24314.stdout - + testsuite/tests/ffi/should_run/T24314_c.c - + testsuite/tests/ffi/should_run/T24598.hs - + testsuite/tests/ffi/should_run/T24598.stdout - + testsuite/tests/ffi/should_run/T24598_cmm.cmm - + testsuite/tests/ffi/should_run/T24598b.hs - + testsuite/tests/ffi/should_run/T24598b.stdout - + testsuite/tests/ffi/should_run/T24598b_cmm.cmm - + testsuite/tests/ffi/should_run/T24598c.hs - + testsuite/tests/ffi/should_run/T24598c.stdout - + testsuite/tests/ffi/should_run/T24598c_cmm.cmm - + testsuite/tests/ffi/should_run/T24818.hs - + testsuite/tests/ffi/should_run/T24818.stdout - + testsuite/tests/ffi/should_run/T24818_c.c - + testsuite/tests/ffi/should_run/T24818_cmm.cmm - testsuite/tests/ffi/should_run/T7170.stderr - testsuite/tests/ffi/should_run/all.T - testsuite/tests/ffi/should_run/ffi008.stderr - + testsuite/tests/ffi/should_run/ffi012.ghc.stderr - testsuite/tests/ffi/should_run/fptrfail01.stderr - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/T12468.stderr - testsuite/tests/gadt/T19847.hs - testsuite/tests/gadt/T19847a.stderr - testsuite/tests/gadt/T20485.stderr - + testsuite/tests/gadt/T23023.stderr - testsuite/tests/gadt/all.T - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/gadt/gadtSyntaxFail001.stderr - testsuite/tests/gadt/gadtSyntaxFail002.stderr - testsuite/tests/gadt/gadtSyntaxFail003.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - + testsuite/tests/generics/T14266.hs - + testsuite/tests/generics/T25148a.hs - + testsuite/tests/generics/T25148b.hs - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/generics/all.T - + testsuite/tests/ghc-api/PrimOpEffect_Sanity.hs - testsuite/tests/ghc-api/T10052/T10052.stderr - testsuite/tests/ghc-api/T10942.hs - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/T20757.stderr - testsuite/tests/ghc-api/T6145.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/annotations-literals/all.T - testsuite/tests/ghc-api/annotations-literals/parsed.hs - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/downsweep/all.T - testsuite/tests/ghc-api/dynCompileExpr/all.T - + testsuite/tests/ghc-api/exactprint/AddClassMethod.expected.hs - + testsuite/tests/ghc-api/exactprint/AddClassMethod.hs - testsuite/tests/ghc-api/exactprint/AddDecl1.expected.hs - testsuite/tests/ghc-api/exactprint/Makefile - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-api/exactprint/all.T - + testsuite/tests/ghc-api/settings-escape/T11938.hs - + testsuite/tests/ghc-api/settings-escape/T11938.stderr - + testsuite/tests/ghc-api/settings-escape/all.T - + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib/.gitkeep - + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/mingw/.gitkeep - testsuite/tests/ghc-api/target-contents/TargetContents.hs - testsuite/tests/ghc-e/should_fail/Makefile - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail18.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail5.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail7.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - + testsuite/tests/ghc-e/should_fail/T23663.stderr - + testsuite/tests/ghc-e/should_fail/T24172.hs - + testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghc-e/should_fail/T9930fail.stderr - testsuite/tests/ghc-e/should_fail/all.T - testsuite/tests/ghc-e/should_run/ghc-e005.stderr - testsuite/tests/ghci.debugger/scripts/T13825-debugger.stdout - testsuite/tests/ghci.debugger/scripts/T19394.stdout - + testsuite/tests/ghci.debugger/scripts/T24306.hs - + testsuite/tests/ghci.debugger/scripts/T24306.script - + testsuite/tests/ghci.debugger/scripts/T24306.stdout - + testsuite/tests/ghci.debugger/scripts/T24712.hs - + testsuite/tests/ghci.debugger/scripts/T24712.script - + testsuite/tests/ghci.debugger/scripts/T24712.stdout - + testsuite/tests/ghci.debugger/scripts/T25109.hs - + testsuite/tests/ghci.debugger/scripts/T25109.script - + testsuite/tests/ghci.debugger/scripts/T25109.stdout - testsuite/tests/ghci.debugger/scripts/all.T - testsuite/tests/ghci.debugger/scripts/break002.stdout - testsuite/tests/ghci.debugger/scripts/break006.stderr - testsuite/tests/ghci.debugger/scripts/break009.stdout - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break017.stdout - testsuite/tests/ghci.debugger/scripts/break021.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci.debugger/scripts/dynbrk001.stdout - testsuite/tests/ghci.debugger/scripts/listCommand001.stdout - testsuite/tests/ghci.debugger/scripts/print019.stderr - testsuite/tests/ghci.debugger/scripts/print027.stdout - testsuite/tests/ghci.debugger/scripts/print028.stdout - testsuite/tests/ghci/T13786/all.T - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - + testsuite/tests/ghci/T23405/T23405.hs - + testsuite/tests/ghci/T23405/T23405.script - + testsuite/tests/ghci/T23405/all.T - + testsuite/tests/ghci/T23612/T23612.hs - + testsuite/tests/ghci/T23612/T23612.script - + testsuite/tests/ghci/T23612/T23612b.script - + testsuite/tests/ghci/T23612/T23612bA.hs - + testsuite/tests/ghci/T23612/T23612bB.hs - + testsuite/tests/ghci/T23612/all.T - + testsuite/tests/ghci/T24327/T24327.hs - + testsuite/tests/ghci/T24327/T24327.script - + testsuite/tests/ghci/T24327/T24327A.hs - + testsuite/tests/ghci/T24327/all.T - testsuite/tests/ghci/linking/Makefile - + testsuite/tests/ghci/linking/T25155.hs - + testsuite/tests/ghci/linking/T25155.stdout - + testsuite/tests/ghci/linking/T25155_TH.hs - + testsuite/tests/ghci/linking/T25155_iserv.hs - + testsuite/tests/ghci/linking/T25155_iserv_main.c - + testsuite/tests/ghci/linking/T25240/Makefile - + testsuite/tests/ghci/linking/T25240/T25240.hs - + testsuite/tests/ghci/linking/T25240/T25240.stderr - + testsuite/tests/ghci/linking/T25240/T25240a.hs - + testsuite/tests/ghci/linking/T25240/all.T - testsuite/tests/ghci/linking/all.T - testsuite/tests/ghci/linking/dyn/T3372.hs - testsuite/tests/ghci/linking/dyn/all.T - testsuite/tests/ghci/prog006/prog006.stderr - testsuite/tests/ghci/prog011/prog011.stderr - testsuite/tests/ghci/prog013/prog013.stderr - testsuite/tests/ghci/prog018/prog018.stdout - testsuite/tests/ghci/scripts/Defer02.stderr - + testsuite/tests/ghci/scripts/ListTuplePunsPpr.script - + testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - + testsuite/tests/ghci/scripts/ListTuplePunsPprNoAbbrevTuple.script - + testsuite/tests/ghci/scripts/ListTuplePunsPprNoAbbrevTuple.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10501.stderr - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T10963.stderr - testsuite/tests/ghci/scripts/T12550.stdout - testsuite/tests/ghci/scripts/T13202a.stderr - + testsuite/tests/ghci/scripts/T13869.script - + testsuite/tests/ghci/scripts/T13869.stdout - + testsuite/tests/ghci/scripts/T13869a.hs - + testsuite/tests/ghci/scripts/T13869b.hs - testsuite/tests/ghci/scripts/T13997.stdout - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T14828.script - testsuite/tests/ghci/scripts/T14969.stderr - testsuite/tests/ghci/scripts/T15325.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T16804.stdout - testsuite/tests/ghci/scripts/T17669.stdout - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T1914.stdout - testsuite/tests/ghci/scripts/T19310.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20217.stdout - testsuite/tests/ghci/scripts/T20587.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T21110.stderr - testsuite/tests/ghci/scripts/T21294a.stdout - testsuite/tests/ghci/scripts/T2182ghci2.stderr - + testsuite/tests/ghci/scripts/T23686.script - + testsuite/tests/ghci/scripts/T23686.stderr - + testsuite/tests/ghci/scripts/T23686A.hs - + testsuite/tests/ghci/scripts/T23686B.hs - + testsuite/tests/ghci/scripts/T24459.script - + testsuite/tests/ghci/scripts/T24459.stdout - testsuite/tests/ghci/scripts/T2452.stderr - testsuite/tests/ghci/scripts/T2452.stdout - + testsuite/tests/ghci/scripts/T25414.script - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T5545.stdout - testsuite/tests/ghci/scripts/T5557.stdout - testsuite/tests/ghci/scripts/T6105.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8042.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8353.stderr - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T8639.stderr - testsuite/tests/ghci/scripts/T8649.stderr - testsuite/tests/ghci/scripts/T9140.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci008.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci021.stderr - testsuite/tests/ghci/scripts/ghci022.stderr - testsuite/tests/ghci/scripts/ghci023.stdout - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci026.stdout - testsuite/tests/ghci/scripts/ghci027.stdout - testsuite/tests/ghci/scripts/ghci036.script - testsuite/tests/ghci/scripts/ghci036.stderr - testsuite/tests/ghci/scripts/ghci051.stderr - testsuite/tests/ghci/scripts/ghci052.stderr - testsuite/tests/ghci/scripts/ghci053.stderr - testsuite/tests/ghci/scripts/ghci055.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - + testsuite/tests/ghci/should_fail/GHCiErrorIndexLinks.script - + testsuite/tests/ghci/should_fail/GHCiErrorIndexLinks.stderr - testsuite/tests/ghci/should_fail/T10549.stderr - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_fail/all.T - testsuite/tests/ghci/should_run/BinaryArray.hs - testsuite/tests/ghci/should_run/GHCiPrimCall/Makefile - + testsuite/tests/ghci/should_run/LocalPrelude/Prelude.hs - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T10857a.stdout - + testsuite/tests/ghci/should_run/T10920.hs - + testsuite/tests/ghci/should_run/T10920.script - + testsuite/tests/ghci/should_run/T10920.stderr - + testsuite/tests/ghci/should_run/T10920.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T15806.stderr - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18064.stderr - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - testsuite/tests/ghci/should_run/T21300.stdout - + testsuite/tests/ghci/should_run/T24115.hs - + testsuite/tests/ghci/should_run/T24115.script - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/haddock_examples/Test.hs - testsuite/tests/haddock/haddock_examples/haddock.Test.stderr - testsuite/tests/haddock/haddock_testsuite/Makefile - testsuite/tests/haddock/haddock_testsuite/all.T - + testsuite/tests/haddock/haddock_testsuite/haddock-th-foreign-repro/A.hs - + testsuite/tests/haddock/haddock_testsuite/haddock-th-foreign-repro/B.hs - + testsuite/tests/haddock/haddock_testsuite/haddock-th-foreign-repro/F.hs - + testsuite/tests/haddock/haddock_testsuite/haddock-th-foreign-repro/arith.c - testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr - + testsuite/tests/haddock/should_compile_flag_haddock/T24221.hs - + testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/haddock/should_compile_flag_haddock/all.T - + testsuite/tests/hiefile/should_compile/T24493.hs - + testsuite/tests/hiefile/should_compile/T24493.stderr - testsuite/tests/hiefile/should_compile/all.T - testsuite/tests/hiefile/should_run/HieQueries.hs - testsuite/tests/hiefile/should_run/HieQueries.stdout - + testsuite/tests/hiefile/should_run/HieVdq.hs - + testsuite/tests/hiefile/should_run/HieVdq.stdout - + testsuite/tests/hiefile/should_run/T23120.hs - + testsuite/tests/hiefile/should_run/T23120.stdout - + testsuite/tests/hiefile/should_run/T23540.hs - + testsuite/tests/hiefile/should_run/T23540.stdout - + testsuite/tests/hiefile/should_run/T24544.hs - + testsuite/tests/hiefile/should_run/T24544.stdout - testsuite/tests/hiefile/should_run/TestUtils.hs - testsuite/tests/hiefile/should_run/all.T - + testsuite/tests/hpc/.gitignore - testsuite/tests/hpc/T17073.stdout - + testsuite/tests/hpc/fork/Makefile - + testsuite/tests/hpc/fork/hpc_fork.hs - + testsuite/tests/hpc/fork/hpc_fork.stdout - + testsuite/tests/hpc/fork/test.T - + testsuite/tests/hpc/function/Makefile - + testsuite/tests/hpc/function/test.T - + testsuite/tests/hpc/function/tough.hs - + testsuite/tests/hpc/function/tough.stdout - + testsuite/tests/hpc/function2/Makefile - + testsuite/tests/hpc/function2/subdir/tough2.lhs - + testsuite/tests/hpc/function2/test.T - + testsuite/tests/hpc/function2/tough2.stdout - + testsuite/tests/hpc/ghc_ghci/A.hs - + testsuite/tests/hpc/ghc_ghci/B.hs - + testsuite/tests/hpc/ghc_ghci/Makefile - + testsuite/tests/hpc/ghc_ghci/hpc_ghc_ghci.stdout - + testsuite/tests/hpc/ghc_ghci/test.T - + testsuite/tests/hpc/hpc.ovr - + testsuite/tests/hpc/hpcrun.pl - + testsuite/tests/hpc/raytrace/CSG.hs - + testsuite/tests/hpc/raytrace/Construct.hs - + testsuite/tests/hpc/raytrace/Data.hs - + testsuite/tests/hpc/raytrace/Eval.hs - + testsuite/tests/hpc/raytrace/Geometry.hs - + testsuite/tests/hpc/raytrace/Illumination.hs - + testsuite/tests/hpc/raytrace/Intersections.hs - + testsuite/tests/hpc/raytrace/Interval.hs - + testsuite/tests/hpc/raytrace/Main.hs - + testsuite/tests/hpc/raytrace/Makefile - + testsuite/tests/hpc/raytrace/Misc.hs - + testsuite/tests/hpc/raytrace/Parse.hs - + testsuite/tests/hpc/raytrace/Pixmap.hs - + testsuite/tests/hpc/raytrace/Primitives.hs - + testsuite/tests/hpc/raytrace/RayTrace.hs - + testsuite/tests/hpc/raytrace/Surface.hs - + testsuite/tests/hpc/raytrace/galois.gml - + testsuite/tests/hpc/raytrace/galois.sample - + testsuite/tests/hpc/raytrace/test.T - + testsuite/tests/hpc/raytrace/tixs/.hpc/CSG.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Construct.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Data.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Eval.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Geometry.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Illumination.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Intersections.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Interval.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Main.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Misc.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Parse.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Primitives.mix - + testsuite/tests/hpc/raytrace/tixs/.hpc/Surface.mix - + testsuite/tests/hpc/raytrace/tixs/Makefile - + testsuite/tests/hpc/raytrace/tixs/hpc_markup_multi_001.stdout - + testsuite/tests/hpc/raytrace/tixs/hpc_markup_multi_002.stdout - + testsuite/tests/hpc/raytrace/tixs/hpc_markup_multi_003.stdout - + testsuite/tests/hpc/raytrace/tixs/hpc_raytrace.stdout - + testsuite/tests/hpc/raytrace/tixs/hpc_report_multi_001.stdout - + testsuite/tests/hpc/raytrace/tixs/hpc_report_multi_002.stdout - + testsuite/tests/hpc/raytrace/tixs/hpc_report_multi_003.stdout - + testsuite/tests/hpc/raytrace/tixs/hpc_sample.tix - + testsuite/tests/hpc/raytrace/tixs/hpc_show_multi_001.stdout - + testsuite/tests/hpc/raytrace/tixs/hpc_show_multi_002.stdout - + testsuite/tests/hpc/raytrace/tixs/test.T - + testsuite/tests/hpc/simple/Makefile - + testsuite/tests/hpc/simple/hpc001.hs - + testsuite/tests/hpc/simple/hpc001.stdout - + testsuite/tests/hpc/simple/test.T - + testsuite/tests/hpc/simple/tixs/.hpc.copy/Main.mix - + testsuite/tests/hpc/simple/tixs/.hpc/Main.mix - + testsuite/tests/hpc/simple/tixs/.hpc/NoParse.mix - + testsuite/tests/hpc/simple/tixs/Makefile - + testsuite/tests/hpc/simple/tixs/T10529a.stderr - + testsuite/tests/hpc/simple/tixs/T10529b.stderr - + testsuite/tests/hpc/simple/tixs/T10529c.stderr - + testsuite/tests/hpc/simple/tixs/hand_overlay.ovr - + testsuite/tests/hpc/simple/tixs/hpc001.hs - + testsuite/tests/hpc/simple/tixs/hpc_bad_001.stdout - + testsuite/tests/hpc/simple/tixs/hpc_draft.stdout - + testsuite/tests/hpc/simple/tixs/hpc_hand_overlay.stdout - + testsuite/tests/hpc/simple/tixs/hpc_help.stdout - + testsuite/tests/hpc/simple/tixs/hpc_help_draft.stdout - + testsuite/tests/hpc/simple/tixs/hpc_help_help.stdout - + testsuite/tests/hpc/simple/tixs/hpc_help_markup.stdout - + testsuite/tests/hpc/simple/tixs/hpc_help_overlay.stdout - + testsuite/tests/hpc/simple/tixs/hpc_help_report.stdout - + testsuite/tests/hpc/simple/tixs/hpc_help_show.stdout - + testsuite/tests/hpc/simple/tixs/hpc_help_version.stdout - + testsuite/tests/hpc/simple/tixs/hpc_markup_001.stdout - + testsuite/tests/hpc/simple/tixs/hpc_markup_002.stdout - + testsuite/tests/hpc/simple/tixs/hpc_markup_error_001.stdout - + testsuite/tests/hpc/simple/tixs/hpc_markup_error_002.stdout - + testsuite/tests/hpc/simple/tixs/hpc_overlay.stdout - + testsuite/tests/hpc/simple/tixs/hpc_overlay2.stdout - + testsuite/tests/hpc/simple/tixs/hpc_report_001.stdout - + testsuite/tests/hpc/simple/tixs/hpc_report_002.stdout - + testsuite/tests/hpc/simple/tixs/hpc_report_003.stdout - + testsuite/tests/hpc/simple/tixs/hpc_report_error_001.stdout - + testsuite/tests/hpc/simple/tixs/hpc_report_error_002.stdout - + testsuite/tests/hpc/simple/tixs/hpc_sample.tix - + testsuite/tests/hpc/simple/tixs/hpc_sample_incompatible_hash.tix - + testsuite/tests/hpc/simple/tixs/hpc_sample_no_parse.tix - + testsuite/tests/hpc/simple/tixs/hpc_sample_non_existing_module.tix - + testsuite/tests/hpc/simple/tixs/hpc_show.stdout - + testsuite/tests/hpc/simple/tixs/hpc_show_error_001.stdout - + testsuite/tests/hpc/simple/tixs/hpc_show_error_002.stdout - + testsuite/tests/hpc/simple/tixs/sample_overlay.ovr - + testsuite/tests/hpc/simple/tixs/test.T - + testsuite/tests/iface/IfaceSharingIfaceType.hs - + testsuite/tests/iface/IfaceSharingName.hs - + testsuite/tests/iface/Lib.hs - + testsuite/tests/iface/Makefile - + testsuite/tests/iface/all.T - + testsuite/tests/iface/if_faststring.hs - + testsuite/tests/iface/if_ifacetype.hs - + testsuite/tests/iface/if_name.hs - testsuite/tests/impredicative/T18126-nasty.hs - + testsuite/tests/impredicative/T24676.hs - testsuite/tests/impredicative/all.T - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/Simple14.hs - − testsuite/tests/indexed-types/should_compile/Simple14.stderr - testsuite/tests/indexed-types/should_compile/T10806.stderr - testsuite/tests/indexed-types/should_compile/T11361a.stderr - testsuite/tests/indexed-types/should_compile/T15322a.stderr - testsuite/tests/indexed-types/should_compile/T15352.hs - testsuite/tests/indexed-types/should_compile/T15852.stderr - testsuite/tests/indexed-types/should_compile/T16356_Compile1.hs - + testsuite/tests/indexed-types/should_compile/T24134.hs - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - + testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/T3208b.stderr - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail15.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12522a.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13571.stderr - testsuite/tests/indexed-types/should_fail/T13571a.stderr - testsuite/tests/indexed-types/should_fail/T13784.stderr - testsuite/tests/indexed-types/should_fail/T13877.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T14369.stderr - testsuite/tests/indexed-types/should_fail/T14887.stderr - testsuite/tests/indexed-types/should_fail/T15172.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15764.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T1897b.stderr - testsuite/tests/indexed-types/should_fail/T1900.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T2544.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T4099.stderr - testsuite/tests/indexed-types/should_fail/T4179.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8227.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T8518.stderr - testsuite/tests/indexed-types/should_fail/T9036.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9171.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - + testsuite/tests/interface-stability/ghc-experimental-exports.stdout - + testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - + testsuite/tests/interface-stability/template-haskell-exports.stdout - + testsuite/tests/javascript/Makefile - + testsuite/tests/javascript/T23479.hs - + testsuite/tests/javascript/T23479.stdout - + testsuite/tests/javascript/T24495.hs - + testsuite/tests/javascript/T24495.stdout - + testsuite/tests/javascript/T24744.hs - + testsuite/tests/javascript/T24744.stdout - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - + testsuite/tests/javascript/closure/Makefile - + testsuite/tests/javascript/closure/T24602.hs - + testsuite/tests/javascript/closure/T24602.stdout - + testsuite/tests/javascript/closure/all.T - + testsuite/tests/javascript/js-c-sources/all.T - + testsuite/tests/javascript/js-c-sources/js-c-sources01.hs - + testsuite/tests/javascript/js-c-sources/js-c-sources01.stdout - + testsuite/tests/javascript/js-c-sources/js-c-sources01_c.c - + testsuite/tests/javascript/js-c-sources/js-c-sources01_js.js - + testsuite/tests/javascript/js-c-sources/js-c-sources02.hs - + testsuite/tests/javascript/js-c-sources/js-c-sources02.stdout - + testsuite/tests/javascript/js-c-sources/js-c-sources02_c.c - + testsuite/tests/javascript/js-c-sources/js-c-sources02_js.js - testsuite/tests/javascript/js-callback03.hs - testsuite/tests/javascript/js-ffi-string.hs - testsuite/tests/javascript/js-ffi-string.stdout - + testsuite/tests/javascript/js-mk_tup.hs - + testsuite/tests/javascript/js-mk_tup.stdout - testsuite/tests/javascript/opt/all.T - testsuite/tests/javascript/opt/deadCodeElim.hs - + testsuite/tests/javascript/opt/jsOptimizer.hs - + testsuite/tests/javascript/test-mk_tup.js - + testsuite/tests/jsffi/README.md - + testsuite/tests/jsffi/all.T - + testsuite/tests/jsffi/gameover.hs - + testsuite/tests/jsffi/gameover.mjs - + testsuite/tests/jsffi/gameover.stdout - + testsuite/tests/jsffi/http.hs - + testsuite/tests/jsffi/http.mjs - + testsuite/tests/jsffi/http.stdout - + testsuite/tests/jsffi/jsffigc.hs - + testsuite/tests/jsffi/jsffigc.mjs - + testsuite/tests/jsffi/jsffigc.stdout - + testsuite/tests/jsffi/jsffioff.hs - + testsuite/tests/jsffi/jsffioff.mjs - + testsuite/tests/jsffi/jsffioff.stdout - + testsuite/tests/jsffi/jsffion.hs - + testsuite/tests/jsffi/jsffion.mjs - + testsuite/tests/jsffi/jsffion.stdout - + testsuite/tests/jsffi/jsffisleep.hs - + testsuite/tests/jsffi/jsffisleep.mjs - + testsuite/tests/jsffi/jsffisleep.stdout - + testsuite/tests/jsffi/textconv.hs - + testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/jsffi/textconv.stdout - testsuite/tests/layout/layout001.stdout - testsuite/tests/layout/layout003.stdout - testsuite/tests/layout/layout004.stdout - testsuite/tests/layout/layout006.stdout - + testsuite/tests/lib/base/CompareLength.hs - + testsuite/tests/lib/base/CompareLength.stdout - + testsuite/tests/lib/base/First-Monoid-sconcat.hs - + testsuite/tests/lib/base/First-Monoid-sconcat.stdout - + testsuite/tests/lib/base/First-Semigroup-sconcat.hs - + testsuite/tests/lib/base/First-Semigroup-sconcat.stdout - + testsuite/tests/lib/base/InitsTails.hs - + testsuite/tests/lib/base/InitsTails.stdout - + testsuite/tests/lib/base/Sort.hs - + testsuite/tests/lib/base/Sort.stdout - + testsuite/tests/lib/base/T24672.hs - + testsuite/tests/lib/base/T24672.stdout - testsuite/tests/lib/base/Unsnoc.hs - testsuite/tests/lib/base/all.T - testsuite/tests/lib/integer/IntegerConversionRules.hs - testsuite/tests/lib/integer/Makefile - testsuite/tests/lib/integer/T20066.stderr - + testsuite/tests/linear/should_compile/LinearLet.hs - + testsuite/tests/linear/should_compile/LinearLetPoly.hs - + testsuite/tests/linear/should_compile/LinearListComprehension.hs - testsuite/tests/linear/should_compile/MultConstructor.hs - + testsuite/tests/linear/should_compile/OmitFieldPat.hs - testsuite/tests/linear/should_compile/T1735Min.hs - + testsuite/tests/linear/should_compile/T23814.hs - + testsuite/tests/linear/should_compile/T25428.hs - + testsuite/tests/linear/should_compile/T25515.hs - testsuite/tests/linear/should_compile/all.T - testsuite/tests/linear/should_fail/Linear9.stderr - testsuite/tests/linear/should_fail/LinearAsPat.stderr - testsuite/tests/linear/should_fail/LinearConfusedDollar.stderr - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLazyPat.stderr - − testsuite/tests/linear/should_fail/LinearLet.stderr - testsuite/tests/linear/should_fail/LinearLet.hs → testsuite/tests/linear/should_fail/LinearLet1.hs - + testsuite/tests/linear/should_fail/LinearLet1.stderr - + testsuite/tests/linear/should_fail/LinearLet10.hs - + testsuite/tests/linear/should_fail/LinearLet10.stderr - + testsuite/tests/linear/should_fail/LinearLet2.hs - + testsuite/tests/linear/should_fail/LinearLet2.stderr - + testsuite/tests/linear/should_fail/LinearLet3.hs - + testsuite/tests/linear/should_fail/LinearLet3.stderr - + testsuite/tests/linear/should_fail/LinearLet4.hs - + testsuite/tests/linear/should_fail/LinearLet4.stderr - + testsuite/tests/linear/should_fail/LinearLet5.hs - + testsuite/tests/linear/should_fail/LinearLet5.stderr - + testsuite/tests/linear/should_fail/LinearLet6.hs - + testsuite/tests/linear/should_fail/LinearLet6.stderr - + testsuite/tests/linear/should_fail/LinearLet7.hs - + testsuite/tests/linear/should_fail/LinearLet7.stderr - + testsuite/tests/linear/should_fail/LinearLet8.hs - + testsuite/tests/linear/should_fail/LinearLet8.stderr - + testsuite/tests/linear/should_fail/LinearLet9.hs - + testsuite/tests/linear/should_fail/LinearLet9.stderr - testsuite/tests/linear/should_fail/LinearNoExt.stderr - testsuite/tests/linear/should_fail/LinearNoExtU.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearPatSyn.stderr - testsuite/tests/linear/should_fail/LinearPolyType.stderr - testsuite/tests/linear/should_fail/LinearTHFail2.stderr - testsuite/tests/linear/should_fail/LinearTHFail3.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/LinearViewPattern.stderr - testsuite/tests/linear/should_fail/T18888.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/linear/should_fail/T23814fail.hs - + testsuite/tests/linear/should_fail/T23814fail.stderr - + testsuite/tests/linear/should_fail/T24961.hs - + testsuite/tests/linear/should_fail/T24961.stderr - + testsuite/tests/linear/should_fail/T25081.hs - + testsuite/tests/linear/should_fail/T25081.stderr - + testsuite/tests/linear/should_fail/T25185.hs - + testsuite/tests/linear/should_fail/T25185.stderr - testsuite/tests/linear/should_fail/all.T - testsuite/tests/linters/Makefile - testsuite/tests/linters/all.T - testsuite/tests/linters/notes.stdout - testsuite/tests/linters/regex-linters/check-cpp.py - testsuite/tests/linters/regex-linters/linter.py - + testsuite/tests/llvm/should_compile/T25019.hs - + testsuite/tests/llvm/should_compile/T25353.asm - + testsuite/tests/llvm/should_compile/T25353.hs - + testsuite/tests/llvm/should_compile/T25606.hs - testsuite/tests/llvm/should_compile/all.T - + testsuite/tests/llvm/should_run/T22033.hs - + testsuite/tests/llvm/should_run/T22033.stdout - + testsuite/tests/llvm/should_run/T22487.hs - + testsuite/tests/llvm/should_run/T22487.stdout - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - + testsuite/tests/llvm/should_run/all.T - testsuite/tests/mdo/should_fail/mdofail005.stderr - testsuite/tests/mdo/should_fail/mdofail006.stderr - testsuite/tests/module/Mod137_A.hs - testsuite/tests/module/Mod138_A.hs - testsuite/tests/module/Mod141_A.hs - testsuite/tests/module/T20007.stderr - + testsuite/tests/module/T21752.stderr - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod147.stderr - testsuite/tests/module/mod150.stderr - testsuite/tests/module/mod151.stderr - testsuite/tests/module/mod152.stderr - testsuite/tests/module/mod153.stderr - testsuite/tests/module/mod154.hs - testsuite/tests/module/mod155.stderr - testsuite/tests/module/mod180.stderr - testsuite/tests/module/mod182.stderr - testsuite/tests/module/mod184.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod39.stderr - testsuite/tests/module/mod40.stderr - testsuite/tests/module/mod41.stderr - testsuite/tests/module/mod42.stderr - testsuite/tests/module/mod43.stderr - testsuite/tests/module/mod45.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod58.stderr - testsuite/tests/module/mod73.stderr - testsuite/tests/module/mod74.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/module/mod98.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19641.stderr - testsuite/tests/numeric/should_compile/T19892.stderr - + testsuite/tests/numeric/should_compile/T23907.hs - + testsuite/tests/numeric/should_compile/T23907.stderr - + testsuite/tests/numeric/should_compile/T24331.hs - + testsuite/tests/numeric/should_compile/T24331.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - testsuite/tests/numeric/should_compile/T8542.stderr - testsuite/tests/numeric/should_compile/all.T - + testsuite/tests/numeric/should_run/T24066.hs - + testsuite/tests/numeric/should_run/T24066.stdout - + testsuite/tests/numeric/should_run/T24245.hs - + testsuite/tests/numeric/should_run/T24245.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - + testsuite/tests/numeric/should_run/div01.hs - + testsuite/tests/numeric/should_run/div01.stdout - + testsuite/tests/numeric/should_run/div01.stdout-ws-32 - testsuite/tests/numeric/should_run/foundation.hs - testsuite/tests/numeric/should_run/mul2.hs - testsuite/tests/numeric/should_run/mul2.stdout - testsuite/tests/numeric/should_run/mul2.stdout-ws-32 - + testsuite/tests/numeric/should_run/mul2int.hs - + testsuite/tests/numeric/should_run/mul2int.stdout - + testsuite/tests/numeric/should_run/mul2int.stdout-ws-32 - + testsuite/tests/numeric/should_run/quotRem2Large.hs - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail03.stderr - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail05.stderr - testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs - testsuite/tests/overloadedrecflds/ghci/GHCiDRF.stdout - testsuite/tests/overloadedrecflds/ghci/T19314.stdout - testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout - testsuite/tests/overloadedrecflds/ghci/overloadedlabelsghci01.stdout - + testsuite/tests/overloadedrecflds/should_compile/T22424.hs - testsuite/tests/overloadedrecflds/should_compile/T23279.hs - testsuite/tests/overloadedrecflds/should_compile/T23279.stderr - + testsuite/tests/overloadedrecflds/should_compile/T24293.hs - + testsuite/tests/overloadedrecflds/should_compile/T24293b.hs - + testsuite/tests/overloadedrecflds/should_compile/T24293c.hs - + testsuite/tests/overloadedrecflds/should_compile/T24293c.stderr - + testsuite/tests/overloadedrecflds/should_compile/T24381.hs - testsuite/tests/overloadedrecflds/should_compile/all.T - testsuite/tests/overloadedrecflds/should_fail/DRFPartialFields.stderr - testsuite/tests/overloadedrecflds/should_fail/NFSDuplicate.stderr - testsuite/tests/overloadedrecflds/should_fail/NoFieldSelectorsFail.stderr - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_fail/T21946.stderr - testsuite/tests/overloadedrecflds/should_fail/hasfieldfail02.hs - testsuite/tests/overloadedrecflds/should_fail/hasfieldfail02.stderr - testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail10.stderr - testsuite/tests/overloadedrecflds/should_run/all.T - + testsuite/tests/overloadedrecflds/should_run/hasfieldrun03.hs - + testsuite/tests/overloadedrecflds/should_run/hasfieldrun03.stdout - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - + testsuite/tests/parser/should_compile/ListTuplePunsFamilies.hs - + testsuite/tests/parser/should_compile/ListTuplePunsFamilies.script - + testsuite/tests/parser/should_compile/ListTuplePunsFamiliesCompat.hs - + testsuite/tests/parser/should_compile/ListTuplePunsSuccess1.hs - + testsuite/tests/parser/should_compile/ListTuplePunsSuccess1.script - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T15279.stderr - testsuite/tests/parser/should_compile/T15323.stderr - + testsuite/tests/parser/should_compile/T17045/Prelude.hs - + testsuite/tests/parser/should_compile/T17045/Test.hs - + testsuite/tests/parser/should_compile/T19082.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20718b.stderr - testsuite/tests/parser/should_compile/T20846.stderr - + testsuite/tests/parser/should_compile/T22155.hs - + testsuite/tests/parser/should_compile/T22155.stderr - testsuite/tests/parser/should_compile/T2245.stderr - testsuite/tests/parser/should_compile/T23315/Makefile - testsuite/tests/parser/should_compile/T23315/T23315.stderr - testsuite/tests/parser/should_compile/T23315/all.T - + testsuite/tests/parser/should_compile/T25132.hs - + testsuite/tests/parser/should_compile/T25258.hs - + testsuite/tests/parser/should_compile/T25258.stderr - testsuite/tests/parser/should_compile/all.T - + testsuite/tests/parser/should_fail/ListTuplePunsFail1.hs - + testsuite/tests/parser/should_fail/ListTuplePunsFail1.script - + testsuite/tests/parser/should_fail/ListTuplePunsFail1.stderr - + testsuite/tests/parser/should_fail/ListTuplePunsFail2.hs - + testsuite/tests/parser/should_fail/ListTuplePunsFail2.script - + testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - + testsuite/tests/parser/should_fail/ListTuplePunsFail3.hs - + testsuite/tests/parser/should_fail/ListTuplePunsFail3.script - + testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - + testsuite/tests/parser/should_fail/ListTuplePunsFail4.hs - + testsuite/tests/parser/should_fail/ListTuplePunsFail4.script - + testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - + testsuite/tests/parser/should_fail/ListTuplePunsFail5.hs - + testsuite/tests/parser/should_fail/ListTuplePunsFail5.script - + testsuite/tests/parser/should_fail/ListTuplePunsFail5.stderr - + testsuite/tests/parser/should_fail/MultilineStringsError.hs - + testsuite/tests/parser/should_fail/MultilineStringsError.stderr - + testsuite/tests/parser/should_fail/MultilineStringsInnerTab.hs - + testsuite/tests/parser/should_fail/MultilineStringsInnerTab.stderr - + testsuite/tests/parser/should_fail/MultilineStringsSmartQuotes.hs - + testsuite/tests/parser/should_fail/MultilineStringsSmartQuotes.stderr - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.hs - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.stderr - testsuite/tests/parser/should_fail/NoBlockArgumentsFail.stderr - testsuite/tests/parser/should_fail/NoBlockArgumentsFail2.stderr - testsuite/tests/parser/should_fail/NoBlockArgumentsFail3.stderr - testsuite/tests/parser/should_fail/NoBlockArgumentsFailArrowCmds.stderr - testsuite/tests/parser/should_fail/NoDoAndIfThenElse.stderr - testsuite/tests/parser/should_fail/NoNumericUnderscores0.stderr - testsuite/tests/parser/should_fail/NoNumericUnderscores1.stderr - testsuite/tests/parser/should_fail/NoPatternSynonyms.stderr - testsuite/tests/parser/should_fail/NondecreasingIndentationFail.stderr - + testsuite/tests/parser/should_fail/Or1.hs - + testsuite/tests/parser/should_fail/Or1.stderr - + testsuite/tests/parser/should_fail/OrPatInExprErr.hs - + testsuite/tests/parser/should_fail/OrPatInExprErr.stderr - testsuite/tests/parser/should_fail/ParserNoForallUnicode.stderr - testsuite/tests/parser/should_fail/ParserNoLambdaCase.stderr - testsuite/tests/parser/should_fail/ParserNoMultiWayIf.stderr - testsuite/tests/parser/should_fail/ParserNoTH1.stderr - testsuite/tests/parser/should_fail/ParserNoTH2.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail12.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail9.stderr - testsuite/tests/parser/should_fail/RecordWildCardsFail.stderr - + testsuite/tests/parser/should_fail/SuffixAtFail.hs - + testsuite/tests/parser/should_fail/SuffixAtFail.stderr - testsuite/tests/parser/should_fail/T12429.stderr - testsuite/tests/parser/should_fail/T12446.stderr - testsuite/tests/parser/should_fail/T12811.stderr - testsuite/tests/parser/should_fail/T14588.stderr - testsuite/tests/parser/should_fail/T16270.stderr - testsuite/tests/parser/should_fail/T16270h.stderr - − testsuite/tests/parser/should_fail/T17045.stderr - testsuite/tests/parser/should_fail/T17162.stderr - + testsuite/tests/parser/should_fail/T17879a.hs - + testsuite/tests/parser/should_fail/T17879a.stderr - + testsuite/tests/parser/should_fail/T17879b.hs - + testsuite/tests/parser/should_fail/T17879b.stderr - testsuite/tests/parser/should_fail/T18251c.stderr - − testsuite/tests/parser/should_fail/T18251d.hs - − testsuite/tests/parser/should_fail/T18251d.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - testsuite/tests/parser/should_fail/T20385A.stderr - testsuite/tests/parser/should_fail/T20385B.stderr - + testsuite/tests/parser/should_fail/T20609.hs - + testsuite/tests/parser/should_fail/T20609.stderr - + testsuite/tests/parser/should_fail/T20609a.hs - + testsuite/tests/parser/should_fail/T20609a.stderr - + testsuite/tests/parser/should_fail/T20609b.hs - + testsuite/tests/parser/should_fail/T20609b.stderr - + testsuite/tests/parser/should_fail/T20609c.hs - + testsuite/tests/parser/should_fail/T20609c.stderr - + testsuite/tests/parser/should_fail/T20609d.hs - + testsuite/tests/parser/should_fail/T20609d.stderr - testsuite/tests/parser/should_fail/T21843a.stderr - testsuite/tests/parser/should_fail/T21843b.stderr - testsuite/tests/parser/should_fail/T21843c.stderr - testsuite/tests/parser/should_fail/T21843d.stderr - testsuite/tests/parser/should_fail/T21843e.stderr - testsuite/tests/parser/should_fail/T21843f.stderr - + testsuite/tests/parser/should_fail/T25258a.hs - + testsuite/tests/parser/should_fail/T25258a.stderr - + testsuite/tests/parser/should_fail/T25258b.hs - + testsuite/tests/parser/should_fail/T25258b.stderr - + testsuite/tests/parser/should_fail/T25258c.hs - + testsuite/tests/parser/should_fail/T25258c.stderr - + testsuite/tests/parser/should_fail/T25530.hs - + testsuite/tests/parser/should_fail/T25530.stderr - testsuite/tests/parser/should_fail/T3095.stderr - testsuite/tests/parser/should_fail/T3751.stderr - testsuite/tests/parser/should_fail/T3811.stderr - testsuite/tests/parser/should_fail/T3811e.stderr - testsuite/tests/parser/should_fail/T5425.stderr - testsuite/tests/parser/should_fail/T8258NoGADTs.stderr - testsuite/tests/parser/should_fail/T8501a.stderr - testsuite/tests/parser/should_fail/T8501b.stderr - testsuite/tests/parser/should_fail/T8501c.stderr - testsuite/tests/parser/should_fail/ViewPatternsFail.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_fail/cmdFail010.hs - + testsuite/tests/parser/should_fail/cmdFail010.stderr - + testsuite/tests/parser/should_fail/cmdFail011.hs - + testsuite/tests/parser/should_fail/cmdFail011.stderr - testsuite/tests/parser/should_fail/patFail001.stderr - testsuite/tests/parser/should_fail/proposal-229c.stderr - testsuite/tests/parser/should_fail/readFail001.stderr - testsuite/tests/parser/should_fail/readFail002.stderr - testsuite/tests/parser/should_fail/readFail004.stderr - testsuite/tests/parser/should_fail/readFail005.stderr - testsuite/tests/parser/should_fail/readFail031.stderr - testsuite/tests/parser/should_fail/readFail033.stderr - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_fail/readFail036.stderr - testsuite/tests/parser/should_fail/readFail037.stderr - testsuite/tests/parser/should_fail/readFail038.stderr - testsuite/tests/parser/should_fail/readFail039.stderr - testsuite/tests/parser/should_fail/readFail040.stderr - testsuite/tests/parser/should_fail/readFail041.stderr - testsuite/tests/parser/should_fail/readFail042.stderr - testsuite/tests/parser/should_fail/readFail043.stderr - testsuite/tests/parser/should_fail/readFailTraditionalRecords1.stderr - testsuite/tests/parser/should_fail/readFailTraditionalRecords2.stderr - testsuite/tests/parser/should_fail/readFailTraditionalRecords3.stderr - testsuite/tests/parser/should_fail/unpack_inside_type.stderr - + testsuite/tests/parser/should_run/ListTuplePunsConstraints.hs - + testsuite/tests/parser/should_run/ListTuplePunsConstraints.script - + testsuite/tests/parser/should_run/MultilineStrings.hs - + testsuite/tests/parser/should_run/MultilineStrings.stdout - + testsuite/tests/parser/should_run/MultilineStringsOverloaded.hs - + testsuite/tests/parser/should_run/MultilineStringsOverloaded.stdout - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - testsuite/tests/parser/should_run/RecordDotSyntax1.hs - + testsuite/tests/parser/should_run/T25375.hs - + testsuite/tests/parser/should_run/T25375.stdout - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/parser/unicode/all.T - + testsuite/tests/parser/unicode/lex_unicode_ids.hs - + testsuite/tests/parser/unicode/lex_unispace.hs - testsuite/tests/parser/unicode/utf8_010.stderr - testsuite/tests/parser/unicode/utf8_011.stderr - testsuite/tests/parser/unicode/utf8_020.stderr - testsuite/tests/parser/unicode/utf8_021.stderr - testsuite/tests/parser/unicode/utf8_022.stderr - testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr - testsuite/tests/partial-sigs/should_compile/T13324_compile2.stderr - testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_compile/all.T - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10615.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/partial-sigs/should_fail/WildcardInTypeSynonymLHS.hs - testsuite/tests/partial-sigs/should_fail/WildcardInTypeSynonymLHS.stderr - testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/patsyn/should_compile/T22328.hs - testsuite/tests/patsyn/should_fail/T11010.stderr - testsuite/tests/patsyn/should_fail/T14507.hs - testsuite/tests/patsyn/should_fail/T14507.stderr - testsuite/tests/patsyn/should_fail/T15695.stderr - + testsuite/tests/patsyn/should_fail/T23467.hs - + testsuite/tests/patsyn/should_fail/T23467.stderr - testsuite/tests/patsyn/should_fail/all.T - testsuite/tests/patsyn/should_fail/export-syntax.stderr - + testsuite/tests/patsyn/should_run/T24552.hs - + testsuite/tests/patsyn/should_run/T24552.stdout - testsuite/tests/patsyn/should_run/all.T - testsuite/tests/patsyn/should_run/ghci.stderr - testsuite/tests/perf/compiler/CoOpt_Singletons.hs - testsuite/tests/perf/compiler/LargeRecord.hs - + testsuite/tests/perf/compiler/LookupFusion.hs - + testsuite/tests/perf/compiler/LookupFusion.stdout - testsuite/tests/perf/compiler/Makefile - + testsuite/tests/perf/compiler/MultiLayerModulesDefsGhciReload.script - + testsuite/tests/perf/compiler/MultiLayerModulesDefsGhciWithCore.script - testsuite/tests/perf/compiler/MultiLayerModulesTH_Make.stderr - testsuite/tests/perf/compiler/MultiLayerModulesTH_OneShot.stderr - + testsuite/tests/perf/compiler/MultilineStringsPerf.hs - testsuite/tests/perf/compiler/T11068.stdout - testsuite/tests/perf/compiler/T12545.hs - testsuite/tests/perf/compiler/T13386.hs - testsuite/tests/perf/compiler/T15630.hs - + testsuite/tests/perf/compiler/T15630a.hs - testsuite/tests/perf/compiler/T16875.hs - testsuite/tests/perf/compiler/T16875.stderr - testsuite/tests/simplCore/should_compile/T18730.hs → testsuite/tests/perf/compiler/T18730.hs - testsuite/tests/simplCore/should_compile/T18730_A.hs → testsuite/tests/perf/compiler/T18730_A.hs - testsuite/tests/perf/compiler/T21839c.hs - + testsuite/tests/perf/compiler/T24471.hs - + testsuite/tests/perf/compiler/T24471a.hs - + testsuite/tests/perf/compiler/T24582.hs - + testsuite/tests/perf/compiler/T24984.hs - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/T4007.stdout - testsuite/tests/perf/compiler/T8095.hs - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/genMultiLayerModulesCore - testsuite/tests/perf/compiler/hard_hole_fits.hs - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/compiler/large-project/all.T - + testsuite/tests/perf/compiler/large-project/large-project.sh - testsuite/tests/perf/haddock/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/T15426.hs - + testsuite/tests/perf/should_run/T17949.hs - testsuite/tests/perf/should_run/T18964.hs - testsuite/tests/perf/should_run/T21839r.hs - + testsuite/tests/perf/should_run/T25055.hs - + testsuite/tests/perf/should_run/T25055.stdout - testsuite/tests/perf/should_run/all.T - + testsuite/tests/perf/size/Makefile - + testsuite/tests/perf/size/all.T - + testsuite/tests/perf/size/javascript/Makefile - + testsuite/tests/perf/size/javascript/all.T - + testsuite/tests/perf/size/size_hello_artifact.hs - + testsuite/tests/perf/size/size_hello_obj.hs - + testsuite/tests/perf/size/size_hello_unicode.hs - testsuite/tests/plugins/Makefile - + testsuite/tests/plugins/T23821.hs - + testsuite/tests/plugins/T23832.hs - + testsuite/tests/plugins/T23832_invalid.hs - + testsuite/tests/plugins/T23832_invalid.stderr - + testsuite/tests/plugins/T25217.hs - + testsuite/tests/plugins/T25217.stdout - testsuite/tests/plugins/all.T - + testsuite/tests/plugins/defaulting-plugin/DefaultInterference.hs - + testsuite/tests/plugins/defaulting-plugin/DefaultInvalid.hs - testsuite/tests/plugins/defaulting-plugin/DefaultLifted.hs - + testsuite/tests/plugins/defaulting-plugin/DefaultMultiParam.hs - testsuite/tests/plugins/defaulting-plugin/defaulting-plugin.cabal - testsuite/tests/plugins/hole-fit-plugin/HoleFitPlugin.hs - testsuite/tests/plugins/hooks-plugin/Hooks/MetaPlugin.hs - + testsuite/tests/plugins/late-plugin/LatePlugin.hs - testsuite/tests/plugins/plugin-recomp/Makefile - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs - testsuite/tests/plugins/static-plugins.hs - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/plugins/test-defaulting-plugin-fail.stderr - testsuite/tests/plugins/test-defaulting-plugin.stderr - testsuite/tests/plugins/test-hole-plugin.stderr - + testsuite/tests/plugins/test-late-plugin.hs - + testsuite/tests/pmcheck/complete_sigs/T24326.hs - + testsuite/tests/pmcheck/complete_sigs/T24326.stderr - + testsuite/tests/pmcheck/complete_sigs/T25115.hs - + testsuite/tests/pmcheck/complete_sigs/T25115.stderr - + testsuite/tests/pmcheck/complete_sigs/T25115a.hs - testsuite/tests/pmcheck/complete_sigs/all.T - + testsuite/tests/pmcheck/should_compile/DoubleMatch.hs - + testsuite/tests/pmcheck/should_compile/DsIncompleteRecSel1.hs - + testsuite/tests/pmcheck/should_compile/DsIncompleteRecSel1.stderr - + testsuite/tests/pmcheck/should_compile/DsIncompleteRecSel2.hs - + testsuite/tests/pmcheck/should_compile/DsIncompleteRecSel2.stderr - + testsuite/tests/pmcheck/should_compile/DsIncompleteRecSel3.hs - + testsuite/tests/pmcheck/should_compile/DsIncompleteRecSel3.stderr - testsuite/tests/pmcheck/should_compile/T11195.hs - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T24234.hs - + testsuite/tests/pmcheck/should_compile/T24234.stderr - + testsuite/tests/pmcheck/should_compile/T24817.hs - + testsuite/tests/pmcheck/should_compile/T24824.hs - + testsuite/tests/pmcheck/should_compile/T24845.hs - + testsuite/tests/pmcheck/should_compile/T24891.hs - + testsuite/tests/pmcheck/should_compile/T24891.stderr - + testsuite/tests/pmcheck/should_compile/T25164.hs - + testsuite/tests/pmcheck/should_compile/T25164_aux.hs - + testsuite/tests/pmcheck/should_compile/T25257.hs - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - + testsuite/tests/pmcheck/should_compile/pmcOrPats.hs - + testsuite/tests/pmcheck/should_compile/pmcOrPats.stderr - testsuite/tests/polykinds/BadKindVar.stderr - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11480b.hs - testsuite/tests/polykinds/T11520.stderr - testsuite/tests/polykinds/T11523.hs - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T12055.hs - testsuite/tests/polykinds/T12055a.hs - testsuite/tests/polykinds/T12055a.stderr - testsuite/tests/polykinds/T13393.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14172.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T14710.stderr - testsuite/tests/polykinds/T14846.stderr - testsuite/tests/polykinds/T15592b.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16244.hs - testsuite/tests/polykinds/T16244.stderr - testsuite/tests/polykinds/T16245.hs - testsuite/tests/polykinds/T16245.stderr - testsuite/tests/polykinds/T16245a.hs - testsuite/tests/polykinds/T16245a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762b.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T24083.hs - + testsuite/tests/polykinds/T24083.stderr - + testsuite/tests/polykinds/T24083a.hs - + testsuite/tests/polykinds/T24686.hs - + testsuite/tests/polykinds/T24686.stderr - + testsuite/tests/polykinds/T24686a.hs - + testsuite/tests/polykinds/T24686a.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7151.stderr - testsuite/tests/polykinds/T7224.hs - testsuite/tests/polykinds/T7278.stderr - testsuite/tests/polykinds/T7433.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/TidyClassKinds.stderr - testsuite/tests/polykinds/all.T - + testsuite/tests/primops/should_compile/T24160_FMA.hs - testsuite/tests/primops/should_compile/all.T - testsuite/tests/primops/should_run/T10481.stderr - + testsuite/tests/primops/should_run/T24496.hs - + testsuite/tests/primops/should_run/T24496.stdout - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - + testsuite/tests/primops/should_run/UnalignedAddrPrimOps.hs - + testsuite/tests/primops/should_run/UnalignedAddrPrimOps.stdout - testsuite/tests/primops/should_run/all.T - + testsuite/tests/printer/AnnotationNoListTuplePuns.hs - + testsuite/tests/printer/AnnotationNoListTuplePuns.stdout - + testsuite/tests/printer/CaseAltComments.hs - + testsuite/tests/printer/DataDeclShort.hs - + testsuite/tests/printer/ListTuplePuns.hs - + testsuite/tests/printer/ListTuplePuns.script - + testsuite/tests/printer/ListTuplePuns.stderr - testsuite/tests/printer/Makefile - + testsuite/tests/printer/MatchPatComments.hs - testsuite/tests/printer/Ppr010.hs - testsuite/tests/printer/Ppr020.hs - testsuite/tests/printer/Ppr053.hs - testsuite/tests/printer/PprArrowLambdaCase.hs - testsuite/tests/printer/PprExportWarn.hs - + testsuite/tests/printer/PprInstanceWarn.hs - + testsuite/tests/printer/PprLetIn.hs - + testsuite/tests/printer/PprOrPat.hs - testsuite/tests/printer/PprUnicodeSyntax.hs - + testsuite/tests/printer/PrefixConComment.hs - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/T18791.stderr - + testsuite/tests/printer/T24237.hs - + testsuite/tests/printer/T24237.stderr - testsuite/tests/printer/Test20297.stdout - + testsuite/tests/printer/Test23465.hs - + testsuite/tests/printer/Test23885.hs - + testsuite/tests/printer/Test23887.hs - + testsuite/tests/printer/Test24159.hs - + testsuite/tests/printer/Test24533.hs - + testsuite/tests/printer/Test24533.stdout - + testsuite/tests/printer/Test24748.hs - + testsuite/tests/printer/Test24749.hs - + testsuite/tests/printer/Test24753.hs - + testsuite/tests/printer/Test24754.hs - + testsuite/tests/printer/Test24755.hs - + testsuite/tests/printer/Test24771.hs - + testsuite/tests/printer/Test25132.hs - + testsuite/tests/printer/Test25454.hs - + testsuite/tests/printer/Test25467.hs - testsuite/tests/printer/all.T - + testsuite/tests/process/.gitignore - + testsuite/tests/process/Makefile - + testsuite/tests/process/T1780.hs - + testsuite/tests/process/T1780.stdout - + testsuite/tests/process/T3231.hs - + testsuite/tests/process/T3231.stdout - + testsuite/tests/process/T3994.hs - + testsuite/tests/process/T3994.stdout - + testsuite/tests/process/T3994app.hs - + testsuite/tests/process/T4198.hs - + testsuite/tests/process/T4198.stdout - + testsuite/tests/process/T4198.stdout-mingw32 - + testsuite/tests/process/T4889.hs - + testsuite/tests/process/T4889.stdout - + testsuite/tests/process/T8343.hs - + testsuite/tests/process/T8343.stdout - + testsuite/tests/process/T9775/Makefile - + testsuite/tests/process/T9775/T9775_fail.hs - + testsuite/tests/process/T9775/T9775_fail.stdout - + testsuite/tests/process/T9775/T9775_good.hs - + testsuite/tests/process/T9775/T9775_good.stdout - + testsuite/tests/process/T9775/all.T - + testsuite/tests/process/T9775/main.c - + testsuite/tests/process/T9775/ok.c - + testsuite/tests/process/all.T - + testsuite/tests/process/exitminus1.c - + testsuite/tests/process/process001.hs - + testsuite/tests/process/process002.hs - + testsuite/tests/process/process003.hs - + testsuite/tests/process/process003.stdout - + testsuite/tests/process/process004.hs - + testsuite/tests/process/process004.stdout - + testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs - + testsuite/tests/process/process004.stdout-mingw32 - + testsuite/tests/process/process005.hs - + testsuite/tests/process/process005.stdin - + testsuite/tests/process/process005.stdout - + testsuite/tests/process/process006.hs - + testsuite/tests/process/process006.stderr - + testsuite/tests/process/process006.stdout - + testsuite/tests/process/process007.hs - + testsuite/tests/process/process007.stdout - + testsuite/tests/process/process007_fd.c - + testsuite/tests/process/process008.hs - + testsuite/tests/process/process008.stdout - + testsuite/tests/process/process009.hs - + testsuite/tests/process/process009.stdout - + testsuite/tests/process/process010.hs - + testsuite/tests/process/process010.stdout - + testsuite/tests/process/process010.stdout-i386-unknown-solaris2 - + testsuite/tests/process/process010.stdout-javascript-unknown-ghcjs - + testsuite/tests/process/process010.stdout-mingw32 - + testsuite/tests/process/process011.hs - + testsuite/tests/process/process011.stdout - + testsuite/tests/process/process011_c.c - + testsuite/tests/process/processT251.hs - + testsuite/tests/process/processT251.stdout - + testsuite/tests/profiling/perf/Makefile - + testsuite/tests/profiling/perf/T23103/all.T - + testsuite/tests/profiling/perf/T23103/info_table_map_perf.stderr - testsuite/tests/profiling/should_compile/T19894/Array.hs - testsuite/tests/profiling/should_compile/T19894/Fold.hs - testsuite/tests/profiling/should_compile/T19894/MArray.hs - testsuite/tests/profiling/should_compile/T19894/Ring.hs - testsuite/tests/profiling/should_compile/T19894/StreamD.hs - testsuite/tests/profiling/should_compile/T19894/StreamK.hs - testsuite/tests/profiling/should_compile/all.T - testsuite/tests/profiling/should_compile/prof-late-cc4.stderr - testsuite/tests/profiling/should_run/T12962.prof.sample - testsuite/tests/profiling/should_run/T2552.prof.sample - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/T5559.prof.sample - testsuite/tests/profiling/should_run/T5654-O0.prof.sample - testsuite/tests/profiling/should_run/T5654-O1.prof.sample - testsuite/tests/profiling/should_run/T5654b-O0.prof.sample - testsuite/tests/profiling/should_run/T5654b-O1.prof.sample - testsuite/tests/profiling/should_run/T680.prof.sample - testsuite/tests/profiling/should_run/T7275.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - testsuite/tests/profiling/should_run/caller-cc/all.T - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/profiling/should_run/callstack002.stderr - testsuite/tests/profiling/should_run/callstack002.stdout - testsuite/tests/profiling/should_run/ignore_scc.prof.sample - testsuite/tests/profiling/should_run/ioprof.prof.sample - testsuite/tests/profiling/should_run/prof-doc-fib.prof.sample - testsuite/tests/profiling/should_run/prof-doc-last.prof.sample - testsuite/tests/profiling/should_run/profinline001.prof.sample - + testsuite/tests/profiling/should_run/scc-prof-overloaded-calls001.hs - + testsuite/tests/profiling/should_run/scc-prof-overloaded-calls001.prof.sample - + testsuite/tests/profiling/should_run/scc-prof-overloaded-calls001.stdout - + testsuite/tests/profiling/should_run/scc-prof-overloaded-calls002.hs - + testsuite/tests/profiling/should_run/scc-prof-overloaded-calls002.prof.sample - + testsuite/tests/profiling/should_run/scc-prof-overloaded-calls002.stdout - + testsuite/tests/profiling/should_run/scc-prof-overloaded001.hs - + testsuite/tests/profiling/should_run/scc-prof-overloaded001.prof.sample - + testsuite/tests/profiling/should_run/scc-prof-overloaded001.stdout - + testsuite/tests/profiling/should_run/scc-prof-overloaded002.hs - + testsuite/tests/profiling/should_run/scc-prof-overloaded002.prof.sample - + testsuite/tests/profiling/should_run/scc-prof-overloaded002.stdout - testsuite/tests/profiling/should_run/scc001.prof.sample - testsuite/tests/profiling/should_run/scc002.prof.sample - testsuite/tests/profiling/should_run/scc003.prof.sample - testsuite/tests/profiling/should_run/scc005.prof.sample - testsuite/tests/profiling/should_run/staticcallstack001.stdout - testsuite/tests/profiling/should_run/staticcallstack002.stdout - testsuite/tests/profiling/should_run/toplevel_scc_1.prof.sample - testsuite/tests/programs/andy_cherry/GenUtils.hs - testsuite/tests/programs/andy_cherry/test.T - testsuite/tests/programs/galois_raytrace/Interval.hs - testsuite/tests/programs/seward-space-leak/test.T - testsuite/tests/qualifieddo/should_fail/qdofail002.stderr - testsuite/tests/qualifieddo/should_fail/qdofail004.stderr - testsuite/tests/quantified-constraints/T15231.stderr - testsuite/tests/quantified-constraints/T15290a.stderr - − testsuite/tests/quantified-constraints/T15290b.stderr - testsuite/tests/quantified-constraints/T15316.stderr - + testsuite/tests/quantified-constraints/T22238.hs - testsuite/tests/quantified-constraints/T23323.hs - + testsuite/tests/quantified-constraints/T25243.hs - + testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quantified-constraints/all.T - testsuite/tests/quasiquotation/Makefile - testsuite/tests/quasiquotation/all.T - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/T18263.stderr - testsuite/tests/quotes/T20893.stdout - + testsuite/tests/quotes/T24750.hs - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_localname.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TH_top_splice.stderr - testsuite/tests/quotes/TTH_top_splice.stderr - testsuite/tests/quotes/all.T - testsuite/tests/rebindable/RebindableFailA.stderr - + testsuite/tests/rebindable/T23147.hs - testsuite/tests/rebindable/all.T - + testsuite/tests/rebindable/pattern-fails.hs - + testsuite/tests/rebindable/pattern-fails.stdout - testsuite/tests/rebindable/rebindable6.stderr - + testsuite/tests/rebindable/simple-rec.hs - + testsuite/tests/rebindable/simple-rec.stdout - testsuite/tests/regalloc/all.T - testsuite/tests/regalloc/regalloc_unit_tests.hs - testsuite/tests/rename/prog001/rn037.hs - testsuite/tests/rename/prog006/all.T - testsuite/tests/rename/should_compile/ExplicitForAllRules1.hs - testsuite/tests/rename/should_compile/ExplicitForAllRules1.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/RecordWildCardDeprecation.hs - + testsuite/tests/rename/should_compile/RecordWildCardDeprecation.stderr - + testsuite/tests/rename/should_compile/RecordWildCardDeprecation_aux.hs - testsuite/tests/rename/should_compile/T13839.stdout - + testsuite/tests/rename/should_compile/T14032b.hs - + testsuite/tests/rename/should_compile/T14032b.stdout - + testsuite/tests/rename/should_compile/T14032d.hs - + testsuite/tests/rename/should_compile/T15681_PatSyn.hs - − testsuite/tests/rename/should_compile/T15798a.stderr - − testsuite/tests/rename/should_compile/T15798b.stderr - − testsuite/tests/rename/should_compile/T15798c.stderr - + testsuite/tests/rename/should_compile/T16618.hs - testsuite/tests/rename/should_compile/T17244A.hs - testsuite/tests/rename/should_compile/T17244A.stderr - testsuite/tests/rename/should_compile/T17244B.hs - testsuite/tests/rename/should_compile/T17244B.stderr - testsuite/tests/rename/should_compile/T17244C.hs - testsuite/tests/rename/should_compile/T17244C.stderr - testsuite/tests/rename/should_compile/T1972.stderr - testsuite/tests/rename/should_compile/T20472.stderr - − testsuite/tests/rename/should_compile/T20609.hs - − testsuite/tests/rename/should_compile/T20609.stderr - − testsuite/tests/rename/should_compile/T20609a.hs - − testsuite/tests/rename/should_compile/T20609a.stderr - − testsuite/tests/rename/should_compile/T20609b.hs - − testsuite/tests/rename/should_compile/T20609b.stderr - − testsuite/tests/rename/should_compile/T20609c.hs - − testsuite/tests/rename/should_compile/T20609c.stderr - − testsuite/tests/rename/should_compile/T20609d.hs - − testsuite/tests/rename/should_compile/T20609d.stderr - testsuite/tests/rename/should_compile/T22478a.hs - testsuite/tests/rename/should_compile/T22513a.stderr - testsuite/tests/rename/should_compile/T22513b.stderr - testsuite/tests/rename/should_compile/T22513c.stderr - testsuite/tests/rename/should_compile/T22513d.stderr - testsuite/tests/rename/should_compile/T22513e.stderr - testsuite/tests/rename/should_compile/T22513f.stderr - testsuite/tests/rename/should_compile/T22513g.hs - testsuite/tests/rename/should_compile/T22513g.stderr - testsuite/tests/rename/should_compile/T22513h.stderr - testsuite/tests/rename/should_compile/T22513i.stderr - + testsuite/tests/rename/should_compile/T22513j.hs - + testsuite/tests/rename/should_compile/T22513j.stderr - + testsuite/tests/rename/should_compile/T24037.hs - + testsuite/tests/rename/should_compile/T24084.hs - + testsuite/tests/rename/should_compile/T24084_A.hs - + testsuite/tests/rename/should_compile/T24084_B.hs - + testsuite/tests/rename/should_compile/T24621_normal.hs - + testsuite/tests/rename/should_compile/T24621_th.hs - + testsuite/tests/rename/should_compile/T24732.hs - + testsuite/tests/rename/should_compile/T24732.stdout - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/T4478.hs - testsuite/tests/rename/should_compile/T7167.hs - testsuite/tests/rename/should_compile/T7167.stderr - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_compile/rn025.hs - testsuite/tests/rename/should_compile/rn027.hs - testsuite/tests/rename/should_compile/rn031.hs - testsuite/tests/rename/should_compile/rn039.ghc.stderr - testsuite/tests/rename/should_compile/rn049.stderr - testsuite/tests/rename/should_compile/rn060.hs - + testsuite/tests/rename/should_fail/Or3.hs - + testsuite/tests/rename/should_fail/Or3.stderr - testsuite/tests/rename/should_fail/PackageImportsDisabled.stderr - testsuite/tests/rename/should_fail/RnDefaultSigFail.stderr - testsuite/tests/rename/should_fail/RnEmptyCaseFail.stderr - testsuite/tests/rename/should_fail/RnEmptyStatementGroup1.stderr - + testsuite/tests/rename/should_fail/RnFail059.hs - + testsuite/tests/rename/should_fail/RnFail059.hs-boot - + testsuite/tests/rename/should_fail/RnFail059_aux.hs - testsuite/tests/rename/should_fail/RnPatternSynonymFail.stderr - testsuite/tests/rename/should_fail/RnStaticPointersFail02.stderr - testsuite/tests/rename/should_fail/RnUnexpectedStandaloneDeriving.stderr - testsuite/tests/rename/should_fail/T10781.stderr - testsuite/tests/rename/should_fail/T11071.stderr - testsuite/tests/rename/should_fail/T11071a.hs - testsuite/tests/rename/should_fail/T11071a.stderr - testsuite/tests/rename/should_fail/T11663.stderr - − testsuite/tests/rename/should_fail/T12686.hs - − testsuite/tests/rename/should_fail/T12686.stderr - + testsuite/tests/rename/should_fail/T12686a.hs - + testsuite/tests/rename/should_fail/T12686a.stderr - + testsuite/tests/rename/should_fail/T12686b.hs - + testsuite/tests/rename/should_fail/T12686b.stderr - + testsuite/tests/rename/should_fail/T12686c.hs - + testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T13568.stderr - + testsuite/tests/rename/should_fail/T14032c.hs - + testsuite/tests/rename/should_fail/T14032c.stderr - + testsuite/tests/rename/should_fail/T14032f.hs - + testsuite/tests/rename/should_fail/T14032f.stderr - testsuite/tests/rename/should_fail/T15487.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - + testsuite/tests/rename/should_fail/T17594b.hs - + testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T18740b.stderr - testsuite/tests/rename/should_fail/T19843c.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T19843k.stderr - testsuite/tests/rename/should_fail/T20147.stderr - testsuite/tests/rename/should_fail/T21605a.stderr - testsuite/tests/rename/should_fail/T21605b.stderr - testsuite/tests/rename/should_fail/T22478b.hs - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478d.hs - testsuite/tests/rename/should_fail/T22478d.stderr - testsuite/tests/rename/should_fail/T22478e.hs - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.hs - + testsuite/tests/rename/should_fail/T23501_fail.hs - + testsuite/tests/rename/should_fail/T23501_fail.stderr - + testsuite/tests/rename/should_fail/T23501_fail_ext.hs - + testsuite/tests/rename/should_fail/T23501_fail_ext.stderr - + testsuite/tests/rename/should_fail/T23570.hs - + testsuite/tests/rename/should_fail/T23570.stderr - + testsuite/tests/rename/should_fail/T23570_aux.hs - + testsuite/tests/rename/should_fail/T23570b.hs - + testsuite/tests/rename/should_fail/T23570b.stderr - + testsuite/tests/rename/should_fail/T23740a.hs - + testsuite/tests/rename/should_fail/T23740a.stderr - + testsuite/tests/rename/should_fail/T23740b.hs - + testsuite/tests/rename/should_fail/T23740b.stderr - + testsuite/tests/rename/should_fail/T23740c.hs - + testsuite/tests/rename/should_fail/T23740c.stderr - + testsuite/tests/rename/should_fail/T23740d.hs - + testsuite/tests/rename/should_fail/T23740d.stderr - + testsuite/tests/rename/should_fail/T23740e.hs - + testsuite/tests/rename/should_fail/T23740e.stderr - + testsuite/tests/rename/should_fail/T23740f.hs - + testsuite/tests/rename/should_fail/T23740f.stderr - + testsuite/tests/rename/should_fail/T23740g.hs - + testsuite/tests/rename/should_fail/T23740g.stderr - + testsuite/tests/rename/should_fail/T23740h.hs - + testsuite/tests/rename/should_fail/T23740h.stderr - + testsuite/tests/rename/should_fail/T23740i.hs - + testsuite/tests/rename/should_fail/T23740i.stderr - + testsuite/tests/rename/should_fail/T23740j.hs - + testsuite/tests/rename/should_fail/T23740j.stderr - + testsuite/tests/rename/should_fail/T25056.hs - + testsuite/tests/rename/should_fail/T25056.stderr - + testsuite/tests/rename/should_fail/T25056a.hs - + testsuite/tests/rename/should_fail/T25056b.hs - + testsuite/tests/rename/should_fail/T25437.hs - + testsuite/tests/rename/should_fail/T25437.stderr - testsuite/tests/rename/should_fail/T2901.stderr - testsuite/tests/rename/should_fail/T3265.stderr - testsuite/tests/rename/should_fail/T5001b.stderr - testsuite/tests/rename/should_fail/T5657.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rename/should_fail/rn_dup.stderr - testsuite/tests/rename/should_fail/rnfail026.stderr - testsuite/tests/rename/should_fail/rnfail029.stderr - testsuite/tests/rename/should_fail/rnfail040.stderr - testsuite/tests/rename/should_fail/rnfail044.stderr - testsuite/tests/rename/should_fail/rnfail051.hs - testsuite/tests/rename/should_fail/rnfail051.stderr - testsuite/tests/rename/should_fail/rnfail052.stderr - testsuite/tests/rename/should_fail/rnfail053.stderr - testsuite/tests/rename/should_fail/rnfail055.stderr - testsuite/tests/rename/should_fail/rnfail056.stderr - + testsuite/tests/rename/should_fail/rnfail059.stderr - + testsuite/tests/rep-poly/LevPolyDataToTag1.hs - + testsuite/tests/rep-poly/LevPolyDataToTag2.hs - + testsuite/tests/rep-poly/LevPolyDataToTag2.stderr - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyMcGuard.stderr - testsuite/tests/rep-poly/RepPolyNPlusK.stderr - testsuite/tests/rep-poly/RepPolyPatSynRes.stderr - testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T12709.stderr - testsuite/tests/rep-poly/T13233.stderr - testsuite/tests/rep-poly/T20363_show_co.stderr - testsuite/tests/rep-poly/T21906.stderr - testsuite/tests/rep-poly/T23153.stderr - + testsuite/tests/rep-poly/T23153b.hs - testsuite/tests/rep-poly/T23154.stderr - + testsuite/tests/rep-poly/T23883a.hs - + testsuite/tests/rep-poly/T23883a.stderr - + testsuite/tests/rep-poly/T23883b.hs - + testsuite/tests/rep-poly/T23883b.stderr - + testsuite/tests/rep-poly/T23883c.hs - + testsuite/tests/rep-poly/T23883c.stderr - + testsuite/tests/rep-poly/T23903.hs - + testsuite/tests/rep-poly/T23903.stderr - testsuite/tests/rep-poly/all.T - testsuite/tests/roles/should_compile/Roles1.hs - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_compile/all.T - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/roles/should_fail/Roles12.stderr - testsuite/tests/roles/should_fail/Roles5.stderr - testsuite/tests/roles/should_fail/RolesIArray.stderr - testsuite/tests/roles/should_fail/T23252.stderr - testsuite/tests/roles/should_fail/T8773.stderr - testsuite/tests/roles/should_fail/T9204.stderr - + testsuite/tests/rts/IOManager.hsc - + testsuite/tests/rts/IOManager.stdout - testsuite/tests/rts/Makefile - testsuite/tests/rts/T10672/Makefile - testsuite/tests/rts/T10672/all.T - testsuite/tests/rts/T12497.hs - testsuite/tests/rts/T13287/all.T - testsuite/tests/rts/T13832.stderr - testsuite/tests/rts/T13894.hs - + testsuite/tests/rts/T14497-compact.hs - + testsuite/tests/rts/T14497-compact.stdout - testsuite/tests/rts/T14497.hs - testsuite/tests/rts/T1791/Makefile - testsuite/tests/rts/T18623/all.T - + testsuite/tests/rts/T20201a.hs - + testsuite/tests/rts/T20201a.stderr - + testsuite/tests/rts/T20201b.hs - + testsuite/tests/rts/T20201b.stderr - + testsuite/tests/rts/T22012.hs - + testsuite/tests/rts/T22012.stdout - + testsuite/tests/rts/T22012_c.c - testsuite/tests/rts/T23221.hs - + testsuite/tests/rts/T24142.hs - + testsuite/tests/rts/T24142.stdout - + testsuite/tests/rts/T25198/T25198.hs - + testsuite/tests/rts/T25198/T25198.stderr - + testsuite/tests/rts/T25198/all.T - + testsuite/tests/rts/T25232.hs - + testsuite/tests/rts/T25280.hs - + testsuite/tests/rts/T25560.hs - testsuite/tests/rts/T2783.stderr - testsuite/tests/rts/T5644/all.T - testsuite/tests/rts/T7037_main.c - testsuite/tests/rts/T7040_ghci_c.c - testsuite/tests/rts/T7087.stderr - testsuite/tests/rts/T7636.stderr - testsuite/tests/rts/all.T - testsuite/tests/rts/atomicinc.c - testsuite/tests/rts/cloneStackLib.c - + testsuite/tests/rts/continuations/T23513.hs - + testsuite/tests/rts/continuations/T23513.stdout - testsuite/tests/rts/continuations/all.T - testsuite/tests/rts/continuations/cont_missing_prompt_err.stderr - testsuite/tests/rts/decodeMyStack.stdout - testsuite/tests/rts/decodeMyStack_underflowFrames.hs - + testsuite/tests/rts/ipe/IpeStats/Fold.hs - + testsuite/tests/rts/ipe/IpeStats/Makefile - + testsuite/tests/rts/ipe/IpeStats/all.T - + testsuite/tests/rts/ipe/T24005/all.T - + testsuite/tests/rts/ipe/T24005/t24005.hs - + testsuite/tests/rts/ipe/T24005/t24005.stdout - testsuite/tests/rts/ipe/all.T - testsuite/tests/rts/ipe/ipeEventLog.stderr - testsuite/tests/rts/ipe/ipeEventLog_fromMap.c - testsuite/tests/rts/ipe/ipeEventLog_fromMap.stderr - testsuite/tests/rts/ipe/ipeMap.c - testsuite/tests/rts/ipe/ipe_lib.c - testsuite/tests/rts/linker/Makefile - testsuite/tests/rts/linker/T11223/Makefile - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32 - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32 - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32 - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32 - testsuite/tests/rts/linker/T11223/all.T - + testsuite/tests/rts/linker/T24171/Lib.hs - + testsuite/tests/rts/linker/T24171/Makefile - + testsuite/tests/rts/linker/T24171/T24171.stdout - + testsuite/tests/rts/linker/T24171/all.T - + testsuite/tests/rts/linker/T24171/main.c - + testsuite/tests/rts/linker/T25191.hs - + testsuite/tests/rts/linker/T25191.stdout - + testsuite/tests/rts/linker/T25191_foo1.c - + testsuite/tests/rts/linker/T25191_foo2.c - testsuite/tests/rts/linker/T2615.hs - − testsuite/tests/rts/linker/T7072-main.c - testsuite/tests/rts/linker/T7072-obj.c → testsuite/tests/rts/linker/T7072.c - testsuite/tests/rts/linker/all.T - + testsuite/tests/rts/linker/load-object.c - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/Makefile - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/all.T - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.c - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.stdout - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/obj.c - + testsuite/tests/rts/linker/reloc-none.c - + testsuite/tests/rts/linker/reloc-none.stderr - testsuite/tests/rts/linker/unload_multiple_objs/linker_unload_multiple_objs.c - testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c - testsuite/tests/rts/testwsdeque.c - testsuite/tests/runghc/Makefile - testsuite/tests/runghc/T7859.stderr - testsuite/tests/runghc/T7859.stderr-mingw32 - testsuite/tests/runghc/all.T - testsuite/tests/safeHaskell/check/Check01_A.hs - testsuite/tests/safeHaskell/check/Check02_A.hs - testsuite/tests/safeHaskell/check/Check03_A.hs - testsuite/tests/safeHaskell/check/Check04_A.hs - testsuite/tests/safeHaskell/check/CheckA.hs - testsuite/tests/safeHaskell/check/CheckB_Aux.hs - testsuite/tests/safeHaskell/check/all.T - testsuite/tests/safeHaskell/check/pkg01/ImpSafe01.stderr - testsuite/tests/safeHaskell/check/pkg01/ImpSafe04.stderr - testsuite/tests/safeHaskell/check/pkg01/all.T - testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout - testsuite/tests/safeHaskell/flags/all.T - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p16.stderr - testsuite/tests/safeHaskell/ghci/p4.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang09.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang10.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang12.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang17.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang18.hs - testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/saks/should_compile/all.T - testsuite/tests/saks/should_compile/saks018.hs - testsuite/tests/saks/should_compile/saks021.hs - testsuite/tests/saks/should_compile/saks030.hs - testsuite/tests/saks/should_compile/saks032.hs - testsuite/tests/saks/should_fail/T16722.stderr - testsuite/tests/saks/should_fail/T20916.stderr - testsuite/tests/saks/should_fail/all.T - + testsuite/tests/saks/should_fail/saks018-fail.hs - + testsuite/tests/saks/should_fail/saks018-fail.stderr - + testsuite/tests/saks/should_fail/saks021-fail.hs - + testsuite/tests/saks/should_fail/saks021-fail.stderr - testsuite/tests/saks/should_fail/saks_fail001.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/DocsInHiFileTH.hs - testsuite/tests/showIface/DocsInHiFileTH.stdout - testsuite/tests/showIface/HaddockIssue849.stdout - testsuite/tests/showIface/HaddockOpts.stdout - + testsuite/tests/showIface/HaddockSpanIssueT24378.hs - + testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/LanguageExts.stdout - testsuite/tests/showIface/MagicHashInHaddocks.stdout - testsuite/tests/showIface/Makefile - testsuite/tests/showIface/NoExportList.stdout - testsuite/tests/showIface/Orphans.stdout - testsuite/tests/showIface/PragmaDocs.stdout - testsuite/tests/showIface/ReExports.stdout - testsuite/tests/showIface/all.T - + testsuite/tests/simd/should_run/Simd009b.hs - + testsuite/tests/simd/should_run/Simd009c.hs - testsuite/tests/unboxedsums/T22187.hs → testsuite/tests/simd/should_run/T22187.hs - testsuite/tests/unboxedsums/T22187_run.hs → testsuite/tests/simd/should_run/T22187_run.hs - + testsuite/tests/simd/should_run/T22187_run.stdout - + testsuite/tests/simd/should_run/T25062_V16.hs - + testsuite/tests/simd/should_run/T25062_V16.stdout - + testsuite/tests/simd/should_run/T25062_V32.hs - + testsuite/tests/simd/should_run/T25062_V32.stdout - + testsuite/tests/simd/should_run/T25062_V64.hs - + testsuite/tests/simd/should_run/T25062_V64.stdout - + testsuite/tests/simd/should_run/T25169.hs - + testsuite/tests/simd/should_run/T25169.stdout - + testsuite/tests/simd/should_run/T25455.hs - + testsuite/tests/simd/should_run/T25455.stdout - + testsuite/tests/simd/should_run/T25486.hs - + testsuite/tests/simd/should_run/T25486.stdout - + testsuite/tests/simd/should_run/T25561.hs - + testsuite/tests/simd/should_run/T25561.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - + testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/int16x8_basic.hs - + testsuite/tests/simd/should_run/int16x8_basic.stdout - + testsuite/tests/simd/should_run/int16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/int16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/int32x4_basic.hs - + testsuite/tests/simd/should_run/int32x4_basic.stdout - + testsuite/tests/simd/should_run/int32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/int32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/int64x2_basic.hs - + testsuite/tests/simd/should_run/int64x2_basic.stdout - + testsuite/tests/simd/should_run/int64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/int64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/int8x16_basic.hs - + testsuite/tests/simd/should_run/int8x16_basic.stdout - + testsuite/tests/simd/should_run/int8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/int8x16_basic_baseline.stdout - + testsuite/tests/simd/should_run/simd000.hs - + testsuite/tests/simd/should_run/simd000.stdout - + testsuite/tests/simd/should_run/simd001.hs - + testsuite/tests/simd/should_run/simd001.stdout - + testsuite/tests/simd/should_run/simd002.hs - + testsuite/tests/simd/should_run/simd002.stdout - + testsuite/tests/simd/should_run/simd003.hs - + testsuite/tests/simd/should_run/simd003.stdout - + testsuite/tests/simd/should_run/simd004.hs - + testsuite/tests/simd/should_run/simd004.stdout - + testsuite/tests/simd/should_run/simd005.hs - + testsuite/tests/simd/should_run/simd005.stdout - + testsuite/tests/simd/should_run/simd006.hs - + testsuite/tests/simd/should_run/simd006.stdout - + testsuite/tests/simd/should_run/simd007.hs - + testsuite/tests/simd/should_run/simd007.stdout - + testsuite/tests/simd/should_run/simd008.hs - + testsuite/tests/simd/should_run/simd008.stdout - + testsuite/tests/simd/should_run/simd009.hs - + testsuite/tests/simd/should_run/simd010.hs - + testsuite/tests/simd/should_run/simd010.stdout - + testsuite/tests/simd/should_run/simd011.hs - + testsuite/tests/simd/should_run/simd011.stdout - + testsuite/tests/simd/should_run/simd012.hs - + testsuite/tests/simd/should_run/simd012.stdout - + testsuite/tests/simd/should_run/simd013.hs - + testsuite/tests/simd/should_run/simd013.stdout - + testsuite/tests/simd/should_run/simd013C.c - + testsuite/tests/simd/should_run/simd014.hs - + testsuite/tests/simd/should_run/simd014.stdout - + testsuite/tests/simd/should_run/simd014Cmm.cmm - + testsuite/tests/simd/should_run/simd_insert.hs - + testsuite/tests/simd/should_run/simd_insert.stdout - + testsuite/tests/simd/should_run/simd_insert_array.hs - + testsuite/tests/simd/should_run/simd_insert_array.stdout - + testsuite/tests/simd/should_run/simd_insert_array_baseline.hs - + testsuite/tests/simd/should_run/simd_insert_array_baseline.stdout - + testsuite/tests/simd/should_run/simd_insert_baseline.hs - + testsuite/tests/simd/should_run/simd_insert_baseline.stdout - + testsuite/tests/simd/should_run/word16x8_basic.hs - + testsuite/tests/simd/should_run/word16x8_basic.stdout - + testsuite/tests/simd/should_run/word16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/word16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/word32x4_basic.hs - + testsuite/tests/simd/should_run/word32x4_basic.stdout - + testsuite/tests/simd/should_run/word32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/word32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/word64x2_basic.hs - + testsuite/tests/simd/should_run/word64x2_basic.stdout - + testsuite/tests/simd/should_run/word64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/word64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/word8x16_basic.hs - + testsuite/tests/simd/should_run/word8x16_basic.stdout - + testsuite/tests/simd/should_run/word8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/word8x16_basic_baseline.stdout - testsuite/tests/simplCore/T9646/Main.hs - testsuite/tests/simplCore/T9646/StrictPrim.hs - testsuite/tests/simplCore/prog003/simplCore.oneShot.stderr → testsuite/tests/simplCore/prog003/simplCore-oneShot.stderr - testsuite/tests/simplCore/prog003/simplCore.oneShot.stdout → testsuite/tests/simplCore/prog003/simplCore-oneShot.stdout - testsuite/tests/simplCore/prog003/test.T - + testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.hs - + testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr - + testsuite/tests/simplCore/should_compile/ExposeOverloaded.hs - + testsuite/tests/simplCore/should_compile/ExposeOverloaded.stderr - testsuite/tests/simplCore/should_compile/Makefile - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T12076sat.hs - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T12877.hs - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T13543.stderr - + testsuite/tests/simplCore/should_compile/T14003.hs - + testsuite/tests/simplCore/should_compile/T14003.stderr - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15056.stderr - testsuite/tests/simplCore/should_compile/T15445.stderr - testsuite/tests/simplCore/should_compile/T15631.hs - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T16038/Makefile - testsuite/tests/simplCore/should_compile/T16254.hs - testsuite/tests/simplCore/should_compile/T17409.hs - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T17966.hs - testsuite/tests/simplCore/should_compile/T18013.hs - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18231.stderr - testsuite/tests/simplCore/should_compile/T18355.hs - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T18995.stderr - testsuite/tests/simplCore/should_compile/T19790.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T20103.stderr - testsuite/tests/simplCore/should_compile/T21286.stderr - + testsuite/tests/simplCore/should_compile/T21348.hs - testsuite/tests/simplCore/should_compile/T21694.hs - testsuite/tests/simplCore/should_compile/T21851.stderr - testsuite/tests/simplCore/should_compile/T21851_2.stderr - + testsuite/tests/simplCore/should_compile/T21917.hs - + testsuite/tests/simplCore/should_compile/T21917.stderr - testsuite/tests/simplCore/should_compile/T22097.stderr - + testsuite/tests/simplCore/should_compile/T22309.hs - + testsuite/tests/simplCore/should_compile/T22309.stderr - testsuite/tests/simplCore/should_compile/T22317.hs - testsuite/tests/simplCore/should_compile/T22375.hs - testsuite/tests/simplCore/should_compile/T22375.stderr - + testsuite/tests/simplCore/should_compile/T22375DataFamily.hs - + testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - + testsuite/tests/simplCore/should_compile/T22404.hs - + testsuite/tests/simplCore/should_compile/T22404.stderr - testsuite/tests/simplCore/should_compile/T22428.stderr - testsuite/tests/simplCore/should_compile/T22611.stderr - + testsuite/tests/simplCore/should_compile/T23083.hs - + testsuite/tests/simplCore/should_compile/T23083.stderr - + testsuite/tests/simplCore/should_compile/T23209.hs - + testsuite/tests/simplCore/should_compile/T23209_Aux.hs - testsuite/tests/simplCore/should_compile/T23307.stderr - testsuite/tests/simplCore/should_compile/T23307a.stderr - testsuite/tests/simplCore/should_compile/T23491a.stderr - + testsuite/tests/simplCore/should_compile/T23864.hs - + testsuite/tests/simplCore/should_compile/T23922a.hs - + testsuite/tests/simplCore/should_compile/T23938.hs - + testsuite/tests/simplCore/should_compile/T23938A.hs - + testsuite/tests/simplCore/should_compile/T23952.hs - + testsuite/tests/simplCore/should_compile/T23952a.hs - + testsuite/tests/simplCore/should_compile/T24014.hs - + testsuite/tests/simplCore/should_compile/T24029.hs - + testsuite/tests/simplCore/should_compile/T24229a.hs - + testsuite/tests/simplCore/should_compile/T24229a.stderr - + testsuite/tests/simplCore/should_compile/T24229b.hs - + testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T24370.hs - + testsuite/tests/simplCore/should_compile/T24551.hs - + testsuite/tests/simplCore/should_compile/T24625.hs - + testsuite/tests/simplCore/should_compile/T24662.hs - + testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T24725a.hs - + testsuite/tests/simplCore/should_compile/T24725a.stderr - + testsuite/tests/simplCore/should_compile/T24726.hs - + testsuite/tests/simplCore/should_compile/T24726.stderr - + testsuite/tests/simplCore/should_compile/T24768.hs - + testsuite/tests/simplCore/should_compile/T24770.hs - + testsuite/tests/simplCore/should_compile/T24808.hs - + testsuite/tests/simplCore/should_compile/T24808.stderr - + testsuite/tests/simplCore/should_compile/T24944.hs - + testsuite/tests/simplCore/should_compile/T24944a.hs - + testsuite/tests/simplCore/should_compile/T25033.hs - + testsuite/tests/simplCore/should_compile/T25160.hs - + testsuite/tests/simplCore/should_compile/T25160.stderr - + testsuite/tests/simplCore/should_compile/T25197.hs - + testsuite/tests/simplCore/should_compile/T25197.stderr - + testsuite/tests/simplCore/should_compile/T25197_TH.hs - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5327.hs - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8331.stderr - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/simpl017.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplCore/should_fail/T7411.stderr - + testsuite/tests/simplCore/should_run/AppIsHNF.hs - + testsuite/tests/simplCore/should_run/AppIsHNF.stderr - testsuite/tests/simplCore/should_run/T16066.stderr - testsuite/tests/simplCore/should_run/T16893/T16893.stderr - + testsuite/tests/simplCore/should_run/T20749.hs - + testsuite/tests/simplCore/should_run/T20749.stdout - testsuite/tests/simplCore/should_run/T22448.hs - + testsuite/tests/simplCore/should_run/T24725.hs - + testsuite/tests/simplCore/should_run/T24725.stdout - + testsuite/tests/simplCore/should_run/T25096.hs - + testsuite/tests/simplCore/should_run/T25096.stdout - testsuite/tests/simplCore/should_run/T457.stderr - testsuite/tests/simplCore/should_run/T5587.stderr - testsuite/tests/simplCore/should_run/T5625.stderr - testsuite/tests/simplCore/should_run/T7924.stderr - testsuite/tests/simplCore/should_run/all.T - testsuite/tests/simplCore/should_run/simplrun009.hs - + testsuite/tests/simplStg/should_compile/T15226b.hs - + testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - + testsuite/tests/simplStg/should_compile/T24806.hs - + testsuite/tests/simplStg/should_compile/T24806.stderr - testsuite/tests/simplStg/should_compile/all.T - testsuite/tests/simplStg/should_compile/inferTags002.stderr - + testsuite/tests/simplStg/should_compile/inferTags003.hs - + testsuite/tests/simplStg/should_compile/inferTags003.stderr - + testsuite/tests/simplStg/should_compile/inferTags004.hs - + testsuite/tests/simplStg/should_compile/inferTags004.stderr - + testsuite/tests/simplStg/should_run/T23783.hs - + testsuite/tests/simplStg/should_run/T23783a.hs - testsuite/tests/simplStg/should_run/T9291.hs - testsuite/tests/simplStg/should_run/all.T - − testsuite/tests/stranal/should_compile/T10069.stderr - − testsuite/tests/stranal/should_compile/T10482.stderr - − testsuite/tests/stranal/should_compile/T10482a.stderr - − testsuite/tests/stranal/should_compile/T13143.stderr - − testsuite/tests/stranal/should_compile/T16029.stdout - − testsuite/tests/stranal/should_compile/T18982.stderr - − testsuite/tests/stranal/should_compile/T20510.stderr - − testsuite/tests/stranal/should_compile/T20663.stderr - − testsuite/tests/stranal/should_compile/T21128.stderr - − testsuite/tests/stranal/should_compile/all.T - − testsuite/tests/stranal/should_run/T12368.stderr - − testsuite/tests/stranal/should_run/T12368a.stderr - − testsuite/tests/stranal/should_run/T13380.stderr - − testsuite/tests/stranal/should_run/T13380d.stderr - − testsuite/tests/stranal/should_run/T13380e.stderr - − testsuite/tests/stranal/should_run/T23208.stderr - − testsuite/tests/stranal/should_run/all.T - − testsuite/tests/stranal/should_run/strun002.stderr - − testsuite/tests/stranal/sigs/FacState.stderr - − testsuite/tests/stranal/sigs/HyperStrUse.stderr - − testsuite/tests/stranal/sigs/NewtypeArity.stderr - − testsuite/tests/stranal/sigs/StrAnalExample.stderr - − testsuite/tests/stranal/sigs/T12370.stderr - − testsuite/tests/stranal/sigs/T13331.stderr - − testsuite/tests/stranal/sigs/T13380c.stderr - − testsuite/tests/stranal/sigs/T17932.stderr - − testsuite/tests/stranal/sigs/T18086.stderr - − testsuite/tests/stranal/sigs/T20746.stderr - − testsuite/tests/stranal/sigs/T20746b.stderr - − testsuite/tests/stranal/sigs/T21717.stderr - − testsuite/tests/stranal/sigs/T21754.stderr - − testsuite/tests/stranal/sigs/T8569.stderr - − testsuite/tests/stranal/sigs/T8598.stderr - − testsuite/tests/stranal/sigs/all.T - testsuite/tests/tcplugins/CtIdPlugin.hs - testsuite/tests/tcplugins/EmitWantedPlugin.hs - testsuite/tests/tcplugins/RewritePlugin.hs - testsuite/tests/typecheck/should_compile/T11462.hs → testsuite/tests/tcplugins/T11462.hs - testsuite/tests/typecheck/should_compile/T11462_Plugin.hs → testsuite/tests/tcplugins/T11462_Plugin.hs - testsuite/tests/typecheck/should_compile/T11525.hs → testsuite/tests/tcplugins/T11525.hs - testsuite/tests/typecheck/should_compile/T11525_Plugin.hs → testsuite/tests/tcplugins/T11525_Plugin.hs - testsuite/tests/tcplugins/TyFamPlugin.hs - testsuite/tests/tcplugins/all.T - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - + testsuite/tests/th/ListTuplePunsTH.hs - + testsuite/tests/th/ListTuplePunsTH.script - + testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10267.stderr - testsuite/tests/th/T10279.hs - testsuite/tests/th/T10279.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10796b.stderr - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.hs - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T11463.stdout - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12411.stderr - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - + testsuite/tests/th/T14032a.hs - + testsuite/tests/th/T14032e.hs - + testsuite/tests/th/T14032e.stderr - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14204.stderr - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15270A.stderr - testsuite/tests/th/T15270B.stderr - testsuite/tests/th/T15321.stderr - testsuite/tests/th/T15360b.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15433b.hs - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16133.stderr - testsuite/tests/th/T16180.hs - testsuite/tests/th/T16326_TH.stderr - testsuite/tests/th/T16895a.stderr - testsuite/tests/th/T16895b.stderr - testsuite/tests/th/T16895c.stderr - testsuite/tests/th/T16895d.stderr - testsuite/tests/th/T16895e.stderr - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T16980.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17688a.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740c.stderr - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T19709d.stderr - testsuite/tests/th/T20185.stdout - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - + testsuite/tests/th/T21077.hs - + testsuite/tests/th/T21077.stderr - + testsuite/tests/th/T21077_Lib.hs - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - + testsuite/tests/th/T23309.c - + testsuite/tests/th/T23309.hs - + testsuite/tests/th/T23309.stderr - + testsuite/tests/th/T23309A.hs - + testsuite/tests/th/T23378.hs - + testsuite/tests/th/T23378.stderr - + testsuite/tests/th/T23378A.hs - + testsuite/tests/th/T23719.hs - + testsuite/tests/th/T23719.stderr - + testsuite/tests/th/T23748.hs - + testsuite/tests/th/T23796.hs - + testsuite/tests/th/T23829_hasty.hs - + testsuite/tests/th/T23829_hasty.stderr - + testsuite/tests/th/T23829_hasty_b.hs - + testsuite/tests/th/T23829_hasty_b.stderr - + testsuite/tests/th/T23829_tardy.ghc.stderr - + testsuite/tests/th/T23829_tardy.hs - + testsuite/tests/th/T23829_tardy.stdout - + testsuite/tests/th/T23829_timely.hs - + testsuite/tests/th/T23927.hs - + testsuite/tests/th/T23927.stdout - + testsuite/tests/th/T23954.hs - + testsuite/tests/th/T23954.stdout - + testsuite/tests/th/T23962.hs - + testsuite/tests/th/T23962.stdout - + testsuite/tests/th/T23968.hs - + testsuite/tests/th/T23968.stdout - + testsuite/tests/th/T23971.hs - + testsuite/tests/th/T23971.stdout - + testsuite/tests/th/T23986.hs - + testsuite/tests/th/T23986.stdout - + testsuite/tests/th/T24046.hs - + testsuite/tests/th/T24074.hs - + testsuite/tests/th/T24074.stderr - + testsuite/tests/th/T24111.hs - + testsuite/tests/th/T24111.stdout - + testsuite/tests/th/T24190.hs - + testsuite/tests/th/T24190.stdout - + testsuite/tests/th/T24299.hs - + testsuite/tests/th/T24299.stderr - + testsuite/tests/th/T24308.hs - + testsuite/tests/th/T24308.stdout - + testsuite/tests/th/T24557a.hs - + testsuite/tests/th/T24557a.stderr - + testsuite/tests/th/T24557b.hs - + testsuite/tests/th/T24557b.stderr - + testsuite/tests/th/T24557c.hs - + testsuite/tests/th/T24557c.stderr - + testsuite/tests/th/T24557d.hs - + testsuite/tests/th/T24557d.stderr - + testsuite/tests/th/T24557e.hs - + testsuite/tests/th/T24559.hs - + testsuite/tests/th/T24571.hs - + testsuite/tests/th/T24572a.hs - + testsuite/tests/th/T24572b.hs - + testsuite/tests/th/T24572b.stderr - + testsuite/tests/th/T24572c.hs - + testsuite/tests/th/T24572c.stderr - + testsuite/tests/th/T24572d.hs - + testsuite/tests/th/T24702a.hs - + testsuite/tests/th/T24702b.hs - + testsuite/tests/th/T24837.hs - + testsuite/tests/th/T24837.stderr - + testsuite/tests/th/T24894.hs - + testsuite/tests/th/T24894.stderr - + testsuite/tests/th/T24911.hs - + testsuite/tests/th/T24911.stderr - + testsuite/tests/th/T24997.hs - + testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25083.hs - + testsuite/tests/th/T25083.stdout - + testsuite/tests/th/T25083_A.hs - + testsuite/tests/th/T25083_B.hs - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - + testsuite/tests/th/T25209.hs - + testsuite/tests/th/T25209.stderr - + testsuite/tests/th/T25252.hs - + testsuite/tests/th/T25252B.hs - + testsuite/tests/th/T25252_c.c - + testsuite/tests/th/T25256.hs - + testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T5362.stderr - testsuite/tests/th/T5508.hs - testsuite/tests/th/T5508.stderr - testsuite/tests/th/T5700a.hs - testsuite/tests/th/T5976.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7276.stderr - testsuite/tests/th/T7276a.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8333.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.hs - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T8987.stderr - testsuite/tests/th/T9064.stderr - testsuite/tests/th/T9084.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_ExplicitForAllRules.stdout - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - + testsuite/tests/th/TH_MultilineStrings.hs - + testsuite/tests/th/TH_MultilineStrings.stdout - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PprStar.stderr - testsuite/tests/th/TH_Promoted1Tuple.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles1.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_exn1.stderr - testsuite/tests/th/TH_exn2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_namePackage.stdout - testsuite/tests/th/TH_recursiveDo.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyDecl2.stderr - testsuite/tests/th/TH_reifyExplicitForAllFams.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_spliceD1_Lib.hs - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_typed5.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/TH_viewPatPrint.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - + testsuite/tests/th/should_compile/T24081/Main.hs - + testsuite/tests/th/should_compile/T24081/Makefile - + testsuite/tests/th/should_compile/T24081/T24081.stderr - + testsuite/tests/th/should_compile/T24081/TH.hs - + testsuite/tests/th/should_compile/T24081/all.T - + testsuite/tests/th/should_compile/T24870/Def.hs - + testsuite/tests/th/should_compile/T24870/Use.hs - + testsuite/tests/th/should_compile/T24870/all.T - + testsuite/tests/th/wasm/T25473A.hs - + testsuite/tests/th/wasm/T25473B.hs - + testsuite/tests/th/wasm/all.T - testsuite/tests/type-data/should_fail/TDExpression.stderr - testsuite/tests/type-data/should_fail/TDNoPragma.stderr - testsuite/tests/type-data/should_fail/TDPattern.stderr - testsuite/tests/type-data/should_run/T22332a.stderr - + testsuite/tests/type-data/should_run/T24620.hs - testsuite/tests/type-data/should_run/all.T - testsuite/tests/typecheck/T13168/Makefile - + testsuite/tests/typecheck/T16127/T16127.hs - + testsuite/tests/typecheck/T16127/T16127.hs-boot - + testsuite/tests/typecheck/T16127/T16127.stderr - + testsuite/tests/typecheck/T16127/T16127Helper.hs - + testsuite/tests/typecheck/T16127/all.T - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T - testsuite/tests/typecheck/bug1465/bug1465.stderr - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/no_skolem_info/T13499.stderr - testsuite/tests/typecheck/no_skolem_info/T20063.stderr - + testsuite/tests/typecheck/should_compile/DataToTagSolving.hs - + testsuite/tests/typecheck/should_compile/DataToTagSolving.stderr - testsuite/tests/typecheck/should_compile/FloatFDs.hs - + testsuite/tests/typecheck/should_compile/InstanceWarnings.hs - + testsuite/tests/typecheck/should_compile/InstanceWarnings.stderr - + testsuite/tests/typecheck/should_compile/InstanceWarnings_aux.hs - testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs - testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs - + testsuite/tests/typecheck/should_compile/LocalGivenEqs2.stderr - testsuite/tests/typecheck/should_compile/Makefile - testsuite/tests/typecheck/should_compile/T11254.stderr - testsuite/tests/typecheck/should_compile/T11811.hs - + testsuite/tests/typecheck/should_compile/T11811.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T13343.hs - testsuite/tests/typecheck/should_compile/T13785.hs - testsuite/tests/typecheck/should_compile/T13785.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/T14763.hs - testsuite/tests/typecheck/should_compile/T15242.stderr - testsuite/tests/typecheck/should_compile/T15368.stderr - testsuite/tests/typecheck/should_compile/T15412.hs - testsuite/tests/typecheck/should_compile/T15473.stderr - testsuite/tests/typecheck/should_compile/T15839a.stderr - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClasses.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesCore.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesEffects.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesReader.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesState.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadPrimitive.hs - + testsuite/tests/typecheck/should_compile/T16234/DataPeano.hs - + testsuite/tests/typecheck/should_compile/T16234/Main.hs - + testsuite/tests/typecheck/should_compile/T16234/Makefile - + testsuite/tests/typecheck/should_compile/T16234/all.T - testsuite/tests/typecheck/should_compile/T17343.stderr - + testsuite/tests/typecheck/should_compile/T17564.hs - + testsuite/tests/typecheck/should_compile/T17594a.hs - + testsuite/tests/typecheck/should_compile/T17594f.hs - testsuite/tests/typecheck/should_compile/T18308.hs - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - testsuite/tests/typecheck/should_compile/T18851d.hs - testsuite/tests/typecheck/should_compile/T18986a.hs - testsuite/tests/typecheck/should_compile/T18986b.hs - testsuite/tests/typecheck/should_compile/T19577.hs - testsuite/tests/typecheck/should_compile/T20443a.hs - − testsuite/tests/typecheck/should_compile/T20666b.stderr - + testsuite/tests/typecheck/should_compile/T21206.hs - + testsuite/tests/typecheck/should_compile/T21765.hs - + testsuite/tests/typecheck/should_compile/T22141a.hs - + testsuite/tests/typecheck/should_compile/T22141a.stderr - + testsuite/tests/typecheck/should_compile/T22141b.hs - + testsuite/tests/typecheck/should_compile/T22141b.stderr - + testsuite/tests/typecheck/should_compile/T22141c.hs - + testsuite/tests/typecheck/should_compile/T22141c.stderr - + testsuite/tests/typecheck/should_compile/T22141d.hs - + testsuite/tests/typecheck/should_compile/T22141d.stderr - + testsuite/tests/typecheck/should_compile/T22141e.hs - + testsuite/tests/typecheck/should_compile/T22141e.stderr - + testsuite/tests/typecheck/should_compile/T22141e_Aux.hs - + testsuite/tests/typecheck/should_compile/T22141f.hs - + testsuite/tests/typecheck/should_compile/T22141g.hs - testsuite/tests/typecheck/should_compile/T22310.hs - testsuite/tests/typecheck/should_compile/T22383.hs - testsuite/tests/typecheck/should_compile/T22560a.hs - testsuite/tests/typecheck/should_compile/T22560b.hs - testsuite/tests/typecheck/should_compile/T22560c.hs - testsuite/tests/typecheck/should_compile/T22560d.hs - + testsuite/tests/typecheck/should_compile/T22560d.stderr - testsuite/tests/typecheck/should_compile/T22560e.hs - + testsuite/tests/typecheck/should_compile/T22788.hs - − testsuite/tests/typecheck/should_compile/T22891.stderr - − testsuite/tests/typecheck/should_compile/T22912.stderr - testsuite/tests/typecheck/should_compile/T23156.stderr - + testsuite/tests/typecheck/should_compile/T23501a.hs - + testsuite/tests/typecheck/should_compile/T23501b.hs - testsuite/tests/typecheck/should_compile/T23514b.hs - testsuite/tests/typecheck/should_compile/T23514c.hs - + testsuite/tests/typecheck/should_compile/T23739a.hs - + testsuite/tests/typecheck/should_compile/T23764.hs - + testsuite/tests/typecheck/should_compile/T23861.hs - + testsuite/tests/typecheck/should_compile/T23918.hs - + testsuite/tests/typecheck/should_compile/T24146.hs - + testsuite/tests/typecheck/should_compile/T24470b.hs - + testsuite/tests/typecheck/should_compile/T24566.hs - + testsuite/tests/typecheck/should_compile/T24810.hs - + testsuite/tests/typecheck/should_compile/T24845a.hs - + testsuite/tests/typecheck/should_compile/T24887.hs - + testsuite/tests/typecheck/should_compile/T24938a.hs - + testsuite/tests/typecheck/should_compile/T25029.hs - + testsuite/tests/typecheck/should_compile/T25094.hs - + testsuite/tests/typecheck/should_compile/T25125.hs - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25266.hs - + testsuite/tests/typecheck/should_compile/T25266a.hs - + testsuite/tests/typecheck/should_compile/T25266a.stderr - + testsuite/tests/typecheck/should_compile/T25266b.hs - + testsuite/tests/typecheck/should_compile/T25597.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/T6018.hs - testsuite/tests/typecheck/should_compile/T6018.stderr - testsuite/tests/typecheck/should_compile/T7169.stderr - testsuite/tests/typecheck/should_compile/T9151.hs - testsuite/tests/typecheck/should_compile/T9497a.stderr - testsuite/tests/typecheck/should_compile/T9834.stderr - + testsuite/tests/typecheck/should_compile/TcIncompleteRecSel.hs - + testsuite/tests/typecheck/should_compile/TcIncompleteRecSel.stderr - testsuite/tests/typecheck/should_compile/TyAppPat_Existential.hs - testsuite/tests/typecheck/should_compile/TyAppPat_ExistentialMulti.hs - testsuite/tests/typecheck/should_compile/TyAppPat_KindDependency.hs - testsuite/tests/typecheck/should_compile/TyAppPat_Mixed.hs - testsuite/tests/typecheck/should_compile/TyAppPat_TH.hs - testsuite/tests/typecheck/should_compile/TyAppPat_Universal.hs - testsuite/tests/typecheck/should_compile/TyAppPat_UniversalMulti1.hs - testsuite/tests/typecheck/should_compile/TyAppPat_UniversalMulti2.hs - testsuite/tests/typecheck/should_compile/TyAppPat_UniversalMulti3.hs - testsuite/tests/typecheck/should_compile/TyAppPat_UniversalNested.hs - testsuite/tests/typecheck/should_compile/TyAppPat_Wildcard.hs - + testsuite/tests/typecheck/should_compile/WarnDefaultedExceptionContext.hs - + testsuite/tests/typecheck/should_compile/WarnDefaultedExceptionContext.stderr - testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/constraint_hole_fits.stderr - testsuite/tests/typecheck/should_compile/free_monad_hole_fits.stderr - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes2.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr - testsuite/tests/typecheck/should_compile/tc165.hs - testsuite/tests/typecheck/should_compile/tc214.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - + testsuite/tests/typecheck/should_fail/DataToTagFails.hs - + testsuite/tests/typecheck/should_fail/DataToTagFails.stderr - + testsuite/tests/typecheck/should_fail/DoExpansion1.hs - + testsuite/tests/typecheck/should_fail/DoExpansion1.stderr - + testsuite/tests/typecheck/should_fail/DoExpansion2.hs - + testsuite/tests/typecheck/should_fail/DoExpansion2.stderr - + testsuite/tests/typecheck/should_fail/DoExpansion3.hs - + testsuite/tests/typecheck/should_fail/DoExpansion3.stderr - + testsuite/tests/typecheck/should_fail/ErrorIndexLinks.hs - + testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/FD1.stderr - testsuite/tests/typecheck/should_fail/GivenForallLoop.stderr - testsuite/tests/typecheck/should_fail/LazyFieldsDisabled.stderr - + testsuite/tests/typecheck/should_fail/Or4.hs - + testsuite/tests/typecheck/should_fail/Or4.stderr - testsuite/tests/typecheck/should_fail/T10351.stderr - testsuite/tests/typecheck/should_fail/T10709.stderr - testsuite/tests/typecheck/should_fail/T10709b.stderr - testsuite/tests/typecheck/should_fail/T10715.hs - testsuite/tests/typecheck/should_fail/T10971b.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11355.stderr - testsuite/tests/typecheck/should_fail/T11947a.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12035.stderr - testsuite/tests/typecheck/should_fail/T12035j.stderr - testsuite/tests/typecheck/should_fail/T12042.stderr - testsuite/tests/typecheck/should_fail/T12083a.stderr - testsuite/tests/typecheck/should_fail/T12083b.stderr - testsuite/tests/typecheck/should_fail/T12729.stderr - testsuite/tests/typecheck/should_fail/T12921.stderr - testsuite/tests/typecheck/should_fail/T12947.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T13902.stderr - testsuite/tests/typecheck/should_fail/T13909.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15527.stderr - testsuite/tests/typecheck/should_fail/T15552a.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T15883d.stderr - testsuite/tests/typecheck/should_fail/T15883e.stderr - testsuite/tests/typecheck/should_fail/T16059c.stderr - testsuite/tests/typecheck/should_fail/T16059d.stderr - testsuite/tests/typecheck/should_fail/T16059e.stderr - testsuite/tests/typecheck/should_fail/T16512b.stderr - testsuite/tests/typecheck/should_fail/T16829a.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17077.stderr - testsuite/tests/typecheck/should_fail/T17139.stderr - testsuite/tests/typecheck/should_fail/T17213.stderr - testsuite/tests/typecheck/should_fail/T17563.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - + testsuite/tests/typecheck/should_fail/T17594c.hs - + testsuite/tests/typecheck/should_fail/T17594c.stderr - + testsuite/tests/typecheck/should_fail/T17594d.hs - + testsuite/tests/typecheck/should_fail/T17594d.stderr - + testsuite/tests/typecheck/should_fail/T17594g.hs - + testsuite/tests/typecheck/should_fail/T17594g.stderr - + testsuite/tests/typecheck/should_fail/T17940.hs - + testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18398.stderr - testsuite/tests/typecheck/should_fail/T18640a.hs - testsuite/tests/typecheck/should_fail/T18640a.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T18939_Fail.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19187.stderr - testsuite/tests/typecheck/should_fail/T19187a.stderr - testsuite/tests/typecheck/should_fail/T19415.stderr - testsuite/tests/typecheck/should_fail/T19627.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20443b.hs - testsuite/tests/typecheck/should_fail/T20443b.stderr - testsuite/tests/typecheck/should_fail/T20588.stderr - testsuite/tests/typecheck/should_fail/T20588c.stderr - testsuite/tests/typecheck/should_fail/T20666.stderr - testsuite/tests/typecheck/should_fail/T20666a.stderr - testsuite/tests/typecheck/should_compile/T20666b.hs → testsuite/tests/typecheck/should_fail/T20666b.hs - + testsuite/tests/typecheck/should_fail/T20666b.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - + testsuite/tests/typecheck/should_fail/T20873d.hs - + testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21130.stderr - testsuite/tests/typecheck/should_fail/T21158.stderr - testsuite/tests/typecheck/should_fail/T21338.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - + testsuite/tests/typecheck/should_fail/T22141a.stderr - + testsuite/tests/typecheck/should_fail/T22141b.stderr - + testsuite/tests/typecheck/should_fail/T22141c.stderr - + testsuite/tests/typecheck/should_fail/T22141d.stderr - + testsuite/tests/typecheck/should_fail/T22141e.stderr - testsuite/tests/typecheck/should_fail/T22478c.hs - testsuite/tests/typecheck/should_fail/T22478c.stderr - testsuite/tests/typecheck/should_fail/T22560_fail_a.hs - testsuite/tests/typecheck/should_fail/T22560_fail_a.stderr - testsuite/tests/typecheck/should_fail/T22560_fail_b.hs - testsuite/tests/typecheck/should_fail/T22560_fail_b.stderr - testsuite/tests/typecheck/should_fail/T22560_fail_c.hs - testsuite/tests/typecheck/should_fail/T22560_fail_c.stderr - testsuite/tests/typecheck/should_fail/T22560_fail_d.hs - testsuite/tests/typecheck/should_fail/T22560_fail_d.stderr - testsuite/tests/typecheck/should_fail/T22560_fail_ext.stderr - testsuite/tests/typecheck/should_fail/T22645.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_compile/T22891.hs → testsuite/tests/typecheck/should_fail/T22891.hs - + testsuite/tests/typecheck/should_fail/T22891.stderr - testsuite/tests/typecheck/should_compile/T22912.hs → testsuite/tests/typecheck/should_fail/T22912.hs - + testsuite/tests/typecheck/should_fail/T22912.stderr - testsuite/tests/typecheck/should_fail/T23427.stderr - + testsuite/tests/typecheck/should_fail/T23734.hs - + testsuite/tests/typecheck/should_fail/T23734.stderr - + testsuite/tests/typecheck/should_fail/T23739b.hs - + testsuite/tests/typecheck/should_fail/T23739b.stderr - + testsuite/tests/typecheck/should_fail/T23739c.hs - + testsuite/tests/typecheck/should_fail/T23739c.stderr - + testsuite/tests/typecheck/should_fail/T23776.hs - + testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T23778.hs - + testsuite/tests/typecheck/should_fail/T23778.stderr - + testsuite/tests/typecheck/should_fail/T24064.hs - + testsuite/tests/typecheck/should_fail/T24064.stderr - + testsuite/tests/typecheck/should_fail/T24279.hs - + testsuite/tests/typecheck/should_fail/T24279.stderr - + testsuite/tests/typecheck/should_fail/T24298.hs - + testsuite/tests/typecheck/should_fail/T24298.stderr - + testsuite/tests/typecheck/should_fail/T24318.hs - + testsuite/tests/typecheck/should_fail/T24318.stderr - + testsuite/tests/typecheck/should_fail/T24470a.hs - + testsuite/tests/typecheck/should_fail/T24470a.stderr - + testsuite/tests/typecheck/should_fail/T24553.hs - + testsuite/tests/typecheck/should_fail/T24553.stderr - + testsuite/tests/typecheck/should_fail/T24868.hs - + testsuite/tests/typecheck/should_fail/T24868.stderr - + testsuite/tests/typecheck/should_fail/T24938.hs - + testsuite/tests/typecheck/should_fail/T24938.stderr - + testsuite/tests/typecheck/should_fail/T25325.hs - + testsuite/tests/typecheck/should_fail/T25325.stderr - testsuite/tests/typecheck/should_fail/T2538.stderr - testsuite/tests/typecheck/should_fail/T2714.stderr - testsuite/tests/typecheck/should_fail/T2846b.stderr - testsuite/tests/typecheck/should_fail/T3155.stderr - testsuite/tests/typecheck/should_fail/T3323.stderr - testsuite/tests/typecheck/should_fail/T3468.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T5957.stderr - testsuite/tests/typecheck/should_fail/T6022.stderr - testsuite/tests/typecheck/should_fail/T6161.stderr - testsuite/tests/typecheck/should_fail/T7019.stderr - testsuite/tests/typecheck/should_fail/T7019a.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T7279.stderr - testsuite/tests/typecheck/should_fail/T7809.stderr - testsuite/tests/typecheck/should_fail/T8030.stderr - testsuite/tests/typecheck/should_fail/T8034.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8450.hs - testsuite/tests/typecheck/should_fail/T8450.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T8603.stderr - testsuite/tests/typecheck/should_fail/T8883.stderr - testsuite/tests/typecheck/should_fail/T9196.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9415.stderr - testsuite/tests/typecheck/should_fail/T9497d.stderr - testsuite/tests/typecheck/should_fail/T9605.stderr - testsuite/tests/typecheck/should_fail/T9739.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr - testsuite/tests/typecheck/should_fail/TcNoNullaryTC.stderr - testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr - testsuite/tests/typecheck/should_fail/TcStaticPointersFail03.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_ExistentialEscape.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearMultiAppPat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearMultiPat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearSinglePat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearSinglePat.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_Nonmatching.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBinding.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_ScopedTyVarConflict.hs - testsuite/tests/typecheck/should_fail/TyAppPat_ScopedTyVarConflict.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.hs - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr - testsuite/tests/typecheck/should_fail/TyfamsDisabled.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail1.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag1_ql.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/fd-loop.stderr - testsuite/tests/typecheck/should_fail/tcfail001.stderr - testsuite/tests/typecheck/should_fail/tcfail008.stderr - testsuite/tests/typecheck/should_fail/tcfail027.stderr - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail037.stderr - testsuite/tests/typecheck/should_fail/tcfail044.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail047.stderr - testsuite/tests/typecheck/should_fail/tcfail068.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail094.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail108.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail127.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail133.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail139.stderr - testsuite/tests/typecheck/should_fail/tcfail140.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail150.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail154.stderr - testsuite/tests/typecheck/should_fail/tcfail157.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail165.hs - − testsuite/tests/typecheck/should_fail/tcfail165.stderr - testsuite/tests/typecheck/should_fail/tcfail166.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail173.stderr - testsuite/tests/typecheck/should_fail/tcfail175.hs - testsuite/tests/typecheck/should_fail/tcfail175.stderr - testsuite/tests/typecheck/should_fail/tcfail181.stderr - testsuite/tests/typecheck/should_fail/tcfail182.stderr - testsuite/tests/typecheck/should_fail/tcfail183.stderr - testsuite/tests/typecheck/should_fail/tcfail184.stderr - testsuite/tests/typecheck/should_fail/tcfail196.stderr - testsuite/tests/typecheck/should_fail/tcfail197.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail201.stderr - testsuite/tests/typecheck/should_fail/tcfail209.stderr - testsuite/tests/typecheck/should_fail/tcfail209a.stderr - testsuite/tests/typecheck/should_fail/tcfail213.stderr - testsuite/tests/typecheck/should_fail/tcfail214.stderr - testsuite/tests/typecheck/should_fail/tcfail216.stderr - testsuite/tests/typecheck/should_fail/tcfail217.stderr - testsuite/tests/typecheck/should_fail/tcfail223.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_fail/tcfail225.hs - testsuite/tests/typecheck/should_fail/tcfail225.stderr - + testsuite/tests/typecheck/should_run/DefaultExceptionContext.hs - testsuite/tests/typecheck/should_run/T10284.stderr - testsuite/tests/typecheck/should_run/T11049.stderr - testsuite/tests/typecheck/should_run/T11715.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T14341.stdout - + testsuite/tests/typecheck/should_run/T15598.hs - + testsuite/tests/typecheck/should_run/T17594e.hs - + testsuite/tests/typecheck/should_run/T17594e.stdout - + testsuite/tests/typecheck/should_run/T18324.hs - + testsuite/tests/typecheck/should_run/T18324.stdout - testsuite/tests/typecheck/should_run/T21973a.stderr - + testsuite/tests/typecheck/should_run/T22086.hs - + testsuite/tests/typecheck/should_run/T22086.stdout - testsuite/tests/typecheck/should_run/T22510.stdout - + testsuite/tests/typecheck/should_run/T23761.hs - + testsuite/tests/typecheck/should_run/T23761.stdout - + testsuite/tests/typecheck/should_run/T23761b.hs - + testsuite/tests/typecheck/should_run/T23761b.stdout - + testsuite/tests/typecheck/should_run/T24411.hs - + testsuite/tests/typecheck/should_run/T24411.stdout - testsuite/tests/typecheck/should_run/T9497a-run.stderr - testsuite/tests/typecheck/should_run/T9497b-run.stderr - testsuite/tests/typecheck/should_run/T9497c-run.stderr - testsuite/tests/typecheck/should_run/TypeRep.stdout - testsuite/tests/typecheck/should_run/Typeable1.stderr - testsuite/tests/typecheck/should_run/all.T - testsuite/tests/typecheck/testeq1/test.T - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - − testsuite/tests/unboxedsums/T22187_run.stdout - testsuite/tests/unboxedsums/all.T - testsuite/tests/unboxedsums/module/all.T - testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/UnlGadt1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - + testsuite/tests/unsatisfiable/T23816.hs - + testsuite/tests/unsatisfiable/T23816.stderr - testsuite/tests/unsatisfiable/UnsatDefault.stderr - testsuite/tests/unsatisfiable/UnsatDefer.stderr - testsuite/tests/unsatisfiable/all.T - + testsuite/tests/vdq-rta/should_compile/Makefile - + testsuite/tests/vdq-rta/should_compile/T14158_vdq.hs - + testsuite/tests/vdq-rta/should_compile/T17792_vdq.hs - + testsuite/tests/vdq-rta/should_compile/T17792_vdq.stderr - + testsuite/tests/vdq-rta/should_compile/T22326_callStack.hs - + testsuite/tests/vdq-rta/should_compile/T22326_idv.hs - + testsuite/tests/vdq-rta/should_compile/T22326_noext.hs - + testsuite/tests/vdq-rta/should_compile/T22326_noext_def.hs - + testsuite/tests/vdq-rta/should_compile/T22326_sig.hs - + testsuite/tests/vdq-rta/should_compile/T22326_sizeOf.hs - + testsuite/tests/vdq-rta/should_compile/T22326_symbolVal.hs - + testsuite/tests/vdq-rta/should_compile/T22326_th_dump1.hs - + testsuite/tests/vdq-rta/should_compile/T22326_th_dump1.stderr - + testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.hs - + testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - + testsuite/tests/vdq-rta/should_compile/T22326_typeRep.hs - + testsuite/tests/vdq-rta/should_compile/T23738_basic.hs - + testsuite/tests/vdq-rta/should_compile/T23738_nested.hs - + testsuite/tests/vdq-rta/should_compile/T23738_overlit.hs - + testsuite/tests/vdq-rta/should_compile/T23738_sigforall.hs - + testsuite/tests/vdq-rta/should_compile/T23738_th.hs - + testsuite/tests/vdq-rta/should_compile/T23738_tyvar.hs - + testsuite/tests/vdq-rta/should_compile/T23738_wild.hs - + testsuite/tests/vdq-rta/should_compile/T23739_idv.hs - + testsuite/tests/vdq-rta/should_compile/T23739_nested.hs - + testsuite/tests/vdq-rta/should_compile/T23739_sig.hs - + testsuite/tests/vdq-rta/should_compile/T23739_sizeOf.hs - + testsuite/tests/vdq-rta/should_compile/T23739_symbolVal.hs - + testsuite/tests/vdq-rta/should_compile/T23739_th_dump1.hs - + testsuite/tests/vdq-rta/should_compile/T23739_th_dump1.stderr - + testsuite/tests/vdq-rta/should_compile/T23739_th_pprint1.hs - + testsuite/tests/vdq-rta/should_compile/T23739_th_pprint1.stderr - + testsuite/tests/vdq-rta/should_compile/T23739_typeRep.hs - + testsuite/tests/vdq-rta/should_compile/T24159_th_type_syntax.hs - + testsuite/tests/vdq-rta/should_compile/T24159_type_syntax.hs - + testsuite/tests/vdq-rta/should_compile/T24159_viewpat.hs - + testsuite/tests/vdq-rta/should_compile/T24159_viewpat.stderr - + testsuite/tests/vdq-rta/should_compile/T24570.hs - + testsuite/tests/vdq-rta/should_compile/WithSpineVDQ_LintErr.hs - + testsuite/tests/vdq-rta/should_compile/all.T - + testsuite/tests/vdq-rta/should_fail/Makefile - + testsuite/tests/vdq-rta/should_fail/T22326_fail_ado.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_ado.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_app.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_app.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_bang_pat.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_bang_pat.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_caseof.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_caseof.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_ext1.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_ext1.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_ext2.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_ext2.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_lam_arg.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_lam_arg.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_match.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_match.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_n_args.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_n_args.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_nonlinear.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_nonlinear.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_notInScope.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_notInScope.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_pat.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_pat.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_patsyn.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_patsyn.stderr - + testsuite/tests/vdq-rta/should_fail/T22326_fail_top.hs - + testsuite/tests/vdq-rta/should_fail/T22326_fail_top.stderr - + testsuite/tests/vdq-rta/should_fail/T23738_fail_implicit_tv.hs - + testsuite/tests/vdq-rta/should_fail/T23738_fail_implicit_tv.stderr - + testsuite/tests/vdq-rta/should_fail/T23738_fail_var.hs - + testsuite/tests/vdq-rta/should_fail/T23738_fail_var.stderr - + testsuite/tests/vdq-rta/should_fail/T23738_fail_wild.hs - + testsuite/tests/vdq-rta/should_fail/T23738_fail_wild.stderr - + testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs - + testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr - + testsuite/tests/vdq-rta/should_fail/T23739_fail_ret.hs - + testsuite/tests/vdq-rta/should_fail/T23739_fail_ret.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_1.hs - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_1.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_2.hs - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_2.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_3.hs - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_3.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_4.hs - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_4.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_5.hs - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_5.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_6.hs - + testsuite/tests/vdq-rta/should_fail/T24159_pat_parse_error_6.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_rn_fail.hs - + testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_rn_fail.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_tc_fail.hs - + testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_tc_fail.stderr - + testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_th_fail.script - + testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_th_fail.stderr - + testsuite/tests/vdq-rta/should_fail/T24176.hs - + testsuite/tests/vdq-rta/should_fail/T24176.stderr - + testsuite/tests/vdq-rta/should_fail/T24604.hs - + testsuite/tests/vdq-rta/should_fail/T24604.stderr - + testsuite/tests/vdq-rta/should_fail/T24604a.hs - + testsuite/tests/vdq-rta/should_fail/T24604a.stderr - + testsuite/tests/vdq-rta/should_fail/all.T - + testsuite/tests/warnings/should_compile/DataToTagWarnings.hs - + testsuite/tests/warnings/should_compile/DataToTagWarnings.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T11077.hs - testsuite/tests/warnings/should_compile/T11077.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T18862a.stderr - testsuite/tests/warnings/should_compile/T18862b.hs - testsuite/tests/warnings/should_compile/T18862b.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - + testsuite/tests/warnings/should_compile/T19564d.stderr - + testsuite/tests/warnings/should_compile/T23465.hs - + testsuite/tests/warnings/should_compile/T23465.stderr - + testsuite/tests/warnings/should_compile/T24396.stderr - + testsuite/tests/warnings/should_compile/T24396a.hs - + testsuite/tests/warnings/should_compile/T24396b.hs - + testsuite/tests/warnings/should_compile/WarnNoncanonical.hs - + testsuite/tests/warnings/should_compile/WarnNoncanonical.stderr - testsuite/tests/warnings/should_compile/all.T - testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr - testsuite/tests/warnings/should_fail/Colour.stderr - + testsuite/tests/warnings/should_fail/T24396c.hs - + testsuite/tests/warnings/should_fail/T24396c.stderr - testsuite/tests/warnings/should_fail/all.T - testsuite/tests/wasm/should_run/control-flow/CmmPaths.hs - testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs - testsuite/tests/wasm/should_run/control-flow/RunCmm.hs - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - testsuite/tests/wcompat-warnings/Template.hs - + testsuite/tests/wcompat-warnings/WCompatDefault.hs - testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr - testsuite/tests/wcompat-warnings/all.T - testsuite/timeout/WinCBindings.hsc - testsuite/timeout/timeout.cabal - utils/check-exact/ExactPrint.hs - − utils/check-exact/Lookup.hs - utils/check-exact/Main.hs - − utils/check-exact/Orphans.hs - utils/check-exact/Parsers.hs - utils/check-exact/Preprocess.hs - utils/check-exact/Transform.hs - utils/check-exact/Types.hs - utils/check-exact/Utils.hs - utils/check-exact/check-exact.cabal - utils/check-ppr/Main.hs - utils/deriveConstants/Main.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/fs/fs.c - utils/genapply/Main.hs - − utils/genapply/Makefile - utils/genapply/genapply.cabal - + utils/genapply/hie.yaml - + utils/genprimopcode/AccessOps.hs - utils/genprimopcode/Lexer.x - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - utils/genprimopcode/Parser.y - utils/genprimopcode/ParserM.hs - utils/genprimopcode/Syntax.hs - utils/genprimopcode/genprimopcode.cabal - − utils/ghc-cabal/Main.hs - − utils/ghc-cabal/Makefile - − utils/ghc-cabal/ghc-cabal.cabal - utils/ghc-pkg/Main.hs - − utils/ghc-pkg/Makefile - utils/ghc-pkg/ghc-pkg.cabal.in - − utils/ghc-pkg/ghc-pkg.wrapper - + utils/ghc-toolchain/.gitignore - + utils/ghc-toolchain/exe/Main.hs - + utils/ghc-toolchain/exe/ghc-toolchain-bin.cabal - + utils/ghc-toolchain/ghc-toolchain.cabal - + utils/ghc-toolchain/src/GHC/Toolchain.hs - + utils/ghc-toolchain/src/GHC/Toolchain/CheckArm.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Lens.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Monad.hs - + utils/ghc-toolchain/src/GHC/Toolchain/NormaliseTriple.hs - + utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - + utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Prelude.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Program.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Target.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/Ar.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/MergeObjs.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/Nm.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/Ranlib.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Tools/Readelf.hs - + utils/ghc-toolchain/src/GHC/Toolchain/Utils.hs - − utils/haddock - + utils/haddock/.github/mergify.yml - + utils/haddock/.github/workflows/ci.yml - + utils/haddock/.github/workflows/hlint-ci.yml - + utils/haddock/.gitignore - + utils/haddock/.hlint.yaml - + utils/haddock/.readthedocs.yaml - + utils/haddock/CHANGES.md - + utils/haddock/CONTRIBUTING.md - + utils/haddock/LICENSE - + utils/haddock/Makefile - + utils/haddock/README.md - + utils/haddock/Setup.lhs - + utils/haddock/cabal.project - + utils/haddock/doc/.gitignore - + utils/haddock/doc/Makefile - + utils/haddock/doc/README.md - + utils/haddock/doc/cheatsheet/LICENSE - + utils/haddock/doc/cheatsheet/README.md - + utils/haddock/doc/cheatsheet/haddocks.md - + utils/haddock/doc/cheatsheet/haddocks.pdf - + utils/haddock/doc/cheatsheet/haddocks.svg - + utils/haddock/doc/common-errors.rst - + utils/haddock/doc/conf.py - + utils/haddock/doc/diagrams/README.md - + utils/haddock/doc/diagrams/haddock-api.mmd - + utils/haddock/doc/diagrams/haddock-api.svg - + utils/haddock/doc/diagrams/haddock-library.mmd - + utils/haddock/doc/diagrams/haddock-library.svg - + utils/haddock/doc/ghc.mk - + utils/haddock/doc/index.rst - + utils/haddock/doc/intro.rst - + utils/haddock/doc/invoking.rst - + utils/haddock/doc/markup.rst - + utils/haddock/doc/multi-components.rst - + utils/haddock/doc/requirements.txt - + utils/haddock/driver/Main.hs - + utils/haddock/fourmolu.yaml - + utils/haddock/ghc-tags.yaml - + utils/haddock/ghc.mk - + utils/haddock/haddock-api/CHANGES.md - + utils/haddock/haddock-api/LICENSE - + utils/haddock/haddock-api/Setup.lhs - + utils/haddock/haddock-api/compat/posix/Haddock/Compat.hs - + utils/haddock/haddock-api/compat/windows/Haddock/Compat.hs - + utils/haddock/haddock-api/haddock-api.cabal - + utils/haddock/haddock-api/resources/html/Classic.theme/haskell_icon.gif - + utils/haddock/haddock-api/resources/html/Classic.theme/minus.gif - + utils/haddock/haddock-api/resources/html/Classic.theme/plus.gif - + utils/haddock/haddock-api/resources/html/Classic.theme/xhaddock.css - + utils/haddock/haddock-api/resources/html/Linuwial.std-theme/linuwial.css - + utils/haddock/haddock-api/resources/html/Linuwial.std-theme/synopsis.png - + utils/haddock/haddock-api/resources/html/Ocean.theme/hslogo-16.png - + utils/haddock/haddock-api/resources/html/Ocean.theme/minus.gif - + utils/haddock/haddock-api/resources/html/Ocean.theme/ocean.css - + utils/haddock/haddock-api/resources/html/Ocean.theme/plus.gif - + utils/haddock/haddock-api/resources/html/Ocean.theme/synopsis.png - + utils/haddock/haddock-api/resources/html/README.md - + utils/haddock/haddock-api/resources/html/gulpfile.js - + utils/haddock/haddock-api/resources/html/haddock-bundle.min.js - + utils/haddock/haddock-api/resources/html/highlight.js - + utils/haddock/haddock-api/resources/html/js-src/cookies.ts - + utils/haddock/haddock-api/resources/html/js-src/details-helper.tsx - + utils/haddock/haddock-api/resources/html/js-src/init.ts - + utils/haddock/haddock-api/resources/html/js-src/quick-jump.tsx - + utils/haddock/haddock-api/resources/html/js-src/style-menu.tsx - + utils/haddock/haddock-api/resources/html/package-lock.json - + utils/haddock/haddock-api/resources/html/package.json - + utils/haddock/haddock-api/resources/html/quick-jump.css - + utils/haddock/haddock-api/resources/html/quick-jump.min.js - + utils/haddock/haddock-api/resources/html/solarized.css - + utils/haddock/haddock-api/resources/html/tsconfig.json - + utils/haddock/haddock-api/resources/latex/haddock.sty - + utils/haddock/haddock-api/src/Documentation/Haddock.hs - + utils/haddock/haddock-api/src/Haddock.hs - + utils/haddock/haddock-api/src/Haddock/Backends/HaddockDB.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs - + utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Meta.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Themes.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Types.hs - + utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs - + utils/haddock/haddock-api/src/Haddock/Convert.hs - + utils/haddock/haddock-api/src/Haddock/Doc.hs - + utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - + utils/haddock/haddock-api/src/Haddock/Interface.hs - + utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - + utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - + utils/haddock/haddock-api/src/Haddock/Interface/Json.hs - + utils/haddock/haddock-api/src/Haddock/Interface/LexParseRn.hs - + utils/haddock/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs - + utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - + utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs - + utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs - + utils/haddock/haddock-api/src/Haddock/ModuleTree.hs - + utils/haddock/haddock-api/src/Haddock/Options.hs - + utils/haddock/haddock-api/src/Haddock/Parser.hs - + utils/haddock/haddock-api/src/Haddock/Types.hs - + utils/haddock/haddock-api/src/Haddock/Utils.hs - + utils/haddock/haddock-api/src/Haddock/Utils/Json.hs - + utils/haddock/haddock-api/src/Haddock/Utils/Json/Parser.hs - + utils/haddock/haddock-api/src/Haddock/Utils/Json/Types.hs - + utils/haddock/haddock-api/src/Haddock/Version.hs - + utils/haddock/haddock-api/test/Haddock/Backends/Hyperlinker/ParserSpec.hs - + utils/haddock/haddock-api/test/Spec.hs - + utils/haddock/haddock-library/CHANGES.md - + utils/haddock/haddock-library/LICENSE - + utils/haddock/haddock-library/Setup.hs - + utils/haddock/haddock-library/fixtures/Fixtures.hs - + utils/haddock/haddock-library/fixtures/examples/definitionList.input - + utils/haddock/haddock-library/fixtures/examples/definitionList.parsed - + utils/haddock/haddock-library/fixtures/examples/identifier.input - + utils/haddock/haddock-library/fixtures/examples/identifier.parsed - + utils/haddock/haddock-library/fixtures/examples/identifierBackticks.input - + utils/haddock/haddock-library/fixtures/examples/identifierBackticks.parsed - + utils/haddock/haddock-library/fixtures/examples/link.input - + utils/haddock/haddock-library/fixtures/examples/link.parsed - + utils/haddock/haddock-library/fixtures/examples/linkInline.input - + utils/haddock/haddock-library/fixtures/examples/linkInline.parsed - + utils/haddock/haddock-library/fixtures/examples/linkInlineMarkup.input - + utils/haddock/haddock-library/fixtures/examples/linkInlineMarkup.parsed - + utils/haddock/haddock-library/fixtures/examples/list-blocks1.input - + utils/haddock/haddock-library/fixtures/examples/list-blocks1.parsed - + utils/haddock/haddock-library/fixtures/examples/list-blocks2.input - + utils/haddock/haddock-library/fixtures/examples/list-blocks2.parsed - + utils/haddock/haddock-library/fixtures/examples/table-cell-strip-whitespaces.input - + utils/haddock/haddock-library/fixtures/examples/table-cell-strip-whitespaces.parsed - + utils/haddock/haddock-library/fixtures/examples/table-simple.input - + utils/haddock/haddock-library/fixtures/examples/table-simple.parsed - + utils/haddock/haddock-library/fixtures/examples/table1.input - + utils/haddock/haddock-library/fixtures/examples/table1.parsed - + utils/haddock/haddock-library/fixtures/examples/table2.input - + utils/haddock/haddock-library/fixtures/examples/table2.parsed - + utils/haddock/haddock-library/fixtures/examples/table3.input - + utils/haddock/haddock-library/fixtures/examples/table3.parsed - + utils/haddock/haddock-library/fixtures/examples/table4.input - + utils/haddock/haddock-library/fixtures/examples/table4.parsed - + utils/haddock/haddock-library/fixtures/examples/table5.input - + utils/haddock/haddock-library/fixtures/examples/table5.parsed - + utils/haddock/haddock-library/fixtures/examples/url.input - + utils/haddock/haddock-library/fixtures/examples/url.parsed - + utils/haddock/haddock-library/fixtures/examples/urlLabel.input - + utils/haddock/haddock-library/fixtures/examples/urlLabel.parsed - + utils/haddock/haddock-library/haddock-library.cabal - + utils/haddock/haddock-library/src/Documentation/Haddock/Doc.hs - + utils/haddock/haddock-library/src/Documentation/Haddock/Markup.hs - + utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs - + utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs - + utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Monad.hs - + utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Util.hs - + utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs - + utils/haddock/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs - + utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs - + utils/haddock/haddock-library/test/Spec.hs - + utils/haddock/haddock-test/Setup.lhs - + utils/haddock/haddock-test/haddock-test.cabal - + utils/haddock/haddock-test/src/Test/Haddock.hs - + utils/haddock/haddock-test/src/Test/Haddock/Config.hs - + utils/haddock/haddock-test/src/Test/Haddock/Process.hs - + utils/haddock/haddock-test/src/Test/Haddock/Utils.hs - + utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs - + utils/haddock/haddock.cabal - + utils/haddock/hoogle-test/Main.hs - + utils/haddock/hoogle-test/ref/Bug722/test.txt - + utils/haddock/hoogle-test/ref/Bug806/test.txt - + utils/haddock/hoogle-test/ref/Bug825/test.txt - + utils/haddock/hoogle-test/ref/Bug946/test.txt - + utils/haddock/hoogle-test/ref/Bug992/test.txt - + utils/haddock/hoogle-test/ref/assoc-types/test.txt - + utils/haddock/hoogle-test/ref/classes/test.txt - + utils/haddock/hoogle-test/ref/fixity/test.txt - + utils/haddock/hoogle-test/ref/modules/test.txt - + utils/haddock/hoogle-test/ref/type-sigs/test.txt - + utils/haddock/hoogle-test/run - + utils/haddock/hoogle-test/src/Bug722/Bug722.hs - + utils/haddock/hoogle-test/src/Bug806/Bug806.hs - + utils/haddock/hoogle-test/src/Bug825/Bug825.hs - + utils/haddock/hoogle-test/src/Bug946/Bug946.hs - + utils/haddock/hoogle-test/src/Bug992/Bug992.hs - + utils/haddock/hoogle-test/src/assoc-types/AssocTypes.hs - + utils/haddock/hoogle-test/src/classes/Classes.hs - + utils/haddock/hoogle-test/src/fixity/Fixity.hs - + utils/haddock/hoogle-test/src/modules/Bar.hs - + utils/haddock/hoogle-test/src/modules/Foo.hs - + utils/haddock/hoogle-test/src/type-sigs/ReaderT.hs - + utils/haddock/hoogle-test/src/type-sigs/ReaderTReexport.hs - + utils/haddock/html-test/Main.hs - + utils/haddock/html-test/ref/A.html - + utils/haddock/html-test/ref/B.html - + utils/haddock/html-test/ref/Bold.html - + utils/haddock/html-test/ref/Bug1.html - + utils/haddock/html-test/ref/Bug1004.html - + utils/haddock/html-test/ref/Bug1033.html - + utils/haddock/html-test/ref/Bug1035.html - + utils/haddock/html-test/ref/Bug1050.html - + utils/haddock/html-test/ref/Bug1054.html - + utils/haddock/html-test/ref/Bug1063.html - + utils/haddock/html-test/ref/Bug1067A.html - + utils/haddock/html-test/ref/Bug1067B.html - + utils/haddock/html-test/ref/Bug1103.html - + utils/haddock/html-test/ref/Bug195.html - + utils/haddock/html-test/ref/Bug2.html - + utils/haddock/html-test/ref/Bug201.html - + utils/haddock/html-test/ref/Bug253.html - + utils/haddock/html-test/ref/Bug26.html - + utils/haddock/html-test/ref/Bug280.html - + utils/haddock/html-test/ref/Bug294.html - + utils/haddock/html-test/ref/Bug298.html - + utils/haddock/html-test/ref/Bug3.html - + utils/haddock/html-test/ref/Bug308.html - + utils/haddock/html-test/ref/Bug308CrossModule.html - + utils/haddock/html-test/ref/Bug310.html - + utils/haddock/html-test/ref/Bug313.html - + utils/haddock/html-test/ref/Bug335.html - + utils/haddock/html-test/ref/Bug4.html - + utils/haddock/html-test/ref/Bug458.html - + utils/haddock/html-test/ref/Bug466.html - + utils/haddock/html-test/ref/Bug546.html - + utils/haddock/html-test/ref/Bug548.html - + utils/haddock/html-test/ref/Bug574.html - + utils/haddock/html-test/ref/Bug6.html - + utils/haddock/html-test/ref/Bug613.html - + utils/haddock/html-test/ref/Bug647.html - + utils/haddock/html-test/ref/Bug679.html - + utils/haddock/html-test/ref/Bug7.html - + utils/haddock/html-test/ref/Bug8.html - + utils/haddock/html-test/ref/Bug85.html - + utils/haddock/html-test/ref/Bug865.html - + utils/haddock/html-test/ref/Bug923.html - + utils/haddock/html-test/ref/Bug952.html - + utils/haddock/html-test/ref/Bug953.html - + utils/haddock/html-test/ref/Bug973.html - + utils/haddock/html-test/ref/BugDeprecated.html - + utils/haddock/html-test/ref/BugExportHeadings.html - + utils/haddock/html-test/ref/Bugs.html - + utils/haddock/html-test/ref/BundledPatterns.html - + utils/haddock/html-test/ref/BundledPatterns2.html - + utils/haddock/html-test/ref/ConstructorArgs.html - + utils/haddock/html-test/ref/ConstructorPatternExport.html - + utils/haddock/html-test/ref/CrossPackageDocs.html - + utils/haddock/html-test/ref/DefaultAssociatedTypes.html - + utils/haddock/html-test/ref/DefaultSignatures.html - + utils/haddock/html-test/ref/DeprecatedClass.html - + utils/haddock/html-test/ref/DeprecatedData.html - + utils/haddock/html-test/ref/DeprecatedFunction.html - + utils/haddock/html-test/ref/DeprecatedFunction2.html - + utils/haddock/html-test/ref/DeprecatedFunction3.html - + utils/haddock/html-test/ref/DeprecatedModule.html - + utils/haddock/html-test/ref/DeprecatedModule2.html - + utils/haddock/html-test/ref/DeprecatedNewtype.html - + utils/haddock/html-test/ref/DeprecatedReExport.html - + utils/haddock/html-test/ref/DeprecatedRecord.html - + utils/haddock/html-test/ref/DeprecatedTypeFamily.html - + utils/haddock/html-test/ref/DeprecatedTypeSynonym.html - + utils/haddock/html-test/ref/DuplicateRecordFields.html - + utils/haddock/html-test/ref/Examples.html - + utils/haddock/html-test/ref/ExportSince1.html - + utils/haddock/html-test/ref/ExportSince2.html - + utils/haddock/html-test/ref/Extensions.html - + utils/haddock/html-test/ref/FunArgs.html - + utils/haddock/html-test/ref/GADTRecords.html - + utils/haddock/html-test/ref/GadtConstructorArgs.html - + utils/haddock/html-test/ref/Hash.html - + utils/haddock/html-test/ref/HiddenInstances.html - + utils/haddock/html-test/ref/HiddenInstancesB.html - + utils/haddock/html-test/ref/Hyperlinks.html - + utils/haddock/html-test/ref/Identifiers.html - + utils/haddock/html-test/ref/IgnoreExports.html - + utils/haddock/html-test/ref/ImplicitParams.html - + utils/haddock/html-test/ref/Instances.html - + utils/haddock/html-test/ref/LinearTypes.html - + utils/haddock/html-test/ref/Math.html - + utils/haddock/html-test/ref/Minimal.html - + utils/haddock/html-test/ref/ModuleWithWarning.html - + utils/haddock/html-test/ref/NamedDoc.html - + utils/haddock/html-test/ref/NamespacedIdentifiers.html - + utils/haddock/html-test/ref/Nesting.html - + utils/haddock/html-test/ref/NoLayout.html - + utils/haddock/html-test/ref/NonGreedy.html - + utils/haddock/html-test/ref/Operators.html - + utils/haddock/html-test/ref/OrphanInstances.html - + utils/haddock/html-test/ref/OrphanInstancesClass.html - + utils/haddock/html-test/ref/OrphanInstancesType.html - + utils/haddock/html-test/ref/PR643.html - + utils/haddock/html-test/ref/PR643_1.html - + utils/haddock/html-test/ref/PatternSyns.html - + utils/haddock/html-test/ref/PromotedTypes.html - + utils/haddock/html-test/ref/Properties.html - + utils/haddock/html-test/ref/PruneWithWarning.html - + utils/haddock/html-test/ref/QuantifiedConstraints.html - + utils/haddock/html-test/ref/QuasiExpr.html - + utils/haddock/html-test/ref/QuasiQuote.html - + utils/haddock/html-test/ref/SectionLabels.html - + utils/haddock/html-test/ref/SpuriousSuperclassConstraints.html - + utils/haddock/html-test/ref/T23616.html - + utils/haddock/html-test/ref/T24294.html - + utils/haddock/html-test/ref/TH.html - + utils/haddock/html-test/ref/TH2.html - + utils/haddock/html-test/ref/Table.html - + utils/haddock/html-test/ref/Test.html - + utils/haddock/html-test/ref/Threaded.html - + utils/haddock/html-test/ref/Threaded_TH.html - + utils/haddock/html-test/ref/Ticket112.html - + utils/haddock/html-test/ref/Ticket61.html - + utils/haddock/html-test/ref/Ticket75.html - + utils/haddock/html-test/ref/TitledPicture.html - + utils/haddock/html-test/ref/TypeFamilies.html - + utils/haddock/html-test/ref/TypeFamilies2.html - + utils/haddock/html-test/ref/TypeFamilies3.html - + utils/haddock/html-test/ref/TypeOperators.html - + utils/haddock/html-test/ref/UnboxedStuff.html - + utils/haddock/html-test/ref/Unicode.html - + utils/haddock/html-test/ref/Unicode2.html - + utils/haddock/html-test/ref/Visible.html - + utils/haddock/html-test/ref/haddock-util.js - + utils/haddock/html-test/ref/hslogo-16.png - + utils/haddock/html-test/ref/mini_A.html - + utils/haddock/html-test/ref/mini_AdvanceTypes.html - + utils/haddock/html-test/ref/mini_B.html - + utils/haddock/html-test/ref/mini_Bug1.html - + utils/haddock/html-test/ref/mini_Bug2.html - + utils/haddock/html-test/ref/mini_Bug3.html - + utils/haddock/html-test/ref/mini_Bug4.html - + utils/haddock/html-test/ref/mini_Bug6.html - + utils/haddock/html-test/ref/mini_Bug7.html - + utils/haddock/html-test/ref/mini_Bug8.html - + utils/haddock/html-test/ref/mini_BugDeprecated.html - + utils/haddock/html-test/ref/mini_BugExportHeadings.html - + utils/haddock/html-test/ref/mini_Bugs.html - + utils/haddock/html-test/ref/mini_CrossPackageDocs.html - + utils/haddock/html-test/ref/mini_DeprecatedClass.html - + utils/haddock/html-test/ref/mini_DeprecatedData.html - + utils/haddock/html-test/ref/mini_DeprecatedFunction.html - + utils/haddock/html-test/ref/mini_DeprecatedFunction2.html - + utils/haddock/html-test/ref/mini_DeprecatedFunction3.html - + utils/haddock/html-test/ref/mini_DeprecatedModule.html - + utils/haddock/html-test/ref/mini_DeprecatedModule2.html - + utils/haddock/html-test/ref/mini_DeprecatedNewtype.html - + utils/haddock/html-test/ref/mini_DeprecatedReExport.html - + utils/haddock/html-test/ref/mini_DeprecatedRecord.html - + utils/haddock/html-test/ref/mini_DeprecatedTypeFamily.html - + utils/haddock/html-test/ref/mini_DeprecatedTypeSynonym.html - + utils/haddock/html-test/ref/mini_Examples.html - + utils/haddock/html-test/ref/mini_FunArgs.html - + utils/haddock/html-test/ref/mini_GADTRecords.html - + utils/haddock/html-test/ref/mini_Hash.html - + utils/haddock/html-test/ref/mini_HiddenInstances.html - + utils/haddock/html-test/ref/mini_HiddenInstancesB.html - + utils/haddock/html-test/ref/mini_Hyperlinks.html - + utils/haddock/html-test/ref/mini_IgnoreExports.html - + utils/haddock/html-test/ref/mini_Math.html - + utils/haddock/html-test/ref/mini_ModuleWithWarning.html - + utils/haddock/html-test/ref/mini_NamedDoc.html - + utils/haddock/html-test/ref/mini_NoLayout.html - + utils/haddock/html-test/ref/mini_NonGreedy.html - + utils/haddock/html-test/ref/mini_Properties.html - + utils/haddock/html-test/ref/mini_PruneWithWarning.html - + utils/haddock/html-test/ref/mini_QuasiExpr.html - + utils/haddock/html-test/ref/mini_QuasiQuote.html - + utils/haddock/html-test/ref/mini_SpuriousSuperclassConstraints.html - + utils/haddock/html-test/ref/mini_TH.html - + utils/haddock/html-test/ref/mini_TH2.html - + utils/haddock/html-test/ref/mini_Test.html - + utils/haddock/html-test/ref/mini_Ticket112.html - + utils/haddock/html-test/ref/mini_Ticket253_1.html - + utils/haddock/html-test/ref/mini_Ticket253_2.html - + utils/haddock/html-test/ref/mini_Ticket61.html - + utils/haddock/html-test/ref/mini_Ticket75.html - + utils/haddock/html-test/ref/mini_TitledPicture.html - + utils/haddock/html-test/ref/mini_TypeFamilies.html - + utils/haddock/html-test/ref/mini_TypeOperators.html - + utils/haddock/html-test/ref/mini_Unicode.html - + utils/haddock/html-test/ref/mini_Visible.html - + utils/haddock/html-test/ref/minus.gif - + utils/haddock/html-test/ref/ocean.css - + utils/haddock/html-test/ref/plus.gif - + utils/haddock/html-test/ref/synopsis.png - + utils/haddock/html-test/run - + utils/haddock/html-test/src/A.hs - + utils/haddock/html-test/src/B.hs - + utils/haddock/html-test/src/Bold.hs - + utils/haddock/html-test/src/Bug1.hs - + utils/haddock/html-test/src/Bug1004.hs - + utils/haddock/html-test/src/Bug1033.hs - + utils/haddock/html-test/src/Bug1035.hs - + utils/haddock/html-test/src/Bug1050.hs - + utils/haddock/html-test/src/Bug1054.hs - + utils/haddock/html-test/src/Bug1063.hs - + utils/haddock/html-test/src/Bug1067A.hs - + utils/haddock/html-test/src/Bug1067B.hs - + utils/haddock/html-test/src/Bug1103.hs - + utils/haddock/html-test/src/Bug195.hs - + utils/haddock/html-test/src/Bug2.hs - + utils/haddock/html-test/src/Bug201.hs - + utils/haddock/html-test/src/Bug253.hs - + utils/haddock/html-test/src/Bug26.hs - + utils/haddock/html-test/src/Bug280.hs - + utils/haddock/html-test/src/Bug294.hs - + utils/haddock/html-test/src/Bug298.hs - + utils/haddock/html-test/src/Bug3.hs - + utils/haddock/html-test/src/Bug308.hs - + utils/haddock/html-test/src/Bug308CrossModule.hs - + utils/haddock/html-test/src/Bug310.hs - + utils/haddock/html-test/src/Bug313.hs - + utils/haddock/html-test/src/Bug335.hs - + utils/haddock/html-test/src/Bug4.hs - + utils/haddock/html-test/src/Bug458.hs - + utils/haddock/html-test/src/Bug466.hs - + utils/haddock/html-test/src/Bug546.hs - + utils/haddock/html-test/src/Bug548.hs - + utils/haddock/html-test/src/Bug574.hs - + utils/haddock/html-test/src/Bug6.hs - + utils/haddock/html-test/src/Bug613.hs - + utils/haddock/html-test/src/Bug647.hs - + utils/haddock/html-test/src/Bug679.hs - + utils/haddock/html-test/src/Bug7.hs - + utils/haddock/html-test/src/Bug8.hs - + utils/haddock/html-test/src/Bug85.hs - + utils/haddock/html-test/src/Bug865.hs - + utils/haddock/html-test/src/Bug923.hs - + utils/haddock/html-test/src/Bug952.hs - + utils/haddock/html-test/src/Bug953.hs - + utils/haddock/html-test/src/Bug973.hs - + utils/haddock/html-test/src/BugDeprecated.hs - + utils/haddock/html-test/src/BugExportHeadings.hs - + utils/haddock/html-test/src/Bugs.hs - + utils/haddock/html-test/src/BundledPatterns.hs - + utils/haddock/html-test/src/BundledPatterns2.hs - + utils/haddock/html-test/src/ConstructorArgs.hs - + utils/haddock/html-test/src/ConstructorPatternExport.hs - + utils/haddock/html-test/src/CrossPackageDocs.hs_hidden - + utils/haddock/html-test/src/DefaultAssociatedTypes.hs - + utils/haddock/html-test/src/DefaultSignatures.hs - + utils/haddock/html-test/src/DeprecatedClass.hs - + utils/haddock/html-test/src/DeprecatedData.hs - + utils/haddock/html-test/src/DeprecatedFunction.hs - + utils/haddock/html-test/src/DeprecatedFunction2.hs - + utils/haddock/html-test/src/DeprecatedFunction3.hs - + utils/haddock/html-test/src/DeprecatedModule.hs - + utils/haddock/html-test/src/DeprecatedModule2.hs - + utils/haddock/html-test/src/DeprecatedNewtype.hs - + utils/haddock/html-test/src/DeprecatedReExport.hs - + utils/haddock/html-test/src/DeprecatedRecord.hs - + utils/haddock/html-test/src/DeprecatedTypeFamily.hs - + utils/haddock/html-test/src/DeprecatedTypeSynonym.hs - + utils/haddock/html-test/src/DuplicateRecordFields.hs - + utils/haddock/html-test/src/Examples.hs - + utils/haddock/html-test/src/ExportSince1.hs - + utils/haddock/html-test/src/ExportSince2.hs - + utils/haddock/html-test/src/Extensions.hs - + utils/haddock/html-test/src/FunArgs.hs - + utils/haddock/html-test/src/GADTRecords.hs - + utils/haddock/html-test/src/GadtConstructorArgs.hs - + utils/haddock/html-test/src/Hash.hs - + utils/haddock/html-test/src/Hidden.hs - + utils/haddock/html-test/src/HiddenInstances.hs - + utils/haddock/html-test/src/HiddenInstancesA.hs - + utils/haddock/html-test/src/HiddenInstancesB.hs - + utils/haddock/html-test/src/Hyperlinks.hs - + utils/haddock/html-test/src/Identifiers.hs - + utils/haddock/html-test/src/IgnoreExports.hs - + utils/haddock/html-test/src/ImplicitParams.hs - + utils/haddock/html-test/src/Instances.hs - + utils/haddock/html-test/src/LinearTypes.hs - + utils/haddock/html-test/src/Math.hs - + utils/haddock/html-test/src/Minimal.hs - + utils/haddock/html-test/src/ModuleWithWarning.hs - + utils/haddock/html-test/src/NamedDoc.hs - + utils/haddock/html-test/src/NamespacedIdentifiers.hs - + utils/haddock/html-test/src/Nesting.hs - + utils/haddock/html-test/src/NoLayout.hs - + utils/haddock/html-test/src/NonGreedy.hs - + utils/haddock/html-test/src/Operators.hs - + utils/haddock/html-test/src/OrphanInstances.hs - + utils/haddock/html-test/src/OrphanInstancesClass.hs - + utils/haddock/html-test/src/OrphanInstancesType.hs - + utils/haddock/html-test/src/PR643.hs - + utils/haddock/html-test/src/PR643_1.hs - + utils/haddock/html-test/src/PatternSyns.hs - + utils/haddock/html-test/src/PromotedTypes.hs - + utils/haddock/html-test/src/Properties.hs - + utils/haddock/html-test/src/PruneWithWarning.hs - + utils/haddock/html-test/src/QuantifiedConstraints.hs - + utils/haddock/html-test/src/QuasiExpr.hs - + utils/haddock/html-test/src/QuasiQuote.hs - + utils/haddock/html-test/src/SectionLabels.hs - + utils/haddock/html-test/src/SpuriousSuperclassConstraints.hs - + utils/haddock/html-test/src/T23616.hs - + utils/haddock/html-test/src/T24294.hs - + utils/haddock/html-test/src/TH.hs - + utils/haddock/html-test/src/TH2.hs - + utils/haddock/html-test/src/Table.hs - + utils/haddock/html-test/src/Test.hs - + utils/haddock/html-test/src/Threaded.hs - + utils/haddock/html-test/src/Threaded_TH.hs - + utils/haddock/html-test/src/Ticket112.hs - + utils/haddock/html-test/src/Ticket61.hs - + utils/haddock/html-test/src/Ticket61_Hidden.hs - + utils/haddock/html-test/src/Ticket75.hs - + utils/haddock/html-test/src/TitledPicture.hs - + utils/haddock/html-test/src/TypeFamilies.hs - + utils/haddock/html-test/src/TypeFamilies2.hs - + utils/haddock/html-test/src/TypeFamilies3.hs - + utils/haddock/html-test/src/TypeOperators.hs - + utils/haddock/html-test/src/UnboxedStuff.hs - + utils/haddock/html-test/src/Unicode.hs - + utils/haddock/html-test/src/Unicode2.hs - + utils/haddock/html-test/src/Visible.hs - + utils/haddock/hypsrc-test/Main.hs - + utils/haddock/hypsrc-test/ref/src/Bug1091.html - + utils/haddock/hypsrc-test/ref/src/CPP.html - + utils/haddock/hypsrc-test/ref/src/CallingQuotes.html - + utils/haddock/hypsrc-test/ref/src/Classes.html - + utils/haddock/hypsrc-test/ref/src/Constructors.html - + utils/haddock/hypsrc-test/ref/src/Identifiers.html - + utils/haddock/hypsrc-test/ref/src/LinkingIdentifiers.html - + utils/haddock/hypsrc-test/ref/src/Literals.html - + utils/haddock/hypsrc-test/ref/src/Operators.html - + utils/haddock/hypsrc-test/ref/src/Polymorphism.html - + utils/haddock/hypsrc-test/ref/src/PositionPragmas.html - + utils/haddock/hypsrc-test/ref/src/Quasiquoter.html - + utils/haddock/hypsrc-test/ref/src/Records.html - + utils/haddock/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html - + utils/haddock/hypsrc-test/ref/src/TemplateHaskellSplices.html - + utils/haddock/hypsrc-test/ref/src/Types.html - + utils/haddock/hypsrc-test/ref/src/UsingQuasiquotes.html - + utils/haddock/hypsrc-test/run - + utils/haddock/hypsrc-test/src/Bug1091.hs - + utils/haddock/hypsrc-test/src/CPP.hs - + utils/haddock/hypsrc-test/src/Classes.hs - + utils/haddock/hypsrc-test/src/Constructors.hs - + utils/haddock/hypsrc-test/src/Identifiers.hs - + utils/haddock/hypsrc-test/src/Include1For1091.h - + utils/haddock/hypsrc-test/src/Include2For1091.h - + utils/haddock/hypsrc-test/src/LinkingIdentifiers.hs - + utils/haddock/hypsrc-test/src/Literals.hs - + utils/haddock/hypsrc-test/src/Operators.hs - + utils/haddock/hypsrc-test/src/Polymorphism.hs - + utils/haddock/hypsrc-test/src/PositionPragmas.hs - + utils/haddock/hypsrc-test/src/Quasiquoter.hs - + utils/haddock/hypsrc-test/src/Records.hs - + utils/haddock/hypsrc-test/src/TemplateHaskellQuasiquotes.hs - + utils/haddock/hypsrc-test/src/TemplateHaskellSplices.hs - + utils/haddock/hypsrc-test/src/Types.hs - + utils/haddock/hypsrc-test/src/UsingQuasiquotes.hs - + utils/haddock/latex-test/Main.hs - + utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex - + utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex - + utils/haddock/latex-test/ref/Deprecated/Deprecated.tex - + utils/haddock/latex-test/ref/Example/Example.tex - + utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex - + utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex - + utils/haddock/latex-test/ref/LinearTypes/haddock.sty - + utils/haddock/latex-test/ref/LinearTypes/main.tex - + utils/haddock/latex-test/ref/NamespacedIdentifier/NamespacedIdentifiers.tex - + utils/haddock/latex-test/ref/Simple/Simple.tex - + utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex - + utils/haddock/latex-test/ref/UnboxedStuff/UnboxedStuff.tex - + utils/haddock/latex-test/run - + utils/haddock/latex-test/src/ConstructorArgs/ConstructorArgs.hs - + utils/haddock/latex-test/src/DefaultSignatures/DefaultSignatures.hs - + utils/haddock/latex-test/src/Deprecated/Deprecated.hs - + utils/haddock/latex-test/src/Example/Example.hs - + utils/haddock/latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs - + utils/haddock/latex-test/src/LinearTypes/LinearTypes.hs - + utils/haddock/latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs - + utils/haddock/latex-test/src/Simple/Simple.hs - + utils/haddock/latex-test/src/TypeFamilies3/TypeFamilies3.hs - + utils/haddock/latex-test/src/UnboxedStuff/UnboxedStuff.hs - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/hp2ps/hp2ps.wrapper - utils/hpc - utils/hsc2hs - − utils/iserv/Makefile - utils/iserv/cbits/iservmain.c - utils/iserv/iserv.cabal.in - + utils/jsffi/dyld.mjs - + utils/jsffi/post-link.mjs - + utils/jsffi/prelude.mjs - + utils/jsffi/test-runner.mjs - utils/llvm-targets/gen-data-layout.sh - − utils/lndir/lndir-Xos.h - − utils/lndir/lndir-Xosdefs.h - − utils/lndir/lndir.c - − utils/remote-iserv/Makefile - utils/runghc/Main.hs - − utils/runghc/Makefile - − utils/runghc/runghc.wrapper - − utils/touchy/Makefile - − utils/touchy/touchy.c - − utils/touchy/touchy.cabal - − utils/unlit/Makefile - − utils/vagrant/bootstrap-deb.sh - − utils/vagrant/bootstrap-rhel.sh The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e1e3a8f45c58dd2cf40b9662a8bdb6ce4f8395ef...c8c660f678bd77fb9d0a855753a165c5a5d1f8e1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e1e3a8f45c58dd2cf40b9662a8bdb6ce4f8395ef...c8c660f678bd77fb9d0a855753a165c5a5d1f8e1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/175852e0/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 16:41:26 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 06 Mar 2025 11:41:26 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 14 commits: perf: Speed up the bytecode assembler Message-ID: <67c9d036796f8_27ef34c86e06959b@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - b371b8f1 by Matthew Craven at 2025-03-06T11:41:13-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 2ea584c4 by Matthew Craven at 2025-03-06T11:41:13-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 999112be by Matthew Craven at 2025-03-06T11:41:13-05:00 Add tests for #25771 - - - - - 89 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/wasm/JSFFI.c - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa358306e0ea578577c7113ac68614b4a479ab00...999112bef6804efb851a5a5042e833bf55b875bb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa358306e0ea578577c7113ac68614b4a479ab00...999112bef6804efb851a5a5042e833bf55b875bb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/6ffa63fc/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 20:03:31 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 06 Mar 2025 15:03:31 -0500 Subject: [Git][ghc/ghc][wip/wasm-fix-lto] rts: avoid building unused cbits on wasm Message-ID: <67c9ff92ea5f3_2cbb3837d28c1077d@gitlab.mail> Cheng Shao pushed to branch wip/wasm-fix-lto at Glasgow Haskell Compiler / GHC Commits: b1aa570d by Cheng Shao at 2025-03-06T20:03:03+00:00 rts: avoid building unused cbits on wasm This commit avoids building rts cbits that aren't used when targetting wasm. The main motivation is getting rid of spurious LTO-specific link-time error messages when building the rts with LLVM LTO mode. - - - - - 1 changed file: - rts/rts.cabal Changes: ===================================== rts/rts.cabal ===================================== @@ -399,10 +399,7 @@ library if arch(ppc) || arch(ppc64) || arch(s390x) || arch(riscv64) || arch(loongarch64) asm-sources: StgCRunAsm.S - c-sources: Adjustor.c - adjustor/AdjustorPool.c - ExecPage.c - Arena.c + c-sources: Arena.c Capability.c CheckUnload.c CheckVectorSupport.c @@ -425,7 +422,6 @@ library Libdw.c LibdwPool.c Linker.c - ReportMemoryMap.c Messages.c OldARMAtomic.c PathUtils.c @@ -446,8 +442,6 @@ library RtsMain.c RtsMessages.c RtsStartup.c - RtsSymbolInfo.c - RtsSymbols.c RtsUtils.c STM.c Schedule.c @@ -481,28 +475,6 @@ library hooks/OnExit.c hooks/OutOfHeap.c hooks/StackOverflow.c - linker/CacheFlush.c - linker/Elf.c - linker/InitFini.c - linker/LoadArchive.c - linker/LoadNativeObjPosix.c - linker/M32Alloc.c - linker/MMap.c - linker/MachO.c - linker/macho/plt.c - linker/macho/plt_aarch64.c - linker/PEi386.c - linker/SymbolExtras.c - linker/elf_got.c - linker/elf_plt.c - linker/elf_plt_aarch64.c - linker/elf_plt_riscv64.c - linker/elf_plt_arm.c - linker/elf_reloc.c - linker/elf_reloc_aarch64.c - linker/elf_reloc_riscv64.c - linker/elf_tlsgd.c - linker/elf_util.c sm/BlockAlloc.c sm/CNF.c sm/Compact.c @@ -529,6 +501,50 @@ library -- I wish we had wildcards..., this would be: -- *.c hooks/**/*.c sm/**/*.c eventlog/**/*.c linker/**/*.c + -- These source files are not actually used by the wasm backend + -- RTS. There's no point in building them, and they actually + -- break certain configurations (e.g. LLVM LTO). + if !arch(wasm32) + c-sources: + -- Wasm code is not in linear memory space + adjustor/AdjustorPool.c + Adjustor.c + ExecPage.c + + -- Wasm dyld does not need these to be linked into + -- rts + RtsSymbolInfo.c + RtsSymbols.c + + -- Wasm has no real mmap + ReportMemoryMap.c + + -- Wasm dyld does not use any existing RTS linker + -- logic + linker/CacheFlush.c + linker/Elf.c + linker/InitFini.c + linker/LoadArchive.c + linker/LoadNativeObjPosix.c + linker/M32Alloc.c + linker/MMap.c + linker/MachO.c + linker/macho/plt.c + linker/macho/plt_aarch64.c + linker/PEi386.c + linker/SymbolExtras.c + linker/elf_got.c + linker/elf_plt.c + linker/elf_plt_aarch64.c + linker/elf_plt_riscv64.c + linker/elf_plt_arm.c + linker/elf_reloc.c + linker/elf_reloc_aarch64.c + linker/elf_reloc_riscv64.c + linker/elf_tlsgd.c + linker/elf_util.c + + if os(windows) c-sources: win32/AsyncMIO.c win32/AsyncWinIO.c View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1aa570ddb11a006e8fc209be8e6e7b5f8801939 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1aa570ddb11a006e8fc209be8e6e7b5f8801939 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/2476d725/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 20:05:34 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 06 Mar 2025 15:05:34 -0500 Subject: [Git][ghc/ghc][wip/wasm-fix-lto] rts: avoid building unused cbits on wasm Message-ID: <67ca000ebe0a3_2cbb3837d0e8135f5@gitlab.mail> Cheng Shao pushed to branch wip/wasm-fix-lto at Glasgow Haskell Compiler / GHC Commits: 488caa0b by Cheng Shao at 2025-03-06T20:05:24+00:00 rts: avoid building unused cbits on wasm This commit avoids building rts cbits that aren't used when targetting wasm. The main motivation is getting rid of spurious LTO-specific link-time error messages when building the rts with LLVM LTO mode. - - - - - 1 changed file: - rts/rts.cabal Changes: ===================================== rts/rts.cabal ===================================== @@ -399,10 +399,7 @@ library if arch(ppc) || arch(ppc64) || arch(s390x) || arch(riscv64) || arch(loongarch64) asm-sources: StgCRunAsm.S - c-sources: Adjustor.c - adjustor/AdjustorPool.c - ExecPage.c - Arena.c + c-sources: Arena.c Capability.c CheckUnload.c CheckVectorSupport.c @@ -425,7 +422,6 @@ library Libdw.c LibdwPool.c Linker.c - ReportMemoryMap.c Messages.c OldARMAtomic.c PathUtils.c @@ -446,8 +442,6 @@ library RtsMain.c RtsMessages.c RtsStartup.c - RtsSymbolInfo.c - RtsSymbols.c RtsUtils.c STM.c Schedule.c @@ -481,28 +475,6 @@ library hooks/OnExit.c hooks/OutOfHeap.c hooks/StackOverflow.c - linker/CacheFlush.c - linker/Elf.c - linker/InitFini.c - linker/LoadArchive.c - linker/LoadNativeObjPosix.c - linker/M32Alloc.c - linker/MMap.c - linker/MachO.c - linker/macho/plt.c - linker/macho/plt_aarch64.c - linker/PEi386.c - linker/SymbolExtras.c - linker/elf_got.c - linker/elf_plt.c - linker/elf_plt_aarch64.c - linker/elf_plt_riscv64.c - linker/elf_plt_arm.c - linker/elf_reloc.c - linker/elf_reloc_aarch64.c - linker/elf_reloc_riscv64.c - linker/elf_tlsgd.c - linker/elf_util.c sm/BlockAlloc.c sm/CNF.c sm/Compact.c @@ -529,6 +501,49 @@ library -- I wish we had wildcards..., this would be: -- *.c hooks/**/*.c sm/**/*.c eventlog/**/*.c linker/**/*.c + -- These source files are not actually used by the wasm backend + -- RTS. There's no point in building them, and they actually + -- break certain configurations (e.g. LLVM LTO). + if !arch(wasm32) + c-sources: + -- Wasm code is not in linear memory space + adjustor/AdjustorPool.c + Adjustor.c + ExecPage.c + + -- Wasm dyld does not need these to be linked into + -- rts + RtsSymbolInfo.c + RtsSymbols.c + + -- Wasm has no real mmap + ReportMemoryMap.c + + -- Wasm dyld does not use any existing RTS linker + -- logic + linker/CacheFlush.c + linker/Elf.c + linker/InitFini.c + linker/LoadArchive.c + linker/LoadNativeObjPosix.c + linker/M32Alloc.c + linker/MMap.c + linker/MachO.c + linker/macho/plt.c + linker/macho/plt_aarch64.c + linker/PEi386.c + linker/SymbolExtras.c + linker/elf_got.c + linker/elf_plt.c + linker/elf_plt_aarch64.c + linker/elf_plt_riscv64.c + linker/elf_plt_arm.c + linker/elf_reloc.c + linker/elf_reloc_aarch64.c + linker/elf_reloc_riscv64.c + linker/elf_tlsgd.c + linker/elf_util.c + if os(windows) c-sources: win32/AsyncMIO.c win32/AsyncWinIO.c View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/488caa0bf50ce7db3bf9be548f0edd9a8197ce25 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/488caa0bf50ce7db3bf9be548f0edd9a8197ce25 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/339231c8/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 20:08:55 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Thu, 06 Mar 2025 15:08:55 -0500 Subject: [Git][ghc/ghc][wip/andreask/arm_mem_model] 239 commits: ghc-internal: Drop GHC.Internal.Data.Enum Message-ID: <67ca00d755af6_2cbb384f92c8138a6@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/arm_mem_model at Glasgow Haskell Compiler / GHC Commits: 55d8304e by Ben Gamari at 2024-12-06T16:56:00-05:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - 56b9f484 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 336d392e by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - dd7ca939 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Mention incorrect Data.Enum addition in changelog - - - - - dfd1db48 by Ben Gamari at 2024-12-06T16:56:36-05:00 base: Reintroduce {Show,Enum} IoSubSystem These instances were dropped in !9676 but not approved by the CLC. Addresses #25549. - - - - - 090fc7c1 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements on T25240 T25240 doesn't need RTS linker, GHCi is sufficient and GHCi can also be dynamically linked. - - - - - 3fb5d399 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements for T25155 Loading C objects requires RTS linker. - - - - - 4c58bdf6 by Leary at 2024-12-07T03:42:07-05:00 TH: Add typed variants of dataToExpQ and liftData This commit introduces to template-haskell (via ghc-internal) two functions `dataToCodeQ` and `liftDataTyped`, typed variants of `dataToExpQ` and `liftData` respectively. Tested in: `dataToCodeQUnit`. - - - - - 63027593 by Serge S. Gulin at 2024-12-08T13:52:05+03:00 JS: Basic cleanup for unused stuff to simplify things. 1. Make `staticInitStat`, `staticDeclStat`, `allocUnboxedConStatic`, `allocateStaticList`, `jsStaticArg` local to modules. 2. Remove unused `hdRawStr`, `hdStrStr` from Haskell and JavaScript (`h$pstr`, `h$rstr`, `h$str`). 3. Introduce a special type `StaticAppKind` enumeration and `StaticApp` to represent boxed scalar static applications. Originally, StaticThunk supported to pass Maybe when it became Nothing for initializied thunks in an alternatie way but it is not used anymore. - - - - - a9f8f1fb by Serge S. Gulin at 2024-12-08T14:10:45+03:00 JS: Add trivial optimizations for `unpackCString` and `unpackCStringUtf8`. It became possible due of introduction strings unfloating at Sinker pass (#13185). Earns few more bytes at optimizations. - - - - - b519c06b by Serge S. Gulin at 2024-12-08T15:50:26+03:00 JS: Specialize unpackCString# CAFs (fixes #24744) Code analysis shown that such optimization would be possible out of the box if `cachedIdentForId` allowed to do that for Haskell `Id`s which are represented by few JavaScript `Ident`s. It is a usual for strings which are represented at JavaScript as a pair of 2 values: the string content and the offset where to start reading actual string from the full content. Usually offset is 0 but technically we need to allow such complex structures to be treated as "global". Enabling it there shown that `genToplevelRhs` and `globalOccs` had inaccuracies in their implementations: 1. `globalOccs` operated over JavaScript's `Ident`s but for complex structures it didn't pay attention to the fact that different Idents actually could be pointed to same Id. Now the algo is changed to calculate occurencies for Ids. 2. `genToplevelRhs` didn't assume that different Idents pointed to same Id can have mixed order of occurence. But actually the order is important. Strings are encoded into 2 variables where first is content and second is offset and their order are not interchangeable. It is fixed by regeneration Idents from collected Ids which is fine because all Idents generation is passed through the Cache and they are quasi-stable. - - - - - a8ceccf3 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Fix panic in multiline string with unterminated gap (#25530) - - - - - 9e464ad0 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Add test case for unterminated multiline string - - - - - ed1ed5c6 by Rodrigo Mesquita at 2024-12-09T16:26:19-05:00 Revert mapMG renaming We had previously renamed this function for consistency, but that caused unnecessary breakage - - - - - 158261f7 by Sylvain Henry at 2024-12-09T16:27:01-05:00 RTS: make Cabal flags manual Cabal shouldn't automatically try to set them. We set them explicitly. - - - - - a83b7ed6 by Matthew Stephenson at 2024-12-10T14:01:22-05:00 Add missing @since documentation for (!?) function - - - - - e745e3a3 by Ben Gamari at 2024-12-10T14:01:59-05:00 compiler: Don't attempt to TSAN-instrument SIMD operations TSAN only provides instrumentation for 8, 16, 32, and 64-bit memory loads/stores. Don't attempt to instrument wider operations. Fixes #25563. - - - - - 684c0018 by Ben Gamari at 2024-12-10T14:02:35-05:00 gitlab/ci: Don't clobber RUNTEST_ARGS Previously the logic handling `IGNORE_PERF_FAILURES` clobbered the user's `RUNTEST_ARGS`. Fix this. - - - - - 41dae5b8 by Ben Gamari at 2024-12-10T14:03:11-05:00 hadrian: Mitigate mktexfmt race At least some versions of Texlive's `mktexfmt` utility cannot be invoked concurrently in their initial run since they fail to handle failure of `mkdir` due to racing. Specifically, we see ``` | Run Xelatex: users_guide.tex => /tmp/extra-dir-9616886274866 | Run Xelatex: Haddock.tex => /tmp/extra-dir-9616886274869 This is XeTeX, Version 3.14159265-2.6-0.999992 (TeX Live 2020) (preloaded format=xelatex) restricted \write18 enabled. kpathsea: Running mktexfmt xelatex.fmt mktexfmt: mktexfmt is using the following fmtutil.cnf files (in precedence order): mktexfmt: /usr/share/texlive/texmf-dist/web2c/fmtutil.cnf mktexfmt: mktexfmt is using the following fmtutil.cnf file for writing changes: mktexfmt: /builds/ghc/ghc/tmp-home/.texlive2020/texmf-config/web2c/fmtutil.cnf /usr/bin/mktexfmt: mkdir(/builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c/) failed for tree /builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c: File exists at /usr/share/texlive/tlpkg/TeXLive/TLUtils.pm line 937. I can't find the format file `xelatex.fmt'! ``` That is two `mktexfmt` invocations (for the user's guide and haddock builds) attempted to create `$HOME/texlive2020/texmf-var/web2c` and raced. One of the two `mkdir`'s consequently failed, bringing down the entire build. We avoid this by ensuring that the first `xelatex` invocation is always performed serially. Fixes #25564. - - - - - 9efbc51f by Ben Gamari at 2024-12-10T14:03:48-05:00 rts/CheckUnload: Reset old_objects if unload is skipped Previously `checkUnload` failed to reset `old_objects` when it decided not to unload (e.g. due to heap profiling being enabled). Fixes #24935. - - - - - 5192a75f by Ben Gamari at 2024-12-11T04:28:11-05:00 rts: Annotate BCOs with their Name This introduces a new bytecode instruction, `BCO_NAME`, to aid in debugging bytecode execution. This instruction is injected by `mkProtoBCO` and captures the Haskell name of the BCO. It is then printed by the disassembler, allowing ready correlation with STG dumps. - - - - - 99225996 by Ben Gamari at 2024-12-11T04:28:48-05:00 configure: Implement ld override whitelist Bring `configure` into alignment with `ghc-toolchain`, ensuring that the ld-override logic will only take effect on Linux and Windows. Fixes #25501. - - - - - 4a8fc928 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Unmark T14028 as broken on FreeBSD This now appears to pass on FreeBSD 14. Closes #19723. - - - - - d7c0eb5a by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Migrate FreeBSD runner tag to FreeBSD 14 - - - - - 7246dacc by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Reintroduce FreeBSD 14 job - - - - - 4af936da by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Allow use of newer cabal-install bindists Newer cabal-install bindists have internal directory structure. Here we detect and account for the presence of such structure. - - - - - cbf38c1b by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Enable documentation build on FreeBSD 14 - - - - - d68107fb by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Use system libffi on FreeBSD - - - - - fea3b590 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark linker_unload as broken on FreeeBSD Due to #25491. - - - - - ccf171ee by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Prefer system toolchain on FreeBSD It's not uncommon to find machines with gcc installed via ports. We should be using the system's default clang-based toolchain instead. - - - - - cfb34738 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T21969 as broken on FreeBSD Due to #25512. - - - - - 0b64e37c by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark RestartEventLogging as broken on FreeBSD I am seeing this fail quite reproducibly. Due to #19724. - - - - - 3b412019 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T16180 as "broken" on FreeBSD Sadly we in fact need to skip it as it merely times out during compilation. See #14012. - - - - - 57e3cab5 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Skip T16992 unless in slow speed This test has extraordinary memory requirements and tests a rather niche aspect of the compact region mechanism. It has been suggested multiple times that we shouldn't run it in the default testsuite configuration. Finally implement this. See #21890. See #21892. - - - - - f08a72eb by Ben Gamari at 2024-12-11T19:30:54-05:00 rts(setNumCapabilities): Assert that n_caps < MAX_N_CAPS It was noticed in #25560 that this would previously be allowed, resulting in a segfault. I will add a proper exception in `base` in a future commit. - - - - - e10d31ad by Ben Gamari at 2024-12-11T19:30:55-05:00 ghc-internal: Fix inconsistent FFI import types The foreign imports of `enabled_capabilities` and `getNumberOfProcessors` were declared as `CInt` whereas they are defined as `uint32_t`. - - - - - 06265655 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Mention maximum capability count in users guide Addresses #25560. - - - - - d488470b by Ben Gamari at 2024-12-11T19:30:55-05:00 rts/Capability: Move induction variable declaration into `for`s Just a stylistic change. - - - - - 71f050b7 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Determine max_n_capabilities at RTS startup Previously the maximum number of capabilities supported by the RTS was statically capped at 256. However, this bound is uncomfortably low given the size of today's machine. While supporting unbounded, fully-dynamic adjustment would be nice, it is complex and so instead we do something simpler: Probe the logical core count at RTS startup and use this as the static bound for the rest of our execution. This should avoid users running into the capability limit on large machines while avoiding wasting memory on a large capabilities array for most users and keeping complexity at bay. Addresses #25560. - - - - - 1e84b411 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Introduce req_c_rts As suggested by @hsyl20, this is intended to mark tests that rely on the behavior of the C RTS. - - - - - 683115a4 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Add test for #25560 - - - - - ef2052a8 by Ben Gamari at 2024-12-12T04:42:32-05:00 testsuite: Only run T14497_compact in normal way This test targets the compacting GC so it makes little sense to run it across all ways. Moreover, it outright conflicts with the `nonmoving` way. - - - - - 34d3e8e6 by Ben Gamari at 2024-12-12T04:43:08-05:00 rts/CheckUnload: Don't prepare to unload if we can't unload Previously `prepareUnloadCheck` would move the `objects` list to `old_objects` even when profiling (where we cannot unload). This caused us to vacate the `objects` list during major GCs, losing track of loaded objects. Fix this by ensuring that `prepareUnloadCheck` and `checkUnload` both use the same short-cutting logic. - - - - - 9c53489d by Andrei Borzenkov at 2024-12-12T15:06:42-05:00 Update GHCi :info type declaration printing (#24459) - Do not print result's kind in type families because we have full kind in SAKS and we display invisible arity using @-binders - Do not suppress significant invisible binders An invisible binder is considered significant when it meets at least one of the following two criteria: - It visibly occurs in the declaration's body - It is followed by a significant binder, so it affects positioning For non-generative type declarations (type synonyms and type families) there is one additional criterion: - It is not followed by a visible binder, so it affects the arity of a type synonym See Note [Print invisible binders in interface declarations] for more information about what is "visibly occurs" - - - - - 13fe48d4 by Matthew Pickering at 2024-12-12T15:07:19-05:00 typechecker: Perform type family consistency checks in topological order Consider a module M importing modules A, B and C. We can waste a lot of work depending on the order that the modules are checked for family consistency. Consider that C imports A and B. When compiling C we must have already checked A and B for consistency, therefore if C is processed first then A and B will not need to be checked for consistency again. If A and B are compared first, then the consistency checks will be performed against (wasted as we already performed them for C). At the moment the order which modules are checked is non-deterministic. Clearly we should engineer that C is checked before B and A, but by what scheme? A simple one is to observe that if a module M is in the transitive closure of X then the size of the consistent family set of M is less than or equal to size of the consistent family set of X. Therefore by sorting the imports by the size of the consistent family set and processing the largest first, you make sure to process modules in topological order. In practice we have observed that this strategy has reduced the amount of consistency checks performed. One solution to #25554 - - - - - 62a2b25f by Sylvain Henry at 2024-12-14T04:31:09-05:00 TNTC: set CmmProc entry_label properly (#25565) Before this patch we were renaming the entry label of a CmmProc late in the CmmToAsm pass. It led to inconsistencies and to some labels being used in info tables but not being emitted (#25565). Now we set the CmmProc entry label earlier in the StgToCmm monad and we don't renamed it afterwards. - - - - - b339e7c3 by Simon Hengel at 2024-12-14T04:31:47-05:00 Make filter functionality for system tools line-based This is more efficient as: - All existing filter functions were line-based anyway. They broke up the input into lines and then joined it back together. - We already break up the output from system tools into lines when processing it. Splitting up the output of system tools once and then filtering and processing it reduces both code and runtime complexity. - - - - - 39669077 by Simon Hengel at 2024-12-14T04:31:47-05:00 Refactoring: Don't use a `Chan` when parsing SysTools output - - - - - 64756530 by Simon Peyton Jones at 2024-12-14T22:28:04-05:00 Tidy up the handling of `assert` Fixes #25493 - - - - - 8658fbc1 by Rodrigo Mesquita at 2024-12-14T22:28:41-05:00 base: displayException for SomeAsyncException Provide a better implementation of `SomeException` for `SomeAsyncException`. The previous, implicit, implementation, would not use the `displayException` of the exception wrapped by `SomeAsyncException`. Implements CLC-Proposal#309 Closes #25513 - - - - - 2d3a0a70 by ARATA Mizuki at 2024-12-15T18:35:30-05:00 LLVM: When emitting a vector literal with ppTypeLit, include the type information Fixes #25561 - - - - - bfacc086 by Simon Peyton Jones at 2024-12-15T18:36:05-05:00 Fix signature lookup in instance declarations This fixes a bug introduced by the fix to #16610 - - - - - 80f0e02d by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Improve GHC build times Two small changes * In GHC.Data.Unboxed, never omit interface pragmas. In "fast builds" one might omit them generally, but doing so gives very bad performance for code that imports this module. * In GHC.Hs.Dump don't do type-class specialisation. For some reason it goes mad and generates vast amounts of useless code. See #25463. - - - - - 175a1355 by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Refactor Lint Refactor Lint for two reasons: * To improve performance * To prepare for type-lets The big changes are all in GHC.Core.Lint: * Change the main APIs: * `lintType` returns nothing rather than returning a `LintedType`; * `lintCoercion` return nothing rather than returning a `LintedCoercion` Reason: these functions did a lot of allocation to return a substituted type/coercion that was often discarded, or used only to extract its kind. Instead we now return nothing, and, when needed, extract the kind and substitute. * Applications are treated as a whole, by `lintApp`. By treating multiple arguments all at once we avoid performing multiple substitutions, each substituting a single type variable. This can make an absolutely huge difference. Overall this led to a pretty massive rewrite of Lint, with many smaller changes. Smaller chnages elsewhere * Rename `GHC.Core.TyCo.Subst.getSubstInScope` to `substInScopeSet` for consistency * Define and use `GHC.Core.Type.liftedTypeOrConstraintKind` Performance. This MR someimtes gives gives a very large improvement in compile time, when Lint is on. here is a selection of changes over 5% in perf/compiler (with -dcore-lint) T25196 -97.0% T14766 -89.7% T14683 -74.4% T5631 -60.9% T20261 -56.7% T18923 -17.6% T13035 -15.8% T6048 -15.8% CoOpt_Read -14.4% T9630 -10.9% T5642 -7.3% Eliminating the egregious offenders is a big win. However, in some cases the compiler allocation /increases/. Here ae the changes over 1%: T9961 1.5% T8095 2.8% T14052 3.9% T12545 4.5% T14052Type 5.5% T5030 8.0% T5321Fun 8.3% T3064 12.7% CoOpt_Singletons 15.6% T9198 16.0% LargeRecord 18.1% I looked at the two biggest increases in compile-time bytes allocated. Interestingly, they both show substantial *decreases* in actual compile time, due to much smaller GC times. I'm honestly not sure either why the allocation increases, or why the GC time decreases; but I'm going to take the win! T9198 Baseline With patch No Lint Alloc 44.6M 44.6M Mut time 0.23s 0.22s GC time 0.21s 0.21s With Lint Alloc 309M 360M Mut time 1.51s 0.85s GC time 2.97s 0.25s ------------------- LargeRecord Baseline With patch No Lint Alloc 1.37G 1.37G Mut time 2.33s 2.33s GC time 2.40s 2.42s With Lint Alloc 3.4G 4.0G Mut time 6.02s 5.68s GC time 3.67s 3.03s IMPORTANT NOTE: These changes don't show up in CI because in CI the tests in perf/compiler are all run with -dcore-lint switched off. I gathered this data with some manual runs. - - - - - 8ef2dad6 by Simon Peyton Jones at 2024-12-17T02:48:09-05:00 Add Note [Typechecking overloaded literals] See #25494. - - - - - e86b1b20 by Ben Gamari at 2024-12-17T13:51:39-05:00 testsuite: Use math.inf instead of division-by-zero This both more directly captures the intent and also fixes #25580. - - - - - 430d965a by Ben Gamari at 2024-12-17T13:52:15-05:00 rts: Fix incorrect format specifiers in era profiling Fixes #25581. - - - - - 267098ad by Andreas Klebinger at 2024-12-18T23:43:13-05:00 Document `-prof` and non `-prof` code being incompatible. Fixes #25518. - - - - - 04433916 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: output metadata fragment in CI (cherry picked from commit 52b58a660e735b20961d792d8fa9267f01247a50) - - - - - 7c78804e by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metatdata: use fedora33 for redhat Redhat 9 doesn't have libtinfo.so.5 anymore (cherry picked from commit dc86785eb43afd1bd292287c064fb5ad94fe8c7f) - - - - - 1d72cfb2 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: still use centos for redhat <9 - - - - - 3f7ebc58 by Sylvain Henry at 2024-12-19T20:40:14-05:00 Merge ghc-bignum into ghc-internal (#24453) First step towards merging ghc-bignum and ghc-prim into ghc-internal. After this patch, ghc-bignum is deprecated and is just a shallow package reexporting modules from ghc-internal and base. Use those directly instead. Move `gmp` submodule into ghc-internal directory. - - - - - ee0150c2 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Improve performance of deriving Show Significantly improves performance of deriving Show instances by avoiding using the very polymorphic `.` operator in favour of inlining its definition. We were generating tons of applications of it, each which had 3 type arguments! Improves on #9557 ------------------------- Metric Decrease: InstanceMatching T12707 T3294 ------------------------ - - - - - 8b266671 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Don't eta expand cons when deriving Data This eta expansion was introduced with the initial commit for Linear types. I believe this isn't needed any longer. My guess is it is an artifact from the initial linear types implementation: data constructors are linear, but they shouldn't need to be eta expanded to be used as higher order functions. I suppose in the early days this wasn't true. For instance, this works now: data T x = T x f = \(x :: forall y. y -> T y) -> x True f T -- ok! T is linear, but can be passed where an unrestricted higher order function is expected. I recall there being some magic around to make this work for data constructors... Since this works, there's no need to eta_expand the data constructors in the derived Data instances. - - - - - 1f67ad21 by Andrei Borzenkov at 2024-12-25T01:42:31-05:00 Flip the order of arguments of setField (#24668) GHC Proposal 583 "HasField redesign" specifies the following order of a setField function arguments as this: setField :: forall fld a b. SetField fld a b. b -> a -> a This patch flips the application order to match the spec. - - - - - 3e0c948d by Ben Gamari at 2024-12-25T01:43:08-05:00 rel-eng/upload: Add set_symlink mode This slightly eases updating of the `latest` symlinks. - - - - - 63d63f9d by Simon Peyton Jones at 2024-12-25T01:43:45-05:00 Preserve orientation when unifying kinds This MR fixes yet another manifestation of the trickiness caused by Note [Fundeps with instances, and equality orientation]. I wish there was a more robust way to do this, but this fix is a definite improvement. Fixes #25597 - - - - - 94ba9a6a by ARATA Mizuki at 2024-12-26T10:47:57-05:00 x86 NCG SIMD: Support pack/insert/broadcast/unpack of 128-bit integer vectors - - - - - 6bf0d587 by Andrew Lelechenko at 2024-12-26T10:48:33-05:00 docs: fix haddock formatting in Control.Monad.Fix - - - - - feb14af1 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Remove unnecessary irrefutable patterns from NonEmpty functions Implementation of https://github.com/haskell/core-libraries-committee/issues/107 - - - - - 6a0d91b4 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Make cons, Semigroup, IsList, and Monad instances stricter - - - - - 1249e597 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Restore some laziness in <| and Semigroup instance, improve Monad instance The Monad instance shouldn't produce the outer :| unless f a reduces to WHNF. (Notice that the b :| bs match is implicitly lazy.) - - - - - 8699d826 by Sergey Vinokurov at 2024-12-27T15:12:30+00:00 Add comment outlining Data.List.NonEmpty implementation guiding principles - - - - - 7febe00e by Sergey Vinokurov at 2024-12-27T22:24:43+00:00 Fix tests since location of ‘>>=’ changed - - - - - a928c326 by ARATA Mizuki at 2024-12-28T03:06:14-05:00 Fix LLVM version detection With a recent LLVM, `llc -version` emits the version on the first line if the vendor is set. It emits the version on the second line otherwise. Therefore, we need to check the both lines to detect the version. GHC now emits a warning if it fails to detect the LLVM version, so we can notice if the output of `llc -version` changes in the future. Also, the warning for using LLVM < 10 on s390x is removed, because we assume LLVM >= 13 now. This fixes the definition of __GLASGOW_HASKELL_LLVM__ macro. Fixes #25606 - - - - - 7f79257a by Zubin Duggal at 2024-12-29T13:04:35+00:00 Bump base, ghc-prim and template-haskell versions for 9.12 Also bump various submodules. (cherry picked from commit 6fc1fa3bdc8f53acdb19e47145789274060e498f) Bump base bound to 4.21 for GHC 9.12 (cherry picked from commit 473a201c6b55aea5bf9c9db0836a66ea1b657e04) Bump binary submodule to 0.8.9.2 (cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20) (cherry picked from commit ec2f40b45c1a3d82d17a2fc07e9ddb9218bc3940) Bump exceptions submodule to 0.10.9 (cherry picked from commit f5b5d1dc2d326368e5b173d622630d77f019b629) Bump file-io submodule to 0.1.4 (cherry picked from commit ba786681de6ac5fa49938e2cd71a5988f0f40d1f) bump os-string submodule to 2.0.6 (cherry picked from commit 3a7ffdbb832c045a55fd1ef24f546abdd9d9e30f) bump transformers submodule to 0.6.1.2 (cherry picked from commit 53b46fd437421b9e5a001edc6d1c427439d7714f) Bump directory submodule to v1.3.9.0 (cherry picked from commit 27dc2664c5404bb462092bb216c2c37b418fd1f8) Bump Win32 submodule to v2.14.1.0 (cherry picked from commit 80df88086180f5e39212b2feacf70a9d2b263c6c) Bump filepath submodule to 1.5.3.0 (cherry picked from commit 29bfae2c58a7303a081a6e7956b9f55e5faf3eeb) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 97b0dff223a6c4cc003adec448104c277f214645) Bump unix submodule to 2.8.6.0 (cherry picked from commit a1f56d6d6a99c100f88ef0a8b4d51298cf24a42d) Bump os-string submodule to 2.0.8 (cherry picked from commit 0121b76fd52ea0c0ce5d07085bc195666b63c625) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 962ceb50c8a6fc370e1c0a267f5cd5562a8cf759) Bump filepath submodule to 1.5.4.0 (cherry picked from commit 7bc6877fd5d41c6d5900678ad5e73ed30f366569) Bump file-io submodule to 0.1.5 (cherry picked from commit 9478b5aefe2877d58baf527edcf936dddbb955b7) Bump Cabal submodule to 3.14.1.0 (cherry picked from commit 5c9c3e3f79a79bb6d9a77a17c716dc3a0bcbd2aa) Bump directory submodule to 0.12.2.0 (cherry picked from commit 897906265db37af34ae2aaa016cec417f263407b) Bump array submodule for base bump Bump stm submodule for base bump Bump process submodule for base bump - - - - - f6079408 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix ghc-e005 after HasCallstack changes (cherry picked from commit 77f340a24561cea8a6f2ada296b3ea356ab1823c) - - - - - 3e10fa75 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Add haskeline to stage0Packages Otherwise we link against boot inplace and boot unix as boot haskeline depends on boot unix. (cherry picked from commit 90b493769ebdf3cd7be404d18462dc20ac1044df) - - - - - 4ad6aec4 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix TH changelog - - - - - ea3f7fd5 by Zubin Duggal at 2024-12-29T13:04:35+00:00 release: copy index.html from correct directory (cherry picked from commit cbfd0829cd61928976c9eb17ba4af18272466063) - - - - - fafb70db by Zubin Duggal at 2024-12-29T13:04:35+00:00 hadrian-multi: warn on unused imports os-string has redundant imports (cherry picked from commit dde3796be689ea57543936e22aa5ea4ef7ed995e) - - - - - c02b1e46 by Simon Peyton Jones at 2024-12-29T17:04:30-05:00 Fix in-scope set for CSE Ticket #25468 showed an assertion failure in CSE because a top-level Id was being used before it was defined. Reason: Note [Glomming] in GHC.Core.Opt.OccurAnal. Solution (used in many places): just put all the top-level bindings in scope at the beginning of CSE. Compile-time allocation wobbles up and down a tiny bit; geo mean is zero. But MultiLayerModulesTH_OneShot and hard_hole_fits increase (on some architectures only) by a bit oever 2% . I think these are just a random fluctuations. Metric Increase: MultiLayerModulesTH_OneShot hard_hole_fits - - - - - 559d4f84 by Krzysztof Gogolewski at 2024-12-30T11:53:19-05:00 Add tests for #23883 The issue has been fixed by commit f5d3e03c56ffc63. Only T23883a is the actual regression test, the remaining ones are tricky cases found during development of an independent fix !11313. - - - - - 278a53ee by Sergey Vinokurov at 2024-12-30T11:53:59-05:00 Update changelog for CLC proposal #107 (NonEmpty laziness) - - - - - f56558be by Matthew Pickering at 2025-01-07T13:53:03-05:00 warnings: Find out if a qualified name is in the interactive scope directly There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600 - - - - - 84155cdb by Simon Peyton Jones at 2025-01-07T13:53:40-05:00 Tidy up kcConDecls Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types - - - - - 6c12b6cf by Bryan Richter at 2025-01-07T18:15:02-05:00 Remove tmp files after toolchain check Fixes #25620 - - - - - 42826a89 by Cheng Shao at 2025-01-07T18:15:39-05:00 xxhash: bump to v0.8.3 - - - - - 185f17e4 by sheaf at 2025-01-07T18:16:15-05:00 Fix typo in GHC.Tc.Solver.Solve.runTcPluginsWanted - - - - - 23099752 by Luite Stegeman at 2025-01-08T00:33:33+01:00 Add flags for switching off speculative evaluation. We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284 - - - - - 0161badc by Ben Gamari at 2025-01-09T17:30:05-05:00 rts/printClosure: Print IPE information for thunks and functions This makes it considerably easier to grok the structure of the heap when IPE information is available. - - - - - 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz Goślinowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - ef59579b by Andreas Klebinger at 2025-03-06T20:45:50+01:00 NCG: AArch64 - Add -fhuge-code-sections. When enabled the arm backend will assume jumps to targets outside of the current module are further than 128MB away. This will allow for code to work if: * The current module results in less than 128MB of code. * The whole program is loaded within a 4GB memory region. We enable this by default on mac where the lack of split sections can sometimes cause us to go over this limit - see #24648. This works around #24648 for now. - - - - - 1528 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload.sh - .gitlab/rel_eng/upload_ghc_libs.py - .gitmodules - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/Unboxed.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Config/CoreToStg/Prep.hs - compiler/GHC/Driver/Config/Linker.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Config.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Llvm/Ppr.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/CodeGen.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Monad.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Symbols.hs - compiler/GHC/StgToJS/Types.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Info.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/cbits/genSym.c - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/debugging.rst - docs/users_guide/diagnostics-as-json-schema-1_0.json - docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/expected-undocumented-flags.txt - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/overloaded_record_update.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/profiling.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/wasm.rst - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/bindist/Makefile - hadrian/cabal.project - hadrian/cfg/system.config.in - hadrian/src/CommandLine.hs - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Warnings.hs - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/array - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/Data/Semigroup.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Exts.hs - + libraries/base/src/GHC/Num/BigNat.hs - + libraries/base/src/GHC/Num/Integer.hs - + libraries/base/src/GHC/Num/Natural.hs - libraries/base/src/System/Timeout.hs - libraries/binary - libraries/bytestring - libraries/deepseq - libraries/directory - libraries/exceptions - libraries/file-io - libraries/filepath - − libraries/ghc-bignum/.gitignore - + libraries/ghc-bignum/Dummy.hs - − libraries/ghc-bignum/Setup.hs - − libraries/ghc-bignum/aclocal.m4 - libraries/ghc-bignum/changelog.md - − libraries/ghc-bignum/config.mk.in - − libraries/ghc-bignum/configure.ac - − libraries/ghc-bignum/ghc-bignum.buildinfo.in - libraries/ghc-bignum/ghc-bignum.cabal - − libraries/ghc-bignum/install-sh - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-compact/tests/all.T - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-experimental/src/Data/Sum/Experimental.hs - libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/stack_big_ret.hs - libraries/ghc-internal/.gitignore - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/aclocal.m4 - libraries/ghc-bignum/README.rst → libraries/ghc-internal/bignum-backend.rst - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-bignum/cbits/gmp_wrappers.c → libraries/ghc-internal/cbits/gmp_wrappers.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/ghc-internal/configure.ac - libraries/ghc-internal/ghc-internal.buildinfo.in - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-bignum/GMP.rst → libraries/ghc-internal/gmp-backend.rst - libraries/ghc-bignum/gmp/ghc-gmp.h → libraries/ghc-internal/gmp/ghc-gmp.h - libraries/ghc-bignum/gmp/gmp-tarballs → libraries/ghc-internal/gmp/gmp-tarballs - libraries/ghc-bignum/include/HsIntegerGmp.h.in → libraries/ghc-internal/include/HsIntegerGmp.h.in - libraries/ghc-bignum/include/WordSize.h → libraries/ghc-internal/include/WordSize.h - libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-bignum/src/GHC/Num/Backend.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Check.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - libraries/ghc-bignum/src/GHC/Num/Backend/FFI.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Native.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Selected.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Selected.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - libraries/ghc-bignum/src/GHC/Num/Integer.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-bignum/src/GHC/Num/Integer.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - libraries/ghc-bignum/src/GHC/Num/Natural.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-bignum/src/GHC/Num/Natural.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - libraries/ghc-bignum/src/GHC/Num/Primitives.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-bignum/src/GHC/Num/WordArray.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - libraries/ghc-internal/src/GHC/Internal/Char.hs - libraries/ghc-prim/GHC/Classes.hs → libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - libraries/ghc-internal/src/GHC/Internal/Err.hs - libraries/ghc-internal/src/GHC/Internal/Event.hs - libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Float/ConversionUtils.hs - libraries/ghc-internal/src/GHC/Internal/Float/RealFracMethods.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - libraries/ghc-internal/src/GHC/Internal/Generics.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/SubSystem.hs - libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Int.hs - libraries/ghc-internal/src/GHC/Internal/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - libraries/ghc-internal/src/GHC/Internal/IsList.hs - libraries/ghc-internal/src/GHC/Internal/Ix.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - libraries/ghc-internal/src/GHC/Internal/Maybe.hs - libraries/ghc-internal/src/GHC/Internal/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs-boot - libraries/ghc-internal/src/GHC/Internal/Numeric/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-prim/GHC/Prim/Exception.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Read.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - libraries/ghc-internal/src/GHC/Internal/Records.hs - libraries/ghc-internal/src/GHC/Internal/Show.hs - libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - libraries/ghc-prim/GHC/Tuple.hs → libraries/ghc-internal/src/GHC/Internal/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats/Internal.hs - libraries/ghc-prim/GHC/Types.hs → libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghc-internal/src/GHC/Internal/Word.hs - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/integer-gmp/integer-gmp.cabal - libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs - libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - libraries/template-haskell/tests/all.T - + libraries/template-haskell/tests/dataToCodeQUnit.hs - + libraries/template-haskell/tests/dataToCodeQUnit.stdout - libraries/terminfo - libraries/text - libraries/transformers - libraries/unix - linters/lint-codes/LintCodes/Static.hs - linters/lint-codes/Main.hs - m4/find_ld.m4 - m4/fp_settings.m4 - m4/ghc_toolchain.m4 - rts/Capability.c - rts/Capability.h - rts/CheckUnload.c - rts/Disassembler.c - rts/Exception.cmm - rts/Interpreter.c - rts/Interpreter.h - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/ProfHeap.c - rts/RtsMain.c - rts/RtsSymbols.c - rts/Schedule.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStdThunks.cmm - rts/configure.ac - rts/external-symbols.list.in - rts/include/RtsAPI.h - rts/include/Stg.h - rts/include/rts/Bytecodes.h - rts/include/rts/Config.h - rts/include/rts/Threads.h - rts/include/stg/Prim.h - rts/js/environment.js - rts/js/mem.js - rts/js/string.js - rts/js/verify.js - rts/linker/MachO.c - rts/rts.cabal - rts/wasm/JSFFI.c - rts/wasm/scheduler.cmm - rts/win32/libHSghc-prim.def - rts/xxhash.h - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/all.T - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - testsuite/tests/bytecode/T24634/Makefile - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - testsuite/tests/codeGen/should_compile/T25166.stdout - testsuite/tests/codeGen/should_run/T23146/all.T - testsuite/tests/codeGen/should_run/T25364.hs - testsuite/tests/codeGen/should_run/T25364.stdout - testsuite/tests/concurrent/should_run/all.T - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - + testsuite/tests/core-to-stg/T25284/A.hs - + testsuite/tests/core-to-stg/T25284/B.hs - + testsuite/tests/core-to-stg/T25284/Cls.hs - + testsuite/tests/core-to-stg/T25284/Main.hs - + testsuite/tests/core-to-stg/T25284/T25284.stdout - + testsuite/tests/core-to-stg/T25284/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/default/DefaultImportFail01.stderr - testsuite/tests/default/DefaultImportFail02.stderr - testsuite/tests/default/DefaultImportFail03.stderr - testsuite/tests/default/DefaultImportFail04.stderr - testsuite/tests/default/DefaultImportFail05.stderr - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail07.stderr - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/deriving/should_run/T9576.stderr - testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/driver/T20604/T20604.stdout - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/recomp24656/recomp24656.stdout - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - testsuite/tests/ghc-e/should_fail/T23663.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghc-e/should_run/ghc-e005.stderr - testsuite/tests/ghci.debugger/scripts/break006.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - testsuite/tests/ghci/linking/T25240/all.T - testsuite/tests/ghci/linking/all.T - testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T19310.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T21294a.stdout - testsuite/tests/ghci/scripts/T23686.stderr - + testsuite/tests/ghci/scripts/T24459.script - + testsuite/tests/ghci/scripts/T24459.stdout - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/T11361a.stderr - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs → testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12522a.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/javascript/Makefile - testsuite/tests/javascript/T23479_1.hs → testsuite/tests/javascript/T23479.hs - testsuite/tests/javascript/T23479_1.stdout → testsuite/tests/javascript/T23479.stdout - testsuite/tests/javascript/T23479_2.hs → testsuite/tests/javascript/T24744.hs - testsuite/tests/javascript/T23479_2.stdout → testsuite/tests/javascript/T24744.stdout - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLet10.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/llvm/should_compile/T25606.hs - testsuite/tests/llvm/should_compile/all.T - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19892.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.hs - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - + testsuite/tests/parser/should_fail/T25530.hs - + testsuite/tests/parser/should_fail/T25530.stderr - testsuite/tests/parser/should_fail/all.T - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - testsuite/tests/parser/should_run/RecordDotSyntax1.hs - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/perf/compiler/T11068.stdout - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/perf/size/all.T - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/all.T - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/profiling/should_run/ioprof.prof.sample - testsuite/tests/profiling/should_run/toplevel_scc_1.prof.sample - testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quasiquotation/all.T - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/T18263.stderr - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_localname.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TTH_top_splice.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/T12686a.stderr - testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23740i.stderr - + testsuite/tests/rename/should_fail/T25437.hs - + testsuite/tests/rename/should_fail/T25437.stderr - testsuite/tests/rename/should_fail/T5001b.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyMcGuard.stderr - testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T12709.stderr - testsuite/tests/rep-poly/T23153.stderr - + testsuite/tests/rep-poly/T23153b.hs - testsuite/tests/rep-poly/T23154.stderr - + testsuite/tests/rep-poly/T23883a.hs - + testsuite/tests/rep-poly/T23883a.stderr - + testsuite/tests/rep-poly/T23883b.hs - + testsuite/tests/rep-poly/T23883b.stderr - + testsuite/tests/rep-poly/T23883c.hs - + testsuite/tests/rep-poly/T23883c.stderr - testsuite/tests/rep-poly/all.T - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T1791/Makefile - + testsuite/tests/rts/T25560.hs - testsuite/tests/rts/all.T - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/ipe/T24005/t24005.hs - testsuite/tests/rts/linker/all.T - testsuite/tests/safeHaskell/check/pkg01/all.T - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/Orphans.stdout - + testsuite/tests/simd/should_run/T25561.hs - + testsuite/tests/simd/should_run/T25561.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/int16x8_basic.hs - + testsuite/tests/simd/should_run/int16x8_basic.stdout - + testsuite/tests/simd/should_run/int16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/int16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/int32x4_basic.hs - + testsuite/tests/simd/should_run/int32x4_basic.stdout - + testsuite/tests/simd/should_run/int32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/int32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/int64x2_basic.hs - + testsuite/tests/simd/should_run/int64x2_basic.stdout - + testsuite/tests/simd/should_run/int64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/int64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/int8x16_basic.hs - + testsuite/tests/simd/should_run/int8x16_basic.stdout - + testsuite/tests/simd/should_run/int8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/int8x16_basic_baseline.stdout - + testsuite/tests/simd/should_run/word16x8_basic.hs - + testsuite/tests/simd/should_run/word16x8_basic.stdout - + testsuite/tests/simd/should_run/word16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/word16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/word32x4_basic.hs - + testsuite/tests/simd/should_run/word32x4_basic.stdout - + testsuite/tests/simd/should_run/word32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/word32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/word64x2_basic.hs - + testsuite/tests/simd/should_run/word64x2_basic.stdout - + testsuite/tests/simd/should_run/word64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/word64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/word8x16_basic.hs - + testsuite/tests/simd/should_run/word8x16_basic.stdout - + testsuite/tests/simd/should_run/word8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/word8x16_basic_baseline.stdout - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T21286.stderr - testsuite/tests/simplCore/should_compile/T21851_2.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T22428.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10279.hs - testsuite/tests/th/T10279.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15360b.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T16980.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23927.stdout - testsuite/tests/th/T24111.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - testsuite/tests/typecheck/should_compile/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.stderr - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25597.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T15883d.stderr - testsuite/tests/typecheck/should_fail/T15883e.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_fail/T23734.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T23778.stderr - testsuite/tests/typecheck/should_fail/T24298.stderr - testsuite/tests/typecheck/should_fail/T24553.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T7279.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail1.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T22510.stdout - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - testsuite/tests/vdq-rta/should_compile/T23739_th_pprint1.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/T24396.stderr - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/Instances.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - utils/hsc2hs - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9cf71c45cf49dc418d3557771fee297be5cfbe8...ef59579b4f0623e41c86b418e7b728bd3af06019 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9cf71c45cf49dc418d3557771fee297be5cfbe8...ef59579b4f0623e41c86b418e7b728bd3af06019 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/ca319593/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 21:03:03 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Thu, 06 Mar 2025 16:03:03 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/int-index/match-ctxt-varying Message-ID: <67ca0d8798b61_2ee61ac62f0348f6@gitlab.mail> Vladislav Zavialov pushed new branch wip/int-index/match-ctxt-varying at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/int-index/match-ctxt-varying You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/ae26b4f1/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 21:06:36 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Thu, 06 Mar 2025 16:06:36 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/int-index/empty-mg Message-ID: <67ca0e5cbe585_2ee61a1531c83504c@gitlab.mail> Vladislav Zavialov pushed new branch wip/int-index/empty-mg at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/int-index/empty-mg You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/04ae572f/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 21:25:32 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Thu, 06 Mar 2025 16:25:32 -0500 Subject: [Git][ghc/ghc][wip/int-index/vdq-emptycase-errmsg] Error message with EmptyCase and RequiredTypeArguments (#25004) Message-ID: <67ca12cc69beb_2f7334c640895986@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/vdq-emptycase-errmsg at Glasgow Haskell Compiler / GHC Commits: b4999d0e by Vladislav Zavialov at 2025-03-07T00:02:14+03:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 9 changed files: - compiler/GHC/Rename/Bind.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Rename/Bind.hs ===================================== @@ -1323,14 +1323,23 @@ rnMatchGroup :: (Outputable (body GhcPs), AnnoBody body) => HsMatchContextRn -> RnM (MatchGroup GhcRn (LocatedA (body GhcRn)), FreeVars) rnMatchGroup ctxt rnBody (MG { mg_alts = L lm ms, mg_ext = origin }) -- see Note [Empty MatchGroups] - = do { whenM ((null ms &&) <$> mustn't_be_empty) (addErr (TcRnEmptyCase ctxt)) + = do { when (null ms) $ checkEmptyCase ctxt ; (new_ms, ms_fvs) <- mapFvRn (rnMatch ctxt rnBody) ms ; return (mkMatchGroup origin (L lm new_ms), ms_fvs) } + +checkEmptyCase :: HsMatchContextRn -> RnM () +checkEmptyCase ctxt + | disallowed_ctxt = + addErr (TcRnEmptyCase ctxt EmptyCaseDisallowedCtxt) + | otherwise = + unlessXOptM LangExt.EmptyCase $ + addErr (TcRnEmptyCase ctxt EmptyCaseWithoutFlag) where - mustn't_be_empty = case ctxt of - LamAlt LamCases -> return True - ArrowMatchCtxt (ArrowLamAlt LamCases) -> return True - _ -> not <$> xoptM LangExt.EmptyCase + disallowed_ctxt = + case ctxt of + LamAlt LamCases -> True + ArrowMatchCtxt (ArrowLamAlt LamCases) -> True + _ -> False rnMatch :: AnnoBody body => HsMatchContextRn ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -62,7 +62,7 @@ import GHC.Core.FamInstEnv ( FamInst(..), famInstAxiom, pprFamInst ) import GHC.Core.InstEnv import GHC.Core.TyCo.Rep (Type(..)) import GHC.Core.TyCo.Ppr (pprWithInvisibleBitsWhen, pprSourceTyCon, - pprTyVars, pprWithTYPE, pprTyVar, pprTidiedType) + pprTyVars, pprWithTYPE, pprTyVar, pprTidiedType, pprForAll) import GHC.Core.PatSyn ( patSynName, pprPatSynType ) import GHC.Core.Predicate import GHC.Core.Type @@ -1359,24 +1359,27 @@ instance Diagnostic TcRnMessage where text "Orphan COMPLETE pragmas not supported" $$ text "A COMPLETE pragma must mention at least one data constructor" $$ text "or pattern synonym defined in the same module." - TcRnEmptyCase ctxt -> mkSimpleDecorated message - where - pp_ctxt = case ctxt of - CaseAlt -> text "case expression" - LamAlt LamCase -> text "\\case expression" - ArrowMatchCtxt (ArrowLamAlt LamSingle) -> text "kappa abstraction" - ArrowMatchCtxt (ArrowLamAlt LamCase) -> text "\\case command" - ArrowMatchCtxt ArrowCaseAlt -> text "case command" - _ -> text "(unexpected)" - <+> pprMatchContextNoun ctxt - - message = case ctxt of - LamAlt LamCases -> lcases_msg <+> text "expression" - ArrowMatchCtxt (ArrowLamAlt LamCases) -> lcases_msg <+> text "command" - _ -> text "Empty list of alternatives in" <+> pp_ctxt - - lcases_msg = - text "Empty list of alternatives is not allowed in \\cases" + TcRnEmptyCase ctxt reason -> mkSimpleDecorated $ + case reason of + EmptyCaseWithoutFlag -> + text "Empty list of alternatives in" <+> pp_ctxt + EmptyCaseDisallowedCtxt -> + text "Empty list of alternatives is not allowed in" <+> pp_ctxt + EmptyCaseForall tvb -> + vcat [ text "Empty list of alternatives in" <+> pp_ctxt + , hang (text "checked against a forall-type:") + 2 (pprForAll [tvb] <+> text "...") + ] + where + pp_ctxt = case ctxt of + CaseAlt -> text "case expression" + LamAlt LamCase -> text "\\case expression" + LamAlt LamCases -> text "\\cases expression" + ArrowMatchCtxt (ArrowLamAlt LamSingle) -> text "kappa abstraction" + ArrowMatchCtxt (ArrowLamAlt LamCase) -> text "\\case command" + ArrowMatchCtxt (ArrowLamAlt LamCases) -> text "\\cases command" + ArrowMatchCtxt ArrowCaseAlt -> text "case command" + ctxt -> text "(unexpected)" <+> pprMatchContextNoun ctxt TcRnNonStdGuards (NonStandardGuards guards) -> mkSimpleDecorated $ text "accepting non-standard pattern guards" $$ nest 4 (interpp'SP guards) @@ -3062,10 +3065,11 @@ instance Diagnostic TcRnMessage where -> noHints TcRnOrphanCompletePragma{} -> noHints - TcRnEmptyCase ctxt -> case ctxt of - LamAlt LamCases -> noHints -- cases syntax doesn't support empty case. - ArrowMatchCtxt (ArrowLamAlt LamCases) -> noHints - _ -> [suggestExtension LangExt.EmptyCase] + TcRnEmptyCase _ reason -> + case reason of + EmptyCaseWithoutFlag{} -> [suggestExtension LangExt.EmptyCase] + EmptyCaseDisallowedCtxt{} -> noHints + EmptyCaseForall{} -> noHints TcRnNonStdGuards{} -> [suggestExtension LangExt.PatternGuards] TcRnDuplicateSigDecl{} ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -103,6 +103,7 @@ module GHC.Tc.Errors.Types ( , DisabledClassExtension(..) , TyFamsDisabledReason(..) , BadInvisPatReason(..) + , BadEmptyCaseReason(..) , HsTypeOrSigType(..) , HsTyVarBndrExistentialFlag(..) , TySynCycleTyCons @@ -223,7 +224,7 @@ import GHC.Core.InstEnv (LookupInstanceErrReason, ClsInst, DFunId) import GHC.Core.PatSyn (PatSyn) import GHC.Core.Predicate (EqRel, predTypeEqRel) import GHC.Core.TyCon (TyCon, Role, FamTyConFlav, AlgTyConRhs) -import GHC.Core.Type (Kind, Type, ThetaType, PredType, ErrorMsgType, ForAllTyFlag) +import GHC.Core.Type (Kind, Type, ThetaType, PredType, ErrorMsgType, ForAllTyFlag, ForAllTyBinder) import GHC.Driver.Backend (Backend) @@ -3086,8 +3087,11 @@ data TcRnMessage where case () of Test cases: rename/should_fail/RnEmptyCaseFail + testsuite/tests/typecheck/should_fail/T25004 -} - TcRnEmptyCase :: HsMatchContextRn -> TcRnMessage + TcRnEmptyCase :: !HsMatchContextRn + -> !BadEmptyCaseReason + -> TcRnMessage {-| TcRnNonStdGuards is a warning thrown when a user uses non-standard guards (e.g. patterns in guards) without @@ -6183,6 +6187,12 @@ data BadInvisPatReason | InvisPatMisplaced deriving (Generic) +-- | Why was the empty case rejected? +data BadEmptyCaseReason + = EmptyCaseWithoutFlag + | EmptyCaseDisallowedCtxt + | EmptyCaseForall ForAllTyBinder + -- | Either `HsType p` or `HsSigType p`. -- -- Used for reporting errors in `TcRnIllegalKind`. ===================================== compiler/GHC/Tc/Gen/Arrow.hs ===================================== @@ -318,8 +318,9 @@ tcCmdMatches :: CmdEnv -> CmdType -> TcM (MatchGroup GhcTc (LHsCmd GhcTc)) tcCmdMatches env scrut_ty matches (stk, res_ty) - = tcCaseMatches tc_body (unrestricted scrut_ty) matches (mkCheckExpType res_ty) + = tcCaseMatches ctxt tc_body (unrestricted scrut_ty) matches (mkCheckExpType res_ty) where + ctxt = ArrowMatchCtxt ArrowCaseAlt tc_body body res_ty' = do { res_ty' <- expTypeToType res_ty' ; tcCmd env body (stk, res_ty') } ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -493,7 +493,7 @@ tcExpr (HsCase ctxt scrut matches) res_ty ; (scrut', scrut_ty) <- tcScalingUsage mult $ tcInferRho scrut ; hasFixedRuntimeRep_syntactic FRRCase scrut_ty - ; matches' <- tcCaseMatches tcBody (Scaled mult scrut_ty) matches res_ty + ; matches' <- tcCaseMatches ctxt tcBody (Scaled mult scrut_ty) matches res_ty ; return (HsCase ctxt scrut' matches') } tcExpr (HsIf x pred b1 b2) res_ty ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -133,10 +133,11 @@ tcFunBindMatches ctxt fun_name mult matches invis_pat_tys exp_ty , text "invis_pat_tys:" <+> ppr invis_pat_tys , text "pat_tys:" <+> ppr pat_tys , text "rhs_ty:" <+> ppr rhs_ty ] - ; tcMatches tcBody (invis_pat_tys ++ pat_tys) rhs_ty matches } + ; tcMatches mctxt tcBody (invis_pat_tys ++ pat_tys) rhs_ty matches } ; return (wrap_fun, r) } where + mctxt = mkPrefixFunRhs (noLocA fun_name) noAnn herald = ExpectedFunTyMatches (NameThing fun_name) matches funBindPrecondition :: MatchGroup GhcRn (LHsExpr GhcRn) -> Bool @@ -157,10 +158,11 @@ tcLambdaMatches e lam_variant matches invis_pat_tys res_ty ; (wrapper, r) <- matchExpectedFunTys herald GenSigCtxt arity res_ty $ \ pat_tys rhs_ty -> - tcMatches tc_body (invis_pat_tys ++ pat_tys) rhs_ty matches + tcMatches ctxt tc_body (invis_pat_tys ++ pat_tys) rhs_ty matches ; return (wrapper, r) } where + ctxt = LamAlt lam_variant herald = ExpectedFunTyLam lam_variant e -- See Note [Herald for matchExpectedFunTys] in GHC.Tc.Utils.Unify @@ -178,7 +180,8 @@ parser guarantees that each equation has exactly one argument. -} tcCaseMatches :: (AnnoBody body, Outputable (body GhcTc)) - => TcMatchAltChecker body -- ^ Typecheck the alternative RHSS + => HsMatchContextRn + -> TcMatchAltChecker body -- ^ Typecheck the alternative RHSS -> Scaled TcSigmaTypeFRR -- ^ Type of scrutinee -> MatchGroup GhcRn (LocatedA (body GhcRn)) -- ^ The case alternatives -> ExpRhoType -- ^ Type of the whole case expression @@ -186,8 +189,8 @@ tcCaseMatches :: (AnnoBody body, Outputable (body GhcTc)) -- Translated alternatives -- wrapper goes from MatchGroup's ty to expected ty -tcCaseMatches tc_body (Scaled scrut_mult scrut_ty) matches res_ty - = tcMatches tc_body [ExpFunPatTy (Scaled scrut_mult (mkCheckExpType scrut_ty))] res_ty matches +tcCaseMatches ctxt tc_body (Scaled scrut_mult scrut_ty) matches res_ty + = tcMatches ctxt tc_body [ExpFunPatTy (Scaled scrut_mult (mkCheckExpType scrut_ty))] res_ty matches -- @tcGRHSsPat@ typechecks @[GRHSs]@ that occur in a @PatMonoBind at . tcGRHSsPat :: Mult -> GRHSs GhcRn (LHsExpr GhcRn) -> ExpRhoType @@ -222,23 +225,29 @@ type AnnoBody body -- | Type-check a MatchGroup. tcMatches :: (AnnoBody body, Outputable (body GhcTc)) - => TcMatchAltChecker body + => HsMatchContextRn + -> TcMatchAltChecker body -> [ExpPatType] -- ^ Expected pattern types. -> ExpRhoType -- ^ Expected result-type of the Match. -> MatchGroup GhcRn (LocatedA (body GhcRn)) -> TcM (MatchGroup GhcTc (LocatedA (body GhcTc))) -tcMatches tc_body pat_tys rhs_ty (MG { mg_alts = L l matches - , mg_ext = origin }) +tcMatches ctxt tc_body pat_tys rhs_ty (MG { mg_alts = L l matches + , mg_ext = origin }) | null matches -- Deal with case e of {} -- Since there are no branches, no one else will fill in rhs_ty -- when in inference mode, so we must do it ourselves, -- here, using expTypeToType = do { tcEmitBindingUsage bottomUE - ; pat_tys <- mapM scaledExpTypeToType (filter_out_forall_pat_tys pat_tys) + ; pat_ty <- case pat_tys of + [ExpFunPatTy t] -> scaledExpTypeToType t + [ExpForAllPatTy tvb] -> failWithTc $ TcRnEmptyCase ctxt (EmptyCaseForall tvb) + -- It should be impossible to trigger the panics because the renamer rejects \cases{} + [] -> panic "tcMatches: no arguments in EmptyCase" + _t1:(_t2:_ts) -> panic "tcMatches: multiple arguments in EmptyCase" ; rhs_ty <- expTypeToType rhs_ty ; return (MG { mg_alts = L l [] - , mg_ext = MatchGroupTc pat_tys rhs_ty origin + , mg_ext = MatchGroupTc [pat_ty] rhs_ty origin }) } | otherwise ===================================== testsuite/tests/typecheck/should_fail/T25004.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE RequiredTypeArguments, EmptyCase, LambdaCase #-} +{-# OPTIONS -Wincomplete-patterns #-} + +module T25004 where + +import Data.Kind + +f :: forall (xs :: Type) -> () +f = \case {} ===================================== testsuite/tests/typecheck/should_fail/T25004.stderr ===================================== @@ -0,0 +1,6 @@ +T25004.hs:9:5: error: [GHC-48010] + • Empty list of alternatives in \case expression + checked against a forall-type: forall xs -> ... + • In the expression: \case + In an equation for ‘f’: f = \case + ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -730,3 +730,4 @@ test('T23739c', normal, compile_fail, ['']) test('T24868', normal, compile_fail, ['']) test('T24938', normal, compile_fail, ['']) test('T25325', normal, compile_fail, ['']) +test('T25004', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b4999d0e99fe6edcaac1ca808796bc4c0b54a86c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b4999d0e99fe6edcaac1ca808796bc4c0b54a86c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/0f046f2d/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 21:32:26 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 06 Mar 2025 16:32:26 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-9.12-o0 Message-ID: <67ca146ac0e7d_2f733441930898383@gitlab.mail> Cheng Shao pushed new branch wip/ghc-9.12-o0 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-9.12-o0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/b8113831/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 21:32:43 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 06 Mar 2025 16:32:43 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/ghc-9.12-o0 Message-ID: <67ca147b3cc19_2f73343ce010985f9@gitlab.mail> Cheng Shao deleted branch wip/ghc-9.12-o0 at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/f26be767/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 22:13:36 2025 From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo)) Date: Thu, 06 Mar 2025 17:13:36 -0500 Subject: [Git][ghc/ghc][wip/T25705-1] template-haskell: fix haddocks Message-ID: <67ca1e10e96_3046f74371f0208e4@gitlab.mail> Teo Camarasu pushed to branch wip/T25705-1 at Glasgow Haskell Compiler / GHC Commits: c3b5b216 by Teo Camarasu at 2025-03-06T22:12:45+00:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 1 changed file: - libraries/template-haskell/template-haskell.cabal.in Changes: ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -53,6 +53,10 @@ Library build-depends: base >= 4.11 && < 4.22, + -- We don't directly depend on any of the modules from `ghc-internal` + -- But we need to depend on it to work around a hadrian bug. + -- See: https://gitlab.haskell.org/ghc/ghc/-/issues/25705 + ghc-internal == @ProjectVersionForLib at .*, ghc-boot-th == @ProjectVersionMunged@ other-modules: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c3b5b216667d946f096116486b835fe717b2e63a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c3b5b216667d946f096116486b835fe717b2e63a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/1e41e33e/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 22:49:30 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 06 Mar 2025 17:49:30 -0500 Subject: [Git][ghc/ghc][wip/backports-9.10] ghcup-metadata: Update for loss of CentOS 7 Message-ID: <67ca267adea49_31b8ae186c80715f0@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: 09d005eb by Ben Gamari at 2025-03-06T17:49:23-05:00 ghcup-metadata: Update for loss of CentOS 7 - - - - - 1 changed file: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py Changes: ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -96,9 +96,6 @@ def darwin(arch): windowsArtifact = PlatformSpec ( 'x86_64-windows' , 'ghc-{version}-x86_64-unknown-mingw32' ) -def centos(n, arch='x86_64'): - return linux_platform(arch, "x86_64-linux-centos{n}".format(n=n)) - def fedora(n, arch='x86_64'): return linux_platform(arch, "x86_64-linux-fedora{n}".format(n=n)) @@ -195,7 +192,6 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): ubuntu1804 = mk(ubuntu("18_04")) ubuntu2004 = mk(ubuntu("20_04")) rocky8 = mk(rocky("8")) - centos7 = mk(centos(7)) fedora33 = mk(fedora(33)) darwin_x86 = mk(darwin("x86_64")) darwin_arm64 = mk(darwin("aarch64")) @@ -228,11 +224,8 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): , "Linux_Mint" : { "< 20": ubuntu1804 , ">= 20": ubuntu2004 , "unknown_versioning": ubuntu2004 } - , "Linux_CentOS" : { "( >= 7 && < 8 )" : centos7 - , "unknown_versioning" : centos7 } - , "Linux_Fedora" : { ">= 33": fedora33 - , "unknown_versioning": centos7 } - , "Linux_RedHat" : { "< 9": centos7 + , "Linux_Fedora" : { ">= 33": fedora33 } + , "Linux_RedHat" : { "< 9": rocky8 , ">= 9": fedora33 , "unknown_versioning": fedora33 } , "Linux_UnknownLinux" : { "unknown_versioning": rocky8 } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/09d005eba5fe8d9e7f64853648dbebb13a1b6d56 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/09d005eba5fe8d9e7f64853648dbebb13a1b6d56 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/b639d36a/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 23:12:01 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 06 Mar 2025 18:12:01 -0500 Subject: [Git][ghc/ghc][master] 2 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67ca2bc17de4e_31b8ae72c414810dd@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 28 changed files: - compiler/GHC.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -104,10 +104,8 @@ module GHC ( mi_module, mi_sig_of, mi_hsc_src, - mi_src_hash, mi_hi_bytes, mi_deps, - mi_usages, mi_exports, mi_used_th, mi_fixities, ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1178,7 +1178,8 @@ defaultFlags settings Opt_ShowErrorContext, Opt_SuppressStgReps, Opt_UnoptimizedCoreForInterpreter, - Opt_SpecialiseIncoherents + Opt_SpecialiseIncoherents, + Opt_WriteSelfRecompInfo ] ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns] ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -692,6 +692,7 @@ data GeneralFlag | Opt_ExposeOverloadedUnfoldings | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code + | Opt_WriteSelfRecompInfo | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1243,11 +1243,11 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h (cg_guts, details) <- liftIO $ hscTidy hsc_env simplified_guts - let !partial_iface = + !partial_iface <- liftIO $ {-# SCC "GHC.Driver.Main.mkPartialIface" #-} -- This `force` saves 2M residency in test T10370 -- See Note [Avoiding space leaks in toIface*] for details. - force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) + fmap force (mkPartialIface hsc_env (cg_binds cg_guts) details summary (tcg_import_decls tc_result) simplified_guts) return HscRecomp { hscs_guts = cg_guts, hscs_mod_location = ms_location summary, ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -875,10 +875,10 @@ pruneCache hpt summ modl = miKey iface linkable' | Just ms <- M.lookup modl ms_map - , mi_src_hash iface /= ms_hs_hash ms - = emptyHomeModInfoLinkable - | otherwise + , mi_src_hash iface == Just (ms_hs_hash ms) = linkable + | otherwise + = emptyHomeModInfoLinkable -- Using UFM Module is safe for determinism because the map is just used for a transient lookup. The cache should be unique and a key clash is an error. ms_map = M.fromListWith ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,6 +2528,7 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, + flagSpec "write-if-self-recomp" Opt_WriteSelfRecompInfo, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -22,14 +22,12 @@ import GHC.Driver.DynFlags import GHC.Driver.Config import GHC.Driver.Config.Core.Lint ( endPassHscEnvIO ) import GHC.Driver.Config.HsToCore.Ticks -import GHC.Driver.Config.HsToCore.Usage import GHC.Driver.Env import GHC.Driver.Backend import GHC.Driver.Plugins import GHC.Hs -import GHC.HsToCore.Usage import GHC.HsToCore.Monad import GHC.HsToCore.Errors.Types import GHC.HsToCore.Expr @@ -42,7 +40,7 @@ import GHC.HsToCore.Docs import GHC.Tc.Types import GHC.Tc.Types.Origin ( Position(..) ) -import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceLoad ) +import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances ) import GHC.Tc.Module ( runTcInteractive ) import GHC.Core.Type @@ -100,6 +98,7 @@ import GHC.Unit.Module.Deps import Data.List (partition) import Data.IORef import Data.Traversable (for) +import GHC.Iface.Make (mkRecompUsageInfo) {- ************************************************************************ @@ -127,12 +126,10 @@ deSugar hsc_env tcg_fix_env = fix_env, tcg_inst_env = inst_env, tcg_fam_inst_env = fam_inst_env, - tcg_merged = merged, tcg_warns = warns, tcg_anns = anns, tcg_binds = binds, tcg_imp_specs = imp_specs, - tcg_dependent_files = dependent_files, tcg_ev_binds = ev_binds, tcg_th_foreign_files = th_foreign_files_var, tcg_fords = fords, @@ -228,8 +225,7 @@ deSugar hsc_env ; endPassHscEnvIO hsc_env name_ppr_ctx CoreDesugarOpt ds_binds ds_rules_for_imps - ; let used_names = mkUsedNames tcg_env - pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) + ; let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) home_unit = hsc_home_unit hsc_env ; let deps = mkDependencies home_unit (tcg_mod tcg_env) @@ -237,17 +233,10 @@ deSugar hsc_env (map mi_module pluginModules) ; used_th <- readIORef tc_splice_used - ; dep_files <- readIORef dependent_files ; safe_mode <- finalSafeMode dflags tcg_env - ; (needed_mods, needed_pkgs) <- readIORef (tcg_th_needed_deps tcg_env) - - ; let uc = initUsageConfig hsc_env - ; let plugins = hsc_plugins hsc_env - ; let fc = hsc_FC hsc_env - ; let unit_env = hsc_unit_env hsc_env - ; usages <- initIfaceLoad hsc_env $ - mkUsageInfo uc plugins fc unit_env mod (imp_mods imports) used_names - dep_files merged needed_mods needed_pkgs + + ; usages <- mkRecompUsageInfo hsc_env tcg_env + -- id_mod /= mod when we are processing an hsig, but hsigs -- never desugared and compiled (there's no code!) -- Consequently, this should hold for any ModGuts that make ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -49,7 +49,6 @@ import GHC.Types.Name.Cache import GHC.Types.SrcLoc import GHC.Platform import GHC.Settings.Constants -import GHC.Utils.Fingerprint import GHC.Iface.Type (IfaceType(..), getIfaceType, putIfaceType, ifaceTypeSharedByte) import Control.Monad @@ -114,7 +113,7 @@ readBinIfaceHeader -> CheckHiWay -> TraceBinIFace -> FilePath - -> IO (Fingerprint, ReadBinHandle) + -> IO ReadBinHandle readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do let platform = profilePlatform profile @@ -156,8 +155,7 @@ readBinIfaceHeader profile _name_cache checkHiWay traceBinIFace hi_path = do when (checkHiWay == CheckHiWay) $ errorOnMismatch "mismatched interface file profile tag" tag check_tag - src_hash <- get bh - pure (src_hash, bh) + pure bh -- | Read an interface file. -- @@ -170,12 +168,11 @@ readBinIface -> FilePath -> IO ModIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do - (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path + bh <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path mod_iface <- getIfaceWithExtFields name_cache bh return $ mod_iface - & addSourceFingerprint src_hash getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface @@ -259,7 +256,6 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh (show hiVersion) let tag = profileBuildTag profile put_ bh tag - put_ bh (mi_src_hash mod_iface) putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1259,21 +1259,25 @@ pprModIfaceSimple unit_state iface = -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc pprModIface unit_state iface - = vcat [ text "interface" + = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) + <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash exts)) , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) + , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat + [ nest 2 (text "src_hash:" <+> ppr src) + , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "opt_hash:" <+> ppr opt_hash) + , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) + , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) + , vcat (map pprUsage usages) + ] , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) - , nest 2 (text "flag hash:" <+> ppr (mi_flag_hash exts)) - , nest 2 (text "opt_hash:" <+> ppr (mi_opt_hash exts)) - , nest 2 (text "hpc_hash:" <+> ppr (mi_hpc_hash exts)) - , nest 2 (text "plugin_hash:" <+> ppr (mi_plugin_hash exts)) - , nest 2 (text "src_hash:" <+> ppr (mi_src_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "used TH splices:" <+> ppr (mi_used_th iface)) , nest 2 (text "where") @@ -1282,7 +1286,6 @@ pprModIface unit_state iface , text "defaults:" , nest 2 (vcat (map ppr (mi_defaults iface))) , pprDeps unit_state (mi_deps iface) - , vcat (map pprUsage (mi_usages iface)) , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] @@ -1302,6 +1305,7 @@ pprModIface unit_state iface ] where exts = mi_final_exts iface + pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -13,6 +13,7 @@ module GHC.Iface.Make ( mkPartialIface , mkFullIface , mkIfaceTc + , mkRecompUsageInfo , mkIfaceExports ) where @@ -110,7 +111,7 @@ mkPartialIface :: HscEnv -> ModSummary -> [ImportUserSpec] -> ModGuts - -> PartialModIface + -> IO PartialModIface mkPartialIface hsc_env core_prog mod_details mod_summary import_decls ModGuts{ mg_module = this_mod , mg_hsc_src = hsc_src @@ -125,8 +126,10 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_trust_pkg = self_trust , mg_docs = docs } - = mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust - safe_mode usages docs mod_summary mod_details + = do + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages + return $ mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info self_trust + safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code -- generator produced information. @@ -181,9 +184,8 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = restoreFromOldModIface mi res - forceModIface resiface - return resiface + forceModIface res + return res -- | Initial ram buffer to allocate for writing interface files. initBinMemSize :: Int @@ -236,14 +238,11 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_merged = merged, tcg_warns = warns, tcg_hpc = other_hpc_info, - tcg_th_splice_used = tc_splice_used, - tcg_dependent_files = dependent_files + tcg_th_splice_used = tc_splice_used } = do - let used_names = mkUsedNames tc_result let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) let home_unit = hsc_home_unit hsc_env let deps = mkDependencies home_unit @@ -252,48 +251,59 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (map mi_module pluginModules) let hpc_info = emptyHpcInfo other_hpc_info used_th <- readIORef tc_splice_used - dep_files <- (readIORef dependent_files) - (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) - let uc = initUsageConfig hsc_env - plugins = hsc_plugins hsc_env - fc = hsc_FC hsc_env - unit_env = hsc_unit_env hsc_env - -- Do NOT use semantic module here; this_mod in mkUsageInfo - -- is used solely to decide if we should record a dependency - -- or not. When we instantiate a signature, the semantic - -- module is something we want to record dependencies for, - -- but if you pass that in here, we'll decide it's the local - -- module and does not need to be recorded as a dependency. - -- See Note [Identity versus semantic module] - usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env this_mod (imp_mods imports) used_names - dep_files merged needed_links needed_pkgs + usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result + self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usage let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src used_th deps rdr_env import_decls fix_env warns hpc_info - (imp_trust_own_pkg imports) safe_mode usages - docs mod_summary + (imp_trust_own_pkg imports) safe_mode self_recomp + docs mod_details mkFullIface hsc_env partial_iface Nothing Nothing NoStubs [] +mkRecompUsageInfo :: HscEnv -> TcGblEnv -> IO (Maybe [Usage]) +mkRecompUsageInfo hsc_env tc_result = do + let dflags = hsc_dflags hsc_env + if not (gopt Opt_WriteSelfRecompInfo dflags) + then return Nothing + else do + let used_names = mkUsedNames tc_result + dep_files <- (readIORef (tcg_dependent_files tc_result)) + (needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result) + let uc = initUsageConfig hsc_env + plugins = hsc_plugins hsc_env + fc = hsc_FC hsc_env + unit_env = hsc_unit_env hsc_env + + -- Do NOT use semantic module here; this_mod in mkUsageInfo + -- is used solely to decide if we should record a dependency + -- or not. When we instantiate a signature, the semantic + -- module is something we want to record dependencies for, + -- but if you pass that in here, we'll decide it's the local + -- module and does not need to be recorded as a dependency. + -- See Note [Identity versus semantic module] + usages <- initIfaceLoad hsc_env $ mkUsageInfo uc plugins fc unit_env (tcg_mod tc_result) (imp_mods (tcg_imports tc_result)) used_names + dep_files (tcg_merged tc_result) needed_links needed_pkgs + return (Just usages) + mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Bool -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo -> Bool -> SafeHaskellMode - -> [Usage] + -> Maybe ModIfaceSelfRecomp -> Maybe Docs - -> ModSummary -> ModDetails -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src used_th deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode usages - docs mod_summary + hpc_info pkg_trust_req safe_mode self_recomp + docs ModDetails{ md_defaults = defaults, md_insts = insts, md_fam_insts = fam_insts, @@ -350,8 +360,8 @@ mkIface_ hsc_env then Nothing else Just semantic_mod) & set_mi_hsc_src hsc_src + & set_mi_self_recomp self_recomp & set_mi_deps deps - & set_mi_usages usages & set_mi_exports (mkIfaceExports exports) & set_mi_defaults (defaultsToIfaceDefaults defaults) @@ -376,7 +386,6 @@ mkIface_ hsc_env & set_mi_docs docs & set_mi_final_exts () & set_mi_ext_fields emptyExtensibleFields - & set_mi_src_hash (ms_hs_hash mod_summary) & set_mi_hi_bytes PartialIfaceBinHandle where ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -15,6 +15,7 @@ module GHC.Iface.Recomp , CompileReason(..) , recompileRequired , addFingerprints + , mkSelfRecomp ) where @@ -171,6 +172,7 @@ data RecompReason = UnitDepRemoved UnitId | ModulePackageChanged FastString | SourceFileChanged + | NoSelfRecompInfo | ThisUnitIdChanged | ImpurePlugin | PluginsChanged @@ -204,6 +206,7 @@ instance Outputable RecompReason where UnitDepRemoved uid -> ppr uid <+> text "removed" ModulePackageChanged s -> ftext s <+> text "package changed" SourceFileChanged -> text "Source file changed" + NoSelfRecompInfo -> text "Old interface lacks recompilation info" ThisUnitIdChanged -> text "-this-unit-id changed" ImpurePlugin -> text "Impure plugin forced recompilation" PluginsChanged -> text "Plugins changed" @@ -283,7 +286,7 @@ check_old_iface hsc_env mod_summary maybe_iface logger = hsc_logger hsc_env getIface = case maybe_iface of - Just _ -> do + Just {} -> do trace_if logger (text "We already have the old interface for" <+> ppr (ms_mod mod_summary)) return maybe_iface @@ -354,7 +357,9 @@ check_old_iface hsc_env mod_summary maybe_iface -- should check versions because some packages -- might have changed or gone away. Just iface -> - check_dyn_hi iface $ checkVersions hsc_env mod_summary iface + case mi_self_recomp_info iface of + Nothing -> return $ outOfDateItemBecause NoSelfRecompInfo Nothing + Just sr_info -> check_dyn_hi iface $ checkVersions hsc_env mod_summary iface sr_info -- | Check if a module is still the same 'version'. -- @@ -370,8 +375,9 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface + -> ModIfaceSelfRecomp -> IfG (MaybeValidated ModIface) -checkVersions hsc_env mod_summary iface +checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger (text "Considering whether compilation is required for" <+> ppr (mi_module iface) <> colon) @@ -380,23 +386,22 @@ checkVersions hsc_env mod_summary iface -- but we ALSO must make sure the instantiation matches up. See -- test case bkpcabal04! ; hsc_env <- getTopEnv - ; if mi_src_hash iface /= ms_hs_hash mod_summary + ; if mi_sr_src_hash self_recomp /= ms_hs_hash mod_summary then return $ outOfDateItemBecause SourceFileChanged Nothing else do { ; if not (isHomeModule home_unit (mi_module iface)) then return $ outOfDateItemBecause ThisUnitIdChanged Nothing else do { - ; recomp <- liftIO $ checkFlagHash hsc_env iface - `recompThen` checkOptimHash hsc_env iface - `recompThen` checkHpcHash hsc_env iface - `recompThen` checkMergedSignatures hsc_env mod_summary iface + ; recomp <- liftIO $ checkFlagHash hsc_env (mi_module iface) self_recomp + `recompThen` checkOptimHash hsc_env self_recomp + `recompThen` checkHpcHash hsc_env self_recomp + `recompThen` checkMergedSignatures hsc_env mod_summary self_recomp `recompThen` checkHsig logger home_unit mod_summary iface `recompThen` pure (checkHie dflags mod_summary) ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { ; recomp <- checkDependencies hsc_env mod_summary iface ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { - ; recomp <- checkPlugins (hsc_plugins hsc_env) iface + ; recomp <- checkPlugins (hsc_plugins hsc_env) self_recomp ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason Nothing ; _ -> do { - -- Source code unchanged and no errors yet... carry on -- -- First put the dependent-module info, read from the old @@ -411,7 +416,7 @@ checkVersions hsc_env mod_summary iface ; updateEps_ $ \eps -> eps { eps_is_boot = mkModDeps $ dep_boot_mods (mi_deps iface) } } ; recomp <- checkList [checkModUsage (hsc_FC hsc_env) u - | u <- mi_usages iface] + | u <- mi_sr_usages self_recomp] ; case recomp of (NeedsRecompile reason) -> return $ OutOfDateItem reason (Just iface) ; _ -> do { ; return $ UpToDateItem iface }}}}}}} @@ -423,11 +428,11 @@ checkVersions hsc_env mod_summary iface -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIface -> IfG RecompileRequired -checkPlugins plugins iface = liftIO $ do +checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp - let old_fingerprint = mi_plugin_hash (mi_final_exts iface) + let old_fingerprint = mi_sr_plugin_hash self_recomp return $ pluginRecompileToRecompileRequired old_fingerprint new_fingerprint recomp recompPlugins :: Plugins -> IO PluginRecompile @@ -516,11 +521,11 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> ModIface -> IO RecompileRequired -checkFlagHash hsc_env iface = do +checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_flag_hash (mi_final_exts iface) - new_hash <- fingerprintDynFlags hsc_env (mi_module iface) putNameLiterally + let old_hash = mi_sr_flag_hash self_recomp + new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally case old_hash == new_hash of True -> up_to_date logger (text "Module flags unchanged") False -> out_of_date_hash logger FlagsChanged @@ -528,10 +533,10 @@ checkFlagHash hsc_env iface = do old_hash new_hash -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIface -> IO RecompileRequired +checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env - let old_hash = mi_opt_hash (mi_final_exts iface) + let old_hash = mi_sr_opt_hash iface new_hash <- fingerprintOptFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -544,10 +549,10 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIface -> IO RecompileRequired -checkHpcHash hsc_env iface = do +checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_hpc_hash (mi_final_exts iface) + let old_hash = mi_sr_hpc_hash self_recomp new_hash <- fingerprintHpcFlags (hsc_dflags hsc_env) putNameLiterally if | old_hash == new_hash @@ -561,11 +566,11 @@ checkHpcHash hsc_env iface = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIface -> IO RecompileRequired -checkMergedSignatures hsc_env mod_summary iface = do +checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env - let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_usages iface ] + let old_merged = sort [ mod | UsageMergedRequirement{ usg_mod = mod } <- mi_sr_usages self_recomp ] new_merged = case lookupUniqMap (requirementContext unit_state) (ms_mod_name mod_summary) of Nothing -> [] @@ -939,6 +944,28 @@ we use is: -} +-- | Compute the information needed for self-recompilation checking. This +-- information can be computed before the backend phase. +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp hsc_env this_mod src_hash usages = do + let dflags = hsc_dflags hsc_env + + flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + + opt_hash <- fingerprintOptFlags dflags putNameLiterally + + hpc_hash <- fingerprintHpcFlags dflags putNameLiterally + + plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + + return (ModIfaceSelfRecomp + { mi_sr_flag_hash = flag_hash + , mi_sr_hpc_hash = hpc_hash + , mi_sr_opt_hash = opt_hash + , mi_sr_plugin_hash = plugin_hash + , mi_sr_src_hash = src_hash + , mi_sr_usages = usages }) + -- | Add fingerprints for top-level declarations to a 'ModIface'. -- -- See Note [Fingerprinting IfaceDecls] @@ -1213,18 +1240,6 @@ addFingerprints hsc_env iface0 sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - -- the flag hash depends on: - -- - (some of) dflags - -- it returns two hashes, one that shouldn't change - -- the abi hash and one that should - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally - - opt_hash <- fingerprintOptFlags dflags putNameLiterally - - hpc_hash <- fingerprintHpcFlags dflags putNameLiterally - - plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) - -- the ABI hash depends on: -- - decls -- - export list @@ -1238,6 +1253,7 @@ addFingerprints hsc_env iface0 mi_warns iface0, mi_foreign iface0) + -- The interface hash depends on: -- - the ABI hash, plus -- - the source file hash, @@ -1246,21 +1262,17 @@ addFingerprints hsc_env iface0 -- - deps (home and external packages, dependent files) -- - hpc iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - mi_src_hash iface0, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_usages iface0, - sorted_deps, - mi_hpc iface0) + (mod_hash, + mi_src_hash iface0, + ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache + mi_usages iface0, + sorted_deps, + mi_hpc iface0) let final_iface_exts = ModIfaceBackend - { mi_iface_hash = iface_hash - , mi_mod_hash = mod_hash - , mi_flag_hash = flag_hash - , mi_opt_hash = opt_hash - , mi_hpc_hash = hpc_hash - , mi_plugin_hash = plugin_hash + { mi_mod_hash = mod_hash + , mi_iface_hash = iface_hash , mi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts @@ -1281,12 +1293,12 @@ addFingerprints hsc_env iface0 where this_mod = mi_module iface0 semantic_mod = mi_semantic_module iface0 - dflags = hsc_dflags hsc_env (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) ann_fn = mkIfaceAnnCache (mi_anns iface0) + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the -- current module). ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -0,0 +1,112 @@ +module GHC.Iface.Recomp.Types ( ModIfaceSelfRecomp(..) + ) where + +import GHC.Prelude +import GHC.Fingerprint +import GHC.Utils.Outputable +import GHC.Unit.Module.Deps + +import GHC.Utils.Binary + +import Control.DeepSeq + +{- +Note [Self recompilation information in interface files] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The flag -fwrite-if-self-recomp controls whether +interface files contain the information necessary to answer the +question: + + Is the interface file up-to-date, relative to: + * the source file it corresponds to, + * the flags passed to the GHC invocation to compile it, + * its dependencies (e.g. imported items, watched files added by addDependentFile, ...) + +If there is no self-recompilation information stored, then we always re-generate +the interface file from scratch. + +Why? Most packages are only built once either by a distribution or cabal +and then placed into an immutable store, after which we will never ask +this question. Therefore we can derive two benefits from omitting this +information. + +* Primary motivation: It vastly reduces the surface area for creating + non-deterministic interface files. See issue #10424 which motivated a + proper fix to that issue. Distributions have long contained versions + of GHC which just have broken self-recompilation checking (in order to + get deterministic interface files). + +* Secondary motivation: This reduces the size of interface files + slightly.. the `mi_usages` field can be quite big but probably this + isn't such a great benefit. + +* Third motivation: Conceptually clarity about which parts of an + interface file are used in order to **communicate** with subsequent + packages about the **interface** for a module. And which parts are + used to self-communicate during recompilation checking. + +The main tracking issue is #22188 but fixes issues such as #10424 in a +proper way. + +-} + +-- | The information for a module which is only used when deciding whether to recompile +-- itself. +-- +-- See Note [Self recompilation information in interface files] +data ModIfaceSelfRecomp = + ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint + -- ^ Hash of the .hs source, used for recompilation checking. + , mi_sr_usages :: [Usage] + -- ^ Usages; kept sorted so that it's easy to decide + -- whether to write a new iface file (changing usages + -- doesn't affect the hash of this module) + -- NOT STRICT! we read this field lazily from the interface file + -- It is *only* consulted by the recompilation checker + + , mi_sr_flag_hash :: !Fingerprint + -- ^ Hash of the important flags used when compiling the module, excluding + -- optimisation flags + , mi_sr_opt_hash :: !Fingerprint + -- ^ Hash of optimisation flags + , mi_sr_hpc_hash :: !Fingerprint + -- ^ Hash of hpc flags + , mi_sr_plugin_hash :: !Fingerprint + -- ^ Hash of plugins + } + + +instance Binary ModIfaceSelfRecomp where + put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do + put_ bh mi_sr_src_hash + lazyPut bh mi_sr_usages + put_ bh mi_sr_flag_hash + put_ bh mi_sr_opt_hash + put_ bh mi_sr_hpc_hash + put_ bh mi_sr_plugin_hash + + get bh = do + src_hash <- get bh + usages <- lazyGet bh + flag_hash <- get bh + opt_hash <- get bh + hpc_hash <- get bh + plugin_hash <- get bh + return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + +instance Outputable ModIfaceSelfRecomp where + ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) + = vcat [text "Self-Recomp" + , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash + , text "usages:" <+> ppr (length mi_sr_usages) + , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "opt hash:" <+> ppr mi_sr_opt_hash + , text "hpc hash:" <+> ppr mi_sr_hpc_hash + , text "plugin hash:" <+> ppr mi_sr_plugin_hash + ])] + +instance NFData ModIfaceSelfRecomp where + -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so + -- I left it as a shallow force. + rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file ===================================== compiler/GHC/Unit/Module/ModGuts.hs ===================================== @@ -53,7 +53,7 @@ data ModGuts mg_exports :: ![AvailInfo], -- ^ What it exports mg_deps :: !Dependencies, -- ^ What it depends on, directly or -- otherwise - mg_usages :: ![Usage], -- ^ What was used? Used for interfaces. + mg_usages :: !(Maybe [Usage]), -- ^ What was used? Used for interfaces. mg_used_th :: !Bool, -- ^ Did we run a TH splice? mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -15,7 +15,6 @@ module GHC.Unit.Module.ModIface , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -36,19 +35,16 @@ module GHC.Unit.Module.ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info ) , pattern ModIface - , restoreFromOldModIface - , addSourceFingerprint , set_mi_module , set_mi_sig_of , set_mi_hsc_src - , set_mi_src_hash + , set_mi_self_recomp , set_mi_hi_bytes , set_mi_deps - , set_mi_usages , set_mi_exports , set_mi_used_th , set_mi_fixities @@ -73,6 +69,8 @@ module GHC.Unit.Module.ModIface , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) + , ModIfaceSelfRecomp (..) + , withSelfRecomp , IfaceDeclExts , IfaceBackendExts , IfaceExport @@ -85,6 +83,12 @@ module GHC.Unit.Module.ModIface , mi_semantic_module , mi_free_holes , mi_mnwib + , mi_flag_hash + , mi_opt_hash + , mi_hpc_hash + , mi_plugin_hash + , mi_src_hash + , mi_usages , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -100,12 +104,14 @@ import GHC.Hs import GHC.Iface.Syntax import GHC.Iface.Ext.Fields +import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) + import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env @@ -150,19 +156,10 @@ type ModIface = ModIface_ 'ModIfaceFinal -- * Or computed just before writing the iface to disk. (Hashes) -- In order to fully instantiate it. data ModIfaceBackend = ModIfaceBackend - { mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_mod_hash :: !Fingerprint + { mi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_flag_hash :: !Fingerprint - -- ^ Hash of the important flags used when compiling the module, excluding - -- optimisation flags - , mi_opt_hash :: !Fingerprint - -- ^ Hash of optimisation flags - , mi_hpc_hash :: !Fingerprint - -- ^ Hash of hpc flags - , mi_plugin_hash :: !Fingerprint - -- ^ Hash of plugins + , mi_iface_hash :: !Fingerprint + -- ^ Hash of the whole interface , mi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans , mi_finsts :: !WhetherHasFamInst @@ -218,6 +215,15 @@ data IfaceBinHandle (phase :: ModIfacePhase) where -- (e.g., set to 'Nothing'). FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal + +withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp iface nk jk = + case mi_self_recomp_info iface of + Nothing -> nk + Just x -> jk x + + + -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, -- and can be written out to an interface file. The 'ModDetails is after @@ -245,16 +251,6 @@ data ModIface_ (phase :: ModIfacePhase) -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages_ :: [Usage], - -- ^ Usages; kept sorted so that it's easy to decide - -- whether to write a new iface file (changing usages - -- doesn't affect the hash of this module) - -- NOT STRICT! we read this field lazily from the interface file - -- It is *only* consulted by the recompilation checker - -- - -- The elements must be *deterministically* sorted to guarantee - -- deterministic interface files - mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier @@ -345,13 +341,15 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash_ :: !Fingerprint, - -- ^ Hash of the .hs source, used for recompilation checking. - mi_hi_bytes_ :: !(IfaceBinHandle phase) + mi_hi_bytes_ :: !(IfaceBinHandle phase), -- ^ A serialised in-memory buffer of this 'ModIface'. -- If this handle is given, we can avoid serialising the 'ModIface' -- when writing this 'ModIface' to disk, and write this buffer to disk instead. -- See Note [Sharing of ModIface]. + + mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] } -- Enough information to reconstruct the top level environment for a module @@ -397,6 +395,24 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} +mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ + +mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ + +mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ + +mi_src_hash :: ModIface_ phase -> Maybe Fingerprint +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ + +mi_usages :: ModIface_ phase -> Maybe [Usage] +mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ + +mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ + -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. mi_boot :: ModIface -> IsBootInterface @@ -454,9 +470,6 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance - -- because we are going to write it - -- out separately in the actual file mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then @@ -464,7 +477,6 @@ instance Binary ModIface where -- the byte array. -- See Note [Private fields in ModIface] mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_fixities_ = fixities, @@ -486,13 +498,10 @@ instance Binary ModIface where mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file + mi_self_recomp_info_ = self_recomp, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -501,16 +510,12 @@ instance Binary ModIface where put_ bh mod put_ bh sig_of put_ bh hsc_src - put_ bh iface_hash + put_ bh self_recomp put_ bh mod_hash - put_ bh flag_hash - put_ bh opt_hash - put_ bh hpc_hash - put_ bh plugin_hash + put_ bh iface_hash put_ bh orphan put_ bh hasFamInsts lazyPut bh deps - lazyPut bh usages put_ bh exports put_ bh exp_hash put_ bh used_th @@ -536,16 +541,12 @@ instance Binary ModIface where mod <- get bh sig_of <- get bh hsc_src <- get bh - iface_hash <- get bh + self_recomp_info <- get bh mod_hash <- get bh - flag_hash <- get bh - opt_hash <- get bh - hpc_hash <- get bh - plugin_hash <- get bh + iface_hash <- get bh orphan <- get bh hasFamInsts <- get bh deps <- lazyGet bh - usages <- {-# SCC "bin_usages" #-} lazyGet bh exports <- {-# SCC "bin_exports" #-} get bh exp_hash <- get bh used_th <- get bh @@ -570,15 +571,12 @@ instance Binary ModIface where mi_module_ = mod, mi_sig_of_ = sig_of, mi_hsc_src_ = hsc_src, - mi_src_hash_ = fingerprint0, -- placeholder because this is dealt - -- with specially when the file is read mi_hi_bytes_ = -- We can't populate this field here, as we are -- missing the 'mi_ext_fields_' field, which is -- handled in 'getIfaceWithExtFields'. FullIfaceBinHandle Strict.Nothing, mi_deps_ = deps, - mi_usages_ = usages, mi_exports_ = exports, mi_used_th_ = used_th, mi_anns_ = anns, @@ -600,13 +598,10 @@ instance Binary ModIface where mi_top_env_ = top_env, mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read + mi_self_recomp_info_ = self_recomp_info, mi_final_exts_ = ModIfaceBackend { - mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, - mi_flag_hash = flag_hash, - mi_opt_hash = opt_hash, - mi_hpc_hash = hpc_hash, - mi_plugin_hash = plugin_hash, + mi_iface_hash = iface_hash, mi_orphan = orphan, mi_finsts = hasFamInsts, mi_exp_hash = exp_hash, @@ -625,10 +620,8 @@ emptyPartialModIface mod { mi_module_ = mod, mi_sig_of_ = Nothing, mi_hsc_src_ = HsSrcFile, - mi_src_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_usages_ = [], mi_exports_ = [], mi_used_th_ = False, mi_fixities_ = [], @@ -648,21 +641,19 @@ emptyPartialModIface mod mi_complete_matches_ = [], mi_docs_ = Nothing, mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields + mi_ext_fields_ = emptyExtensibleFields, + mi_self_recomp_info_ = Nothing } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) { mi_decls_ = [] + , mi_self_recomp_info_ = Nothing , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing , mi_final_exts_ = ModIfaceBackend - { mi_iface_hash = fingerprint0, - mi_mod_hash = fingerprint0, - mi_flag_hash = fingerprint0, - mi_opt_hash = fingerprint0, - mi_hpc_hash = fingerprint0, - mi_plugin_hash = fingerprint0, + { mi_mod_hash = fingerprint0, + mi_iface_hash = fingerprint0, mi_orphan = False, mi_finsts = False, mi_exp_hash = fingerprint0, @@ -692,18 +683,17 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_, mi_src_hash_ }) + , mi_ext_fields_ }) = rnf mi_module_ `seq` rnf mi_sig_of_ `seq` mi_hsc_src_ `seq` mi_hi_bytes_ `seq` mi_deps_ - `seq` mi_usages_ `seq` mi_exports_ `seq` rnf mi_used_th_ `seq` mi_fixities_ @@ -724,20 +714,14 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_docs_ `seq` mi_final_exts_ `seq` mi_ext_fields_ - `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_iface_hash, mi_mod_hash, mi_flag_hash, mi_opt_hash - , mi_hpc_hash, mi_plugin_hash, mi_orphan, mi_finsts, mi_exp_hash + rnf (ModIfaceBackend{ mi_mod_hash + , mi_orphan, mi_finsts, mi_exp_hash , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn , mi_hash_fn}) - = rnf mi_iface_hash - `seq` rnf mi_mod_hash - `seq` rnf mi_flag_hash - `seq` rnf mi_opt_hash - `seq` rnf mi_hpc_hash - `seq` rnf mi_plugin_hash + = rnf mi_mod_hash `seq` rnf mi_orphan `seq` rnf mi_finsts `seq` rnf mi_exp_hash @@ -803,27 +787,6 @@ completePartialModIface partial decls extra_decls final_exts = partial , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing } --- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array --- buffer 'mi_hi_bytes'. --- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. --- --- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. -addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase -addSourceFingerprint val iface = iface { mi_src_hash_ = val } - --- | Copy fields that aren't serialised to disk to the new 'ModIface_'. --- This includes especially hashes that are usually stored in the interface --- file header. --- --- We need this function after calling 'shareIface', to make sure the --- 'ModIface_' doesn't lose any information. This function does not discard --- the in-memory byte array buffer 'mi_hi_bytes'. -restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase -restoreFromOldModIface old new = new - { mi_hsc_src_ = mi_hsc_src_ old - , mi_src_hash_ = mi_src_hash_ old - } - set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } @@ -833,8 +796,8 @@ set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } -set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase -set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } +set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -842,9 +805,6 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } -set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase -set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } - set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } @@ -969,7 +929,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} -{-# INLINE mi_usages #-} {-# INLINE mi_exports #-} {-# INLINE mi_used_th #-} {-# INLINE mi_fixities #-} @@ -989,25 +948,23 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_docs #-} {-# INLINE mi_final_exts #-} {-# INLINE mi_ext_fields #-} -{-# INLINE mi_src_hash #-} {-# INLINE mi_hi_bytes #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + Module -> Maybe Module -> HscSource -> Dependencies -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface { mi_module , mi_sig_of , mi_hsc_src , mi_deps - , mi_usages , mi_exports , mi_used_th , mi_fixities @@ -1028,14 +985,13 @@ pattern ModIface , mi_docs , mi_final_exts , mi_ext_fields - , mi_src_hash , mi_hi_bytes + , mi_self_recomp_info } <- PrivateModIface { mi_module_ = mi_module , mi_sig_of_ = mi_sig_of , mi_hsc_src_ = mi_hsc_src , mi_deps_ = mi_deps - , mi_usages_ = mi_usages , mi_exports_ = mi_exports , mi_used_th_ = mi_used_th , mi_fixities_ = mi_fixities @@ -1056,6 +1012,6 @@ pattern ModIface , mi_docs_ = mi_docs , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields - , mi_src_hash_ = mi_src_hash , mi_hi_bytes_ = mi_hi_bytes + , mi_self_recomp_info_ = mi_self_recomp_info } ===================================== compiler/ghc.cabal.in ===================================== @@ -606,6 +606,7 @@ Library GHC.Iface.Recomp GHC.Iface.Recomp.Binary GHC.Iface.Recomp.Flags + GHC.Iface.Recomp.Types GHC.Iface.Rename GHC.Iface.Syntax GHC.Iface.Tidy ===================================== docs/users_guide/phases.rst ===================================== @@ -702,6 +702,24 @@ Options affecting code generation depend on the optimisation level. Any definitions which are already included in an interface file (via an unfolding for an exported identifier) are reused. +.. ghc-flag:: -fwrite-if-self-recomp + :shortdesc: Write information for self-recompilation checking in an interface file + :type: dynamic + :category: codegen + + :default: on + + Include information in an interface file which can be used in future to determine + whether we need to recompile a module or can reuse the existing interface. + + This is intended to be turned off in situations where you know you will never try + to recompile a module, such as when compiling a package for distribution. + The advantage is that by omitting unecessary information to do with dependencies + there is less chance of build paths leaking into the interface file and affecting + determinism. + + + .. ghc-flag:: -fobject-code :shortdesc: Generate object code ===================================== hadrian/doc/flavours.md ===================================== @@ -107,7 +107,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH <td>-O2</td> </tr> <tr> - <th>release (same as perf with -haddock)</td> + <th>release (same as perf with -haddock and +no_self_recomp)</td> <td></td> <td>-O<br>-H64m</td> <td>-O<br>-H64m</td> @@ -329,6 +329,10 @@ The supported transformers are listed below: <td><code>dump_stg</code></td> <td>Dump STG of all modules compiled by a stage1 compiler to a file</td> </tr> + <tr> + <td><code>no_self_recomp</code></td> + <td>Disable including self-recompilation information in interface files via <code>-fno-write-if-self-recomp</code>. If you are building a distribution you can enable this flag to produce more deterministic interface files.</td> + </tr> </table> ### Static ===================================== hadrian/src/Flavour.hs ===================================== @@ -16,6 +16,7 @@ module Flavour , disableProfiledLibs , enableLinting , enableHaddock + , disableSelfRecompInfo , enableHiCore , useNativeBignum , enableTextWithSIMDUTF @@ -67,6 +68,7 @@ flavourTransformers = M.fromList , "debug_stage1_ghc" =: debugGhc Stage1 , "lint" =: enableLinting , "haddock" =: enableHaddock + , "no_self_recomp" =: disableSelfRecompInfo , "hi_core" =: enableHiCore , "late_ccs" =: enableLateCCS , "boot_nonmoving_gc" =: enableBootNonmovingGc @@ -208,6 +210,17 @@ enableHaddock = [ arg "-haddock" ] +-- | Disable self recompilation information in interface files +disableSelfRecompInfo :: Flavour -> Flavour +disableSelfRecompInfo = + addArgs $ stage1 ? mconcat + [ builder (Ghc CompileHs) ? selfRecomp + ] + where + selfRecomp = mconcat + [ arg "-fno-write-if-self-recomp" + ] + -- | Build stage2 dependencies with options to emit Core into -- interface files which is sufficient to restart code generation. enableHiCore :: Flavour -> Flavour ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,8 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableHaddock performanceFlavour { name = "release" } +releaseFlavour = + -- 1. These interface files will be distributed and the source files never recompiled. + disableSelfRecompInfo + -- 2. Include documentation in the interface for tools such as haddock and HLS to use + $ enableHaddock performanceFlavour { name = "release" } ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -112,6 +112,7 @@ GHC.Hs.Utils GHC.Iface.Errors.Types GHC.Iface.Ext.Fields GHC.Iface.Recomp.Binary +GHC.Iface.Recomp.Types GHC.Iface.Syntax GHC.Iface.Type GHC.Parser.Annotation ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -118,6 +118,7 @@ GHC.HsToCore.Pmc.Solver.Types GHC.Iface.Errors.Types GHC.Iface.Ext.Fields GHC.Iface.Recomp.Binary +GHC.Iface.Recomp.Types GHC.Iface.Syntax GHC.Iface.Type GHC.Linker.Static.Utils ===================================== testsuite/tests/driver/self-recomp/Makefile ===================================== @@ -0,0 +1,38 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +TEST_HC_OPTS_NO_RTSOPTS = $(filter-out -rtsopts,$(TEST_HC_OPTS)) + +# ----------------------------------------------------------------------------- +# One-shot compilations, non-hierarchical modules + +# Check that modifying flags doesn't affect interface +SelfRecomp01: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface1 + rm SelfRecomp01.hi + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp01.hs -fno-write-if-self-recomp -Iidir -v0 + "$(TEST_HC)" --show-iface SelfRecomp01.hi > iface2 + diff iface1 iface2 + +# Check that the result of addDependentFile doesn't end up in interface +SelfRecomp02: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp02.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp02.hi > iface + [ -z $(grep iface SelfRecomp02.hs) ] + +# Check that modifying source doesn't affect interface +SelfRecomp03: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface1 + rm SelfRecomp03.hi + echo "" >> SelfRecomp03.hs + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp03.hs -fno-write-if-self-recomp -v0 + "$(TEST_HC)" --show-iface SelfRecomp03.hi > iface2 + diff iface1 iface2 + +# Check that if you don't have recompilation info then you always recompile. +SelfRecomp04: + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-if-self-recomp -fhide-source-paths + "$(TEST_HC)" $(TEST_HC_OPTS) SelfRecomp04.hs -fno-write-if-self-recomp -fhide-source-paths ===================================== testsuite/tests/driver/self-recomp/SelfRecomp01.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp01 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp02.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +module SelfRecomp02 where + +import Language.Haskell.TH.Syntax + +main = $(addDependentFile "SelfRecomp02.hs" >> [| print () |]) ===================================== testsuite/tests/driver/self-recomp/SelfRecomp03.hs ===================================== @@ -0,0 +1,2 @@ +module SelfRecomp03 where + ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.hs ===================================== @@ -0,0 +1 @@ +module SelfRecomp04 where ===================================== testsuite/tests/driver/self-recomp/SelfRecomp04.stdout ===================================== @@ -0,0 +1,2 @@ +[1 of 1] Compiling SelfRecomp04 +[1 of 1] Compiling SelfRecomp04 [Old interface lacks recompilation info] ===================================== testsuite/tests/driver/self-recomp/all.T ===================================== @@ -0,0 +1,4 @@ +test('SelfRecomp01', normal, makefile_test, ['SelfRecomp01']) +test('SelfRecomp02', normal, makefile_test, ['SelfRecomp02']) +test('SelfRecomp03', [copy_files], makefile_test, ['SelfRecomp03']) +test('SelfRecomp04', normal, makefile_test, ['SelfRecomp04']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07fe6d1daad01030cb7b9e6897492b7bdaec5a90...5b05c27bf186e66edc4fbf4a54943c8bd04f5024 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07fe6d1daad01030cb7b9e6897492b7bdaec5a90...5b05c27bf186e66edc4fbf4a54943c8bd04f5024 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/b0011ea7/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 23:12:40 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 06 Mar 2025 18:12:40 -0500 Subject: [Git][ghc/ghc][master] 3 commits: Cmm: Add surface syntax for Word/Float bitcast ops Message-ID: <67ca2be834393_31b8ae7adc94838b5@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 6 changed files: - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T Changes: ===================================== compiler/GHC/Cmm/Opt.hs ===================================== @@ -19,9 +19,11 @@ import GHC.Cmm import GHC.Utils.Misc import GHC.Utils.Panic +import GHC.Utils.Outputable import GHC.Platform import Data.Maybe +import GHC.Float constantFoldNode :: Platform -> CmmNode e x -> CmmNode e x @@ -63,24 +65,51 @@ cmmMachOpFoldM _ (MO_VF_Broadcast lg _w) exprs = [CmmLit l] -> Just $! CmmLit (CmmVec $ replicate lg l) _ -> Nothing cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] - = case op of - MO_S_Neg _ -> Just $! CmmLit (CmmInt (narrowS rep (-x)) rep) - MO_Not _ -> Just $! CmmLit (CmmInt (complement x) rep) + | MO_WF_Bitcast width <- op = case width of + W32 | res <- castWord32ToFloat (fromInteger x) + -- Since we store float literals as Rationals + -- we must check for the usual tricky cases first + , not (isNegativeZero res || isNaN res || isInfinite res) + -- (round-tripping subnormals is not a problem) + , !res_rat <- toRational res + -> Just (CmmLit (CmmFloat res_rat W32)) + + W64 | res <- castWord64ToDouble (fromInteger x) + -- Since we store float literals as Rationals + -- we must check for the usual tricky cases first + , not (isNegativeZero res || isNaN res || isInfinite res) + -- (round-tripping subnormals is not a problem) + , !res_rat <- toRational res + -> Just (CmmLit (CmmFloat res_rat W64)) + + _ -> Nothing + | otherwise + = Just $! case op of + MO_S_Neg _ -> CmmLit (CmmInt (narrowS rep (-x)) rep) + MO_Not _ -> CmmLit (CmmInt (complement x) rep) -- these are interesting: we must first narrow to the -- "from" type, in order to truncate to the correct size. -- The final narrow/widen to the destination type -- is implicit in the CmmLit. - MO_SF_Round _frm to -> Just $! CmmLit (CmmFloat (fromInteger x) to) - MO_SS_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) - MO_UU_Conv from to -> Just $! CmmLit (CmmInt (narrowU from x) to) - MO_XX_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) - - -- Not as simply as it seems, since CmmFloat uses Rational, so skipping those - -- for now ... - MO_WF_Bitcast _w -> Nothing - MO_FW_Bitcast _w -> Nothing + MO_SF_Round _frm to -> CmmLit (CmmFloat (fromInteger x) to) + MO_SS_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + MO_UU_Conv from to -> CmmLit (CmmInt (narrowU from x) to) + MO_XX_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + + MO_F_Neg{} -> invalidArgPanic + MO_FS_Truncate{} -> invalidArgPanic + MO_FF_Conv{} -> invalidArgPanic + MO_FW_Bitcast{} -> invalidArgPanic + MO_VS_Neg{} -> invalidArgPanic + MO_VF_Neg{} -> invalidArgPanic + MO_RelaxedRead{} -> invalidArgPanic + MO_AlignmentCheck{} -> invalidArgPanic + _ -> panic $ "cmmMachOpFoldM: unknown unary op: " ++ show op + where invalidArgPanic = pprPanic "cmmMachOpFoldM" $ + text "Found" <+> pprMachOp op + <+> text "illegally applied to an int literal" -- Eliminate shifts that are wider than the shiftee cmmMachOpFoldM _ op [_shiftee, CmmLit (CmmInt shift _)] ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -1109,7 +1109,10 @@ machOps = listToUFM $ ( "f2i32", flip MO_FS_Truncate W32 ), ( "f2i64", flip MO_FS_Truncate W64 ), ( "i2f32", flip MO_SF_Round W32 ), - ( "i2f64", flip MO_SF_Round W64 ) + ( "i2f64", flip MO_SF_Round W64 ), + + ( "w2f_bitcast", MO_WF_Bitcast ), + ( "f2w_bitcast", MO_FW_Bitcast ) ] callishMachOps :: Platform -> UniqFM FastString ([CmmExpr] -> (CallishMachOp, [CmmExpr])) ===================================== testsuite/tests/cmm/opt/T25771.cmm ===================================== @@ -0,0 +1,8 @@ +// The point of this test is that the bitcast operations +// should be successfully constant-folded, without panicking. + +func (float64 x) { + x = %fadd(x, %w2f_bitcast(0x4028b0a3d70a3d71 :: bits64)); + x = %fadd(x, %f2f64(%w2f_bitcast(0x3f2a0000 :: bits32))); + return (x); +} ===================================== testsuite/tests/cmm/opt/T25771.stderr ===================================== @@ -0,0 +1,20 @@ + +==================== Output Cmm ==================== +[func() { // [D1] + { info_tbls: [] + stack_info: arg_space: 8 + } + {offset + c2: // global + //tick src<T25771.cmm:(4,18)-(8,1)> + //tick src<T25771.cmm:5:5-59> + //tick src<T25771.cmm:6:5-59> + _c1::F64 = D1; // CmmAssign + _c1::F64 = %MO_F_Add_W64(D1, 12.345 :: W64); // CmmAssign + D1 = %MO_F_Add_W64(_c1::F64, + %MO_FF_Conv_W32_W64(0.6640625 :: W32)); // CmmAssign + call (P64[Sp])(D1) args: 8, res: 0, upd: 8; // CmmCall + } + }] + + ===================================== testsuite/tests/cmm/opt/all.T ===================================== @@ -8,3 +8,7 @@ test('T20142', normal, compile, ['']) # We check this by telling the assembler to exit on warnings. test('T24556', [only_ways('optasm'), cmm_src], compile, ['-O -opta -Xassembler -opta --fatal-warnings']) +test('T25771', [cmm_src, only_ways(['optasm']), + grep_errmsg(r'(12\.345|0\.6640625)',[1]), + ], + compile, ['-ddump-cmm']) ===================================== testsuite/tests/codeGen/should_run/all.T ===================================== @@ -210,7 +210,9 @@ test('T16846', [only_ways(['optasm']), exit_code(1)], compile_and_run, ['']) test('T17920', [cmm_src], compile_and_run, ['']) test('T18527', req_c, compile_and_run, ['T18527FFI.c']) test('T19149', [req_c,only_ways('sanity')], compile_and_run, ['T19149_c.c']) -test('T20275', normal, compile_and_run, ['']) +test('T20275', [unless(js_arch(),extra_ways(['optasm']))], compile_and_run, ['']) + # Also tested with optimizations because + # that's the original reproducer for #25771 test('CallConv', [when(unregisterised(), skip), unless(arch('x86_64') or arch('aarch64'), skip), View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b05c27bf186e66edc4fbf4a54943c8bd04f5024...30bdea67fcd9755619b1f513d199f2122591b28e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b05c27bf186e66edc4fbf4a54943c8bd04f5024...30bdea67fcd9755619b1f513d199f2122591b28e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/568839fe/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 6 23:32:36 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Thu, 06 Mar 2025 18:32:36 -0500 Subject: [Git][ghc/ghc][wip/int-index/conpat-one-list] One list in ConPat (part of #25127) Message-ID: <67ca30944e0bf_31b8ae54886485365@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/conpat-one-list at Glasgow Haskell Compiler / GHC Commits: 640080a9 by Vladislav Zavialov at 2025-03-07T02:30:51+03:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - 54 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/GREInfo.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/640080a9e85c12934fea655ec6f0d70c936e30d0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/640080a9e85c12934fea655ec6f0d70c936e30d0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/87291f72/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 23:45:32 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Thu, 06 Mar 2025 18:45:32 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/int-index/conpat-one-list-th Message-ID: <67ca339bf369b_33e0d8c87309294d@gitlab.mail> Vladislav Zavialov pushed new branch wip/int-index/conpat-one-list-th at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/int-index/conpat-one-list-th You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/97e148a4/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 6 23:57:57 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 06 Mar 2025 18:57:57 -0500 Subject: [Git][ghc/ghc][wip/T24359] new plan from March 7 Message-ID: <67ca3684e81c6_33e0d815e3c094617@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 4a48dbec by sheaf at 2025-03-07T00:57:42+01:00 new plan from March 7 - - - - - 9 changed files: - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Types/Evidence.hs - testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs Changes: ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -39,7 +39,7 @@ import GHC.Tc.Gen.HsType import GHC.Tc.Solver( reportUnsolvedEqualities, pushLevelAndSolveEqualitiesX , emitResidualConstraints ) import GHC.Tc.Solver.Solve( solveWanteds ) -import GHC.Tc.Solver.Monad( runTcS, runTcSWithEvBinds ) +import GHC.Tc.Solver.Monad( runTcS, runTcSFullySolve ) import GHC.Tc.Validity ( checkValidType ) import GHC.Tc.Utils.Monad @@ -1029,38 +1029,22 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) <- tcRuleBndrs skol_info rule_bndrs $ tcInferRho spec_e - -- (2) Clone these Wanteds, solve them, and zonk the original - -- Wanteds, in order to benefit from any unifications. - - ; throwaway_ev_binds_var <- newTcEvBinds - ; spec_e_wanted_clone <- cloneWC spec_e_wanted - ; _ <- setTcLevel rhs_tclvl $ - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds spec_e_wanted_clone + -- (2) Solve the resulting wanteds in TcSFullySolve mode. + ; ev_binds_var <- newTcEvBinds + ; spec_e_wanted <- setTcLevel rhs_tclvl $ + runTcSFullySolve ev_binds_var $ + solveWanteds spec_e_wanted ; spec_e_wanted <- liftZonkM $ zonkWC spec_e_wanted -- (3) Compute which constraints to quantify over. - -- (a) Compute quantification candidates - ; ev_binds_var <- newTcEvBinds ; (quant_cands, residual_wc) <- getRuleQuantCts spec_e_wanted - -- (b) Compute fully soluble constraints - -- See Note [Fully solving constraints for specialisation] - ; traceTc "tcSpecPrag SpecSigE: computing fully soluble Wanteds {" empty - ; fully_soluble_evids <- - setTcLevel rhs_tclvl $ - mkVarSet <$> - mapMaybeM fullySolveCt_maybe (bagToList quant_cands) - ; let (fully_soluble_cts, quant_cts) = partitionBag ((`elemVarSet` fully_soluble_evids) . ctEvId) quant_cands - -- (c) Compute constraints to quantify over using 'mkMinimalBySCs' - qevs = map ctEvId (bagToList quant_cts) - ; traceTc "tcSpecPrag SpecSigE: computed fully soluble Wanteds }" (ppr fully_soluble_cts) - -- (4) Emit the residual constraints (that we are not quantifying over) ; let tv_bndrs = filter isTyVar rule_bndrs' + qevs = map ctEvId (bagToList quant_cands) ; emitResidualConstraints rhs_tclvl skol_info_anon ev_binds_var emptyVarSet tv_bndrs qevs - (residual_wc `addSimples` fully_soluble_cts) + residual_wc ; let lhs_call = mkLHsWrap (WpLet (TcEvBinds ev_binds_var)) tc_spec_e ; traceTc "tcSpecPrag SpecSigE }" $ @@ -1070,9 +1054,8 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) , text "spec_e:" <+> ppr tc_spec_e , text "inl:" <+> ppr inl , text "spec_e_wanted:" <+> ppr spec_e_wanted - , text "quant_cts:" <+> ppr quant_cts + , text "quant_cands:" <+> ppr quant_cands , text "residual_wc:" <+> ppr residual_wc - , text "fully_soluble_wanteds:" <+> ppr fully_soluble_cts ] -- (5) Store the results in a SpecPragE record, which will be @@ -1087,24 +1070,6 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) tcSpecPrag _ prag = pprPanic "tcSpecPrag" (ppr prag) --- | Try to fully solve a constraint. -fullySolveCt_maybe :: Ct -> TcM (Maybe EvId) -fullySolveCt_maybe ct = do - throwaway_ev_binds_var <- newTcEvBinds - res_wc <- - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds $ emptyWC { wc_simple = unitBag ct } - -- NB: don't use 'solveSimpleWanteds', as this will not - -- fully solve quantified constraints. - traceTc "fullySolveCt_maybe" $ - vcat [ text "ct:" <+> ppr ct - , text "res_wc:" <+> ppr res_wc - ] - return $ - if isSolvedWC res_wc - then Just $ ctEvId ct - else Nothing - -------------- tcSpecWrapper :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper -- A simpler variant of tcSubType, used for SPECIALISE pragmas ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -61,6 +61,7 @@ import Data.Void( Void ) import Control.Monad.Trans.Maybe( MaybeT, runMaybeT ) import Control.Monad.Trans.Class( lift ) import Control.Monad +import {-# SOURCE #-} GHC.Tc.Solver.Solve (solveCompletelyIfRequired) {- ********************************************************************* @@ -101,26 +102,6 @@ solveDict dict_ct@(DictCt { di_ev = ev, di_cls = cls, di_tys = tys }) ; simpleStage (updInertDicts dict_ct) ; stopWithStage (dictCtEvidence dict_ct) "Kept inert DictCt" } -updInertDicts :: DictCt -> TcS () -updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys }) - = do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls <+> ppr tys) - - ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys - -> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters] - -- Update /both/ inert_cans /and/ inert_solved_dicts. - updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) -> - inerts { inert_cans = updDicts (filterDicts (not_ip_for str_ty)) ics - , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved } - | otherwise - -> return () - - -- Add the new constraint to the inert set - ; updInertCans (updDicts (addDict dict_ct)) } - where - not_ip_for :: Type -> DictCt -> Bool - not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys }) - = not (mentionsIP str_ty cls tys) - canDictCt :: CtEvidence -> Class -> [Type] -> SolverStage DictCt -- Once-only processing of Dict constraints: -- * expand superclasses @@ -868,7 +849,8 @@ shortCutSolver dflags ev_w ev_i tryInstances :: DictCt -> SolverStage () tryInstances dict_ct = Stage $ do { inerts <- getInertSet - ; try_instances inerts dict_ct } + ; solveCompletelyIfRequired (continueWith ()) $ + try_instances inerts dict_ct } try_instances :: InertSet -> DictCt -> TcS (StopOrContinue ()) -- Try to use type-class instance declarations to simplify the constraint ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeApplications #-} @@ -16,6 +17,7 @@ module GHC.Tc.Solver.InertSet ( InertSet(..), InertCans(..), emptyInert, + partitionInerts, andInertSet, noGivenNewtypeReprEqs, updGivenEqs, prohibitedSuperClassSolve, @@ -54,7 +56,7 @@ import GHC.Tc.Types.Constraint import GHC.Tc.Types.Origin import GHC.Tc.Types.CtLoc( CtLoc, ctLocOrigin, ctLocSpan, ctLocLevel ) import GHC.Tc.Solver.Types -import GHC.Tc.Utils.TcType +import GHC.Tc.Utils.TcType hiding () -- Make sure maxTcLevel is imported import GHC.Types.Var import GHC.Types.Var.Env @@ -286,9 +288,9 @@ extendWorkListCts :: Cts -> WorkList -> WorkList extendWorkListCts cts wl = foldr extendWorkListCt wl cts isEmptyWorkList :: WorkList -> Bool -isEmptyWorkList (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X +isEmptyWorkList (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X, wl_rw_eqs = rw_eqs , wl_rest = rest, wl_implics = implics }) - = null eqs_N && null eqs_X && null rest && isEmptyBag implics + = null eqs_N && null eqs_X && null rw_eqs && null rest && isEmptyBag implics emptyWorkList :: WorkList emptyWorkList = WL { wl_eqs_N = [], wl_eqs_X = [] @@ -390,7 +392,6 @@ emptyInert , inert_famapp_cache = emptyFunEqs , inert_solved_dicts = emptyDictMap } - {- Note [Solved dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When we apply a top-level instance declaration, we add the "solved" @@ -2214,3 +2215,116 @@ Wrong! The level-check ensures that the inner implicit parameter wins. (Actually I think that the order in which the work-list is processed means that this chain of events won't happen, but that's very fragile.) -} + +-- | Partition the inert set according to a predicate. +partitionInerts :: (Ct -> Bool) -> InertSet -> (InertSet, InertSet) +partitionInerts pred is@(IS { inert_cans = cans }) + = (is { inert_cans = givens_cans }, is { inert_cans = wanteds_cans }) + where + -- Helper functions to convert between Ct and specific constraint types + eqPred :: EqCt -> Bool + eqPred eq = pred (CEqCan eq) + + dictPred :: DictCt -> Bool + dictPred dict = pred (CDictCan dict) + + irredPred :: IrredCt -> Bool + irredPred irred = pred (CIrredCan irred) + + qciPred :: QCInst -> Bool + qciPred qci = pred (CQuantCan qci) + + -- Partition the inert constraints + (eq_givens_list, eq_wanteds) = partitionInertEqs eqPred (inert_eqs cans) + (funeq_givens_list, funeq_wanteds) = partitionFunEqs eqPred (inert_funeqs cans) + (dict_givens_bag, dict_wanteds) = partitionDicts dictPred (inert_dicts cans) + (safehask_givens_bag, safehask_wanteds) = partitionDicts dictPred (inert_safehask cans) + insts_givens = filter qciPred (inert_insts cans) + insts_wanteds = filter (not . qciPred) (inert_insts cans) + (irreds_givens, irreds_wanteds) = partitionBag irredPred (inert_irreds cans) + + -- Convert lists to the appropriate container types + eq_givens = foldr addInertEqs emptyTyEqs eq_givens_list + funeq_givens = foldr addFunEqs emptyFunEqs funeq_givens_list + + givens_cans = emptyInertCans { + inert_eqs = eq_givens, + inert_funeqs = funeq_givens, + inert_dicts = dictsToDictMap dict_givens_bag, + inert_safehask = dictsToDictMap safehask_givens_bag, + inert_insts = insts_givens, + inert_irreds = irreds_givens, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + + wanteds_cans = emptyInertCans { + inert_eqs = eq_wanteds, + inert_funeqs = funeq_wanteds, + inert_dicts = dict_wanteds, + inert_safehask = safehask_wanteds, + inert_insts = insts_wanteds, + inert_irreds = irreds_wanteds, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + +-- | Convert a Bag of DictCts to a DictMap +dictsToDictMap :: Bag DictCt -> DictMap DictCt +dictsToDictMap = foldr addDict emptyDictMap . bagToList + +-- | Union two DictMaps +unionDictMap :: DictMap DictCt -> DictMap DictCt -> DictMap DictCt +unionDictMap dm1 dm2 = foldrTcAppMap addDict dm1 dm2 + +-- | Union two InertEqs +unionTyEqs :: InertEqs -> InertEqs -> InertEqs +unionTyEqs eqs1 eqs2 = foldrTyEqs addInertEqs eqs1 eqs2 + +-- | Union two InertFunEqs +unionFunEqs :: InertFunEqs -> InertFunEqs -> InertFunEqs +unionFunEqs feqs1 feqs2 = foldrFunEqs addFunEqs feqs1 feqs2 + +-- | Union two FunEqMap Reductions +unionFunEqMap :: FunEqMap Reduction -> FunEqMap Reduction -> FunEqMap Reduction +unionFunEqMap m1 m2 = foldTcAppMap (\r acc -> + let ty = reductionReducedType r + in case tcSplitTyConApp_maybe ty of + Just (tc, args) -> insertTcApp acc tc args r + Nothing -> acc) + m1 m2 + +-- | Fold over a TcAppMap with a function +foldrTcAppMap :: (a -> b -> b) -> TcAppMap a -> b -> b +foldrTcAppMap k m z = foldTcAppMap (\x acc -> k x acc) m z + +-- | Fold over FunEqs with a function +foldrFunEqs :: (EqCt -> b -> b) -> InertFunEqs -> b -> b +foldrFunEqs k feqs z = foldFunEqs (\eq acc -> k eq acc) feqs z + +-- | Fold over TyEqs with a function +foldrTyEqs :: (EqCt -> b -> b) -> InertEqs -> b -> b +foldrTyEqs k eqs z = foldTyEqs (\eq acc -> k eq acc) eqs z + +-- | Combine two 'InertSet's in a monoidal manner. +andInertSet :: InertSet -> InertSet -> InertSet +andInertSet is1 is2 + = IS { inert_cans = combinedCans, + inert_cycle_breakers = inert_cycle_breakers is1, -- Keep the first one's cycle breakers + inert_famapp_cache = unionFunEqMap (inert_famapp_cache is1) (inert_famapp_cache is2), + inert_solved_dicts = unionDictMap (inert_solved_dicts is1) (inert_solved_dicts is2) + } + where + cans1 = inert_cans is1 + cans2 = inert_cans is2 + + combinedCans = IC { + inert_eqs = unionTyEqs (inert_eqs cans1) (inert_eqs cans2), + inert_funeqs = unionFunEqs (inert_funeqs cans1) (inert_funeqs cans2), + inert_dicts = unionDictMap (inert_dicts cans1) (inert_dicts cans2), + inert_safehask = unionDictMap (inert_safehask cans1) (inert_safehask cans2), + inert_insts = inert_insts cans1 ++ inert_insts cans2, + inert_irreds = unionBags (inert_irreds cans1) (inert_irreds cans2), + inert_given_eq_lvl = maxTcLevel (inert_given_eq_lvl cans1) (inert_given_eq_lvl cans2), + inert_given_eqs = inert_given_eqs cans1 || inert_given_eqs cans2 + } ===================================== compiler/GHC/Tc/Solver/Irred.hs ===================================== @@ -39,10 +39,6 @@ solveIrred irred ; simpleStage (updInertIrreds irred) ; stopWithStage (irredCtEvidence irred) "Kept inert IrredCt" } -updInertIrreds :: IrredCt -> TcS () -updInertIrreds irred - = do { tc_lvl <- getTcLevel - ; updInertCans $ addIrredToCans tc_lvl irred } {- ********************************************************************* * * ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -14,7 +14,9 @@ module GHC.Tc.Solver.Monad ( -- The TcS monad - TcS, runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + TcS(..), TcSEnv(..), TcSMode(..), + runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + runTcSFullySolve, failTcS, warnTcS, addErrTcS, wrapTcS, ctLocWarnTcS, runTcSEqualities, nestTcS, nestImplicTcS, setEvBindsTcS, @@ -71,9 +73,10 @@ module GHC.Tc.Solver.Monad ( getInertEqs, getInertCans, getInertGivens, getInertInsols, getInnermostGivenEqLevel, getInertSet, setInertSet, - getUnsolvedInerts, + getUnsolvedInerts, getUnsolvedInerts2, removeInertCts, getPendingGivenScs, insertFunEq, addInertForAll, + updInertDicts, updInertIrreds, emitWorkNC, emitWork, lookupInertDict, @@ -202,13 +205,14 @@ import GHC.Exts (oneShot) import Control.Monad import Data.Foldable hiding ( foldr1 ) import Data.IORef -import Data.List ( mapAccumL ) +import Data.List ( mapAccumL, unfoldr ) import Data.List.NonEmpty ( nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) import qualified Data.Semigroup as S import GHC.Types.SrcLoc import GHC.Rename.Env +--import GHC.Tc.Solver.Solve (solveWanteds) #if defined(DEBUG) import GHC.Types.Unique.Set (nonDetEltsUniqSet) @@ -369,6 +373,31 @@ duplicates, is explained in Note [Use only the best matching quantified constrai in GHC.Tc.Solver.Dict. -} +updInertDicts :: DictCt -> TcS () +updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys }) + = do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls <+> ppr tys) + + ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys + -> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters] + -- Update /both/ inert_cans /and/ inert_solved_dicts. + updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) -> + inerts { inert_cans = updDicts (filterDicts (not_ip_for str_ty)) ics + , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved } + | otherwise + -> return () + + -- Add the new constraint to the inert set + ; updInertCans (updDicts (addDict dict_ct)) } + where + not_ip_for :: Type -> DictCt -> Bool + not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys }) + = not (mentionsIP str_ty cls tys) + +updInertIrreds :: IrredCt -> TcS () +updInertIrreds irred + = do { tc_lvl <- getTcLevel + ; updInertCans $ addIrredToCans tc_lvl irred } + {- ********************************************************************* * * Kicking out @@ -579,7 +608,7 @@ getInertGivens :: TcS [Ct] getInertGivens = do { inerts <- getInertCans ; let all_cts = foldIrreds ((:) . CIrredCan) (inert_irreds inerts) - $ foldDicts ((:) . CDictCan) (inert_dicts inerts) + $ foldDicts ((:) . CDictCan) (inert_dicts inerts) $ foldFunEqs ((:) . CEqCan) (inert_funeqs inerts) $ foldTyEqs ((:) . CEqCan) (inert_eqs inerts) $ [] @@ -679,6 +708,45 @@ getUnsolvedInerts where ct = mk_ct thing +getUnsolvedInerts2 :: TcS ( Bag Implication, Cts ) +getUnsolvedInerts2 + = do { IC { inert_eqs = tv_eqs + , inert_funeqs = fun_eqs + , inert_irreds = irreds + , inert_dicts = idicts + } <- getInertCans + + ; let unsolved_tv_eqs = foldTyEqs (add_if_unsolved CEqCan) tv_eqs emptyCts + unsolved_fun_eqs = foldFunEqs (add_if_unsolved CEqCan) fun_eqs emptyCts + unsolved_irreds = foldr (add_if_unsolved CIrredCan) emptyCts irreds + unsolved_dicts = foldDicts (add_if_unsolved CDictCan) idicts emptyCts + + ; wl_var <- getTcSWorkListRef + ; wl_curr <- readTcRef wl_var + ; implics <- getWorkListImplics + ; let wl_simpls = listToBag $ unfoldr selectWorkItem wl_curr + + ; traceTcS "getUnsolvedInerts" $ + vcat [ text " tv eqs =" <+> ppr unsolved_tv_eqs + , text "fun eqs =" <+> ppr unsolved_fun_eqs + , text "dicts =" <+> ppr unsolved_dicts + , text "irreds =" <+> ppr unsolved_irreds + , text "implics =" <+> ppr implics ] + + ; return ( implics, unsolved_tv_eqs `unionBags` + unsolved_fun_eqs `unionBags` + unsolved_irreds `unionBags` + unsolved_dicts `unionBags` + wl_simpls) } + where + add_if_unsolved :: (a -> Ct) -> a -> Cts -> Cts + add_if_unsolved mk_ct thing cts + | isWantedCt ct = ct `consCts` cts + | otherwise = cts + where + ct = mk_ct thing + + getHasGivenEqs :: TcLevel -- TcLevel of this implication -> TcS ( HasGivenEqs -- are there Given equalities? , InertIrreds ) -- Insoluble equalities arising from givens @@ -824,6 +892,27 @@ for it, so TcS carries a mutable location where the binding can be added. This is initialised from the innermost implication constraint. -} +-- | See Note [TcSMode] +data TcSMode + = TcSVanilla -- ^ Normal constraint solving + | TcSEarlyAbort -- ^ Abort early on insoluble constraints + | TcSFullySolve -- ^ Fully solve all constraints + deriving (Eq) + +{- Note [TcSMode] +~~~~~~~~~~~~~~~~~ +The constraint solver can operate in different modes: + +* TcSVanilla: Normal constraint solving mode. This is the default. + +* TcSEarlyAbort: Abort (fail in the monad) as soon as we come across an + insoluble constraint. This is used to fail-fast when checking for hole-fits. + See Note [Speeding up valid hole-fits]. + +* TcSFullySolve: Fully solve all constraints. This mode is not currently used + but is included for future extensions. +-} + data TcSEnv = TcSEnv { tcs_ev_binds :: EvBindsVar, @@ -843,13 +932,11 @@ data TcSEnv tcs_inerts :: IORef InertSet, -- Current inert set - -- Whether to throw an exception if we come across an insoluble constraint. - -- Used to fail-fast when checking for hole-fits. See Note [Speeding up - -- valid hole-fits]. - tcs_abort_on_insoluble :: Bool, + -- | The mode of operation for the constraint solver. + -- See Note [TcSMode] + tcs_mode :: TcSMode, - -- See Note [WorkList priorities] in GHC.Tc.Solver.InertSet - tcs_worklist :: IORef WorkList -- Current worklist + tcs_worklist :: IORef WorkList } --------------- @@ -920,9 +1007,9 @@ addErrTcS = wrapTcS . TcM.addErr panicTcS doc = pprPanic "GHC.Tc.Solver.Monad" doc tryEarlyAbortTcS :: TcS () --- Abort (fail in the monad) if the abort_on_insoluble flag is on +-- Abort (fail in the monad) if the mode is TcSEarlyAbort tryEarlyAbortTcS - = mkTcS (\env -> when (tcs_abort_on_insoluble env) TcM.failM) + = mkTcS (\env -> when (tcs_mode env == TcSEarlyAbort) TcM.failM) -- | Emit a warning within the 'TcS' monad at the location given by the 'CtLoc'. ctLocWarnTcS :: CtLoc -> TcRnMessage -> TcS () @@ -992,7 +1079,15 @@ runTcS tcs runTcSEarlyAbort :: TcS a -> TcM a runTcSEarlyAbort tcs = do { ev_binds_var <- TcM.newTcEvBinds - ; runTcSWithEvBinds' True True ev_binds_var tcs } + ; runTcSWithEvBinds' True TcSEarlyAbort ev_binds_var tcs } + +-- | Run the TcS monad in 'TcSFullySolve' mode, +-- which attempts to fully solve all constraints. +-- +-- See Note [Fully solving constraints for specialisation] +runTcSFullySolve :: EvBindsVar -> TcS a -> TcM a +runTcSFullySolve ev_binds_var tcs + = runTcSWithEvBinds' True TcSFullySolve ev_binds_var tcs -- | This can deal only with equality constraints. runTcSEqualities :: TcS a -> TcM a @@ -1005,7 +1100,7 @@ runTcSEqualities thing_inside runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet) runTcSInerts inerts tcs = do ev_binds_var <- TcM.newTcEvBinds - runTcSWithEvBinds' False False ev_binds_var $ do + runTcSWithEvBinds' False TcSVanilla ev_binds_var $ do setInertSet inerts a <- tcs new_inerts <- getInertSet @@ -1014,17 +1109,17 @@ runTcSInerts inerts tcs = do runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds = runTcSWithEvBinds' True False +runTcSWithEvBinds = runTcSWithEvBinds' True TcSVanilla -runTcSWithEvBinds' :: Bool -- ^ Restore type variable cycles afterwards? +runTcSWithEvBinds' :: Bool -- True <=> restore type equality cycles -- Don't if you want to reuse the InertSet. -- See also Note [Type equality cycles] -- in GHC.Tc.Solver.Equality - -> Bool + -> TcSMode -> EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs +runTcSWithEvBinds' restore_cycles mode ev_binds_var tcs = do { unified_var <- TcM.newTcRef 0 ; step_count <- TcM.newTcRef 0 ; inert_var <- TcM.newTcRef emptyInert @@ -1035,7 +1130,7 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs , tcs_unif_lvl = unif_lvl_var , tcs_count = step_count , tcs_inerts = inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = wl_var } -- Run the computation @@ -1097,7 +1192,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_inerts = old_inert_var , tcs_count = count , tcs_unif_lvl = unif_lvl - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode } -> do { inerts <- TcM.readTcRef old_inert_var ; let nest_inert = inerts { inert_cycle_breakers = pushCycleBreakerVarStack @@ -1112,7 +1207,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_ev_binds = ref , tcs_unified = unified_var , tcs_inerts = new_inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = new_wl_var } ; res <- TcM.setTcLevel inner_tclvl $ thing_inside nest_env @@ -1127,7 +1222,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) #endif ; return res } -nestTcS :: TcS a -> TcS a +nestTcS :: TcS a -> TcS a -- Use the current untouchables, augmenting the current -- evidence bindings, and solved dictionaries -- But have no effect on the InertCans, or on the inert_famapp_cache ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RecursiveDo #-} module GHC.Tc.Solver.Solve ( @@ -5,6 +6,7 @@ module GHC.Tc.Solver.Solve ( solveWanteds, -- Solves WantedConstraints solveSimpleGivens, -- Solves [Ct] solveSimpleWanteds, -- Solves Cts + solveCompletelyIfRequired, setImplicationStatus ) where @@ -51,6 +53,7 @@ import GHC.Driver.Session import Data.List( deleteFirstsBy ) import Control.Monad +import Data.Foldable ( for_ ) import qualified Data.Semigroup as S import Data.Void( Void ) @@ -1214,6 +1217,7 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo tvs theta pred _fuel = -- See Note [Solving a Wanted forall-constraint] TcS.setSrcSpan (getCtLocEnvLoc $ ctLocEnv loc) $ + solveCompletelyIfRequired add_inert_wanted_qc $ -- This setSrcSpan is important: the emitImplicationTcS uses that -- TcLclEnv for the implication, and that in turn sets the location -- for the Givens when solving the constraint (#21006) @@ -1251,6 +1255,10 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo ; stopWith ev "Wanted forall-constraint" } where + add_inert_wanted_qc = + do { updInertIrreds (IrredCt ev IrredShapeReason) + ; stopWith ev "Wanted QC not fully solved" + } -- Getting the size of the head is a bit horrible -- because of the special treament for class predicates get_size pred = case classifyPredType pred of @@ -1298,7 +1306,7 @@ Note [Solving a Given forall-constraint] For a Given constraint [G] df :: forall ab. (Eq a, Ord b) => C x a b we just add it to TcS's local InstEnv of known instances, -via addInertForall. Then, if we look up (C x Int Bool), say, +via addInertForAll. Then, if we look up (C x Int Bool), say, we'll find a match in the InstEnv. @@ -1539,3 +1547,103 @@ runTcPluginSolvers solvers all_cts CtWanted {} -> (givens, (ev,ct):wanteds) +-------------------------------------------------------------------------------- + +-- | If the mode is 'TcSFullySolve', attempt to fully solve the Wanted +-- constraints that arise from 'thing_inside'; returning whether this was +-- successful. +-- +-- If not in 'TcSFullySolve' mode, simply run 'thing_inside'. +solveCompletelyIfRequired :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) +solveCompletelyIfRequired not_fully_solved_action (TcS thing_inside) + = TcS $ \ env@(TcSEnv { tcs_ev_binds = outer_ev_binds_var + , tcs_unified = outer_unified_var + , tcs_inerts = outer_inert_var + , tcs_count = outer_count + , tcs_mode = mode + }) -> + case mode of + TcSFullySolve -> + do { traceTc "solveCompletelyIfRequired {" empty + -- Create a fresh environment for the inner computation + ; outer_inerts <- TcM.readTcRef outer_inert_var + ; let (outer_givens, outer_wanteds) = + partitionInerts isGivenCt outer_inerts + -- Keep the ambient Given inerts, but drop the Wanteds. + ; new_inert_var <- TcM.newTcRef outer_givens + ; new_wl_var <- TcM.newTcRef emptyWorkList + ; new_ev_binds_var <- TcM.newTcEvBinds + ; new_unified_var <- TcM.newTcRef 0 + ; new_count <- TcM.newTcRef 0 + ; new_unif_lvl <- TcM.newTcRef Nothing + + ; let + inner_env = + TcSEnv + -- KEY part: recur with TcSVanilla + { tcs_mode = TcSVanilla + + -- Use new variables for the inner computation, because + -- we may want to discard its state entirely. + , tcs_count = new_count + , tcs_unif_lvl = new_unif_lvl + , tcs_ev_binds = new_ev_binds_var + , tcs_unified = new_unified_var + , tcs_inerts = new_inert_var + , tcs_worklist = new_wl_var + } + -- Run the inner computation + ; traceTc "solveCompletelyIfRequired thing_inside {{" empty + ; r <- thing_inside inner_env + ; wl <- TcM.readTcRef new_wl_var + ; traceTc "solveCompletelyIfRequired thing_inside }}" $ + vcat [ text "work list:" <+> ppr wl ] + + -- Now attempt to solve the resulting constraints using 'solveWanteds' + ; (implics, simples) <- unTcS getUnsolvedInerts2 inner_env + ; let wc = emptyWC { wc_simple = simples, wc_impl = implics } + ; traceTc "solveCompletelyIfRequired solveWanteds" $ + vcat [ text "wc:" <+> ppr wc + ] + ; solved_wc <- unTcS (solveWanteds wc) inner_env + + ; if isSolvedWC solved_wc + then + do { -- The constraint was fully solved. Continue with + -- the inner solved state. + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + + -- Add new evidence bindings to the existing ones + ; inner_ev_binds <- TcM.getTcEvBindsMap new_ev_binds_var + ; outer_ev_binds <- TcM.getTcEvBindsMap outer_ev_binds_var + ; let merged_ev_binds = outer_ev_binds `unionEvBindMap` inner_ev_binds + ; TcM.setTcEvBindsMap outer_ev_binds_var merged_ev_binds + + -- Use the new inert set, adding back on the outer Wanteds + ; new_inerts <- TcM.readTcRef new_inert_var + ; TcM.writeTcRef outer_inert_var (new_inerts `andInertSet` outer_wanteds) + + -- Update the outer unified, count, and unif_lvl variables + ; inner_unified <- TcM.readTcRef new_unified_var + ; inner_count <- TcM.readTcRef new_count + ; inner_unif_lvl <- TcM.readTcRef new_unif_lvl + ; TcM.updTcRef outer_unified_var (+ inner_unified) + ; TcM.updTcRef outer_count (+ inner_count) + ; for_ inner_unif_lvl $ \inner_lvl -> + unTcS (setUnificationFlag inner_lvl) env + + -- No need to update the outer work list: the inner work list + -- is empty by now (after 'solveWanteds'). + ; return r } + else + do { traceTc "solveCompletelyIfRequired: unsolved }" $ + vcat [ text "wc:" <+> ppr wc + ,text "solved_wc:" <+> ppr solved_wc ] + ; -- Failed to fully solve the constraint. + -- Discard the inner solver state and continue. + ; unTcS not_fully_solved_action env + } } + _notFullySolveMode -> + thing_inside env ===================================== compiler/GHC/Tc/Solver/Solve.hs-boot ===================================== @@ -0,0 +1,6 @@ +module GHC.Tc.Solver.Solve where + +import GHC.Tc.Solver.Monad (StopOrContinue, TcS) + +solveCompletelyIfRequired + :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) ===================================== compiler/GHC/Tc/Types/Evidence.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Tc.Types.Evidence ( -- * Evidence bindings TcEvBinds(..), EvBindsVar(..), - EvBindMap(..), emptyEvBindMap, extendEvBinds, + EvBindMap(..), emptyEvBindMap, extendEvBinds, unionEvBindMap, lookupEvBind, evBindMapBinds, foldEvBindMap, nonDetStrictFoldEvBindMap, filterEvBindMap, @@ -433,6 +433,11 @@ extendEvBinds bs ev_bind (eb_lhs ev_bind) ev_bind } +unionEvBindMap :: EvBindMap -> EvBindMap -> EvBindMap +unionEvBindMap bs1 bs2 + = EvBindMap { ev_bind_varenv = plusDVarEnv (ev_bind_varenv bs1) + (ev_bind_varenv bs2) } + isEmptyEvBindMap :: EvBindMap -> Bool isEmptyEvBindMap (EvBindMap m) = isEmptyDVarEnv m ===================================== testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs ===================================== @@ -17,7 +17,6 @@ import Data.Proxy f1 :: ( Num a, Eq b ) => a -> b -> Int f1 _ _ = 111 - -- Make sure we don't generate a rule with an LHS of the form -- -- forall @e (d :: Eq e). f1 @[e] ($fEqList d) = ... @@ -56,12 +55,18 @@ f3 z = z == z -------------------------------------------------------------------------------- -f4 :: Monad m => a -> m a +f4 :: (Eq a, Monad m) => a -> m a f4 = return -- Check we can deal with locally quantified variables in constraints, -- in this case 'Monad (ST s)'. -{-# SPECIALISE f4 :: b -> ST s b #-} +{-# SPECIALISE f4 :: forall s b. Eq b => b -> ST s b #-} + +f4_qc :: (Eq a, forall m. Monad m => Monad (t m)) => t m a -> () +f4_qc _ = () + +-- Like 'f4' but with a quantified constraint. +{-# SPECIALISE f4_qc :: forall r n b. (forall m. Monad m => Monad (r m)) => r n Int -> () #-} -------------------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4a48dbecf15ebd7f5d4dc80b63057cbb62e19c73 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4a48dbecf15ebd7f5d4dc80b63057cbb62e19c73 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250306/3d37c7e7/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 07:35:13 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Fri, 07 Mar 2025 02:35:13 -0500 Subject: [Git][ghc/ghc][wip/supersven/riscv-fix-switch-jump-tables] RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738) Message-ID: <67caa1b17b62b_385d8d1720014116919@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-fix-switch-jump-tables at Glasgow Haskell Compiler / GHC Commits: e24e647a by Sven Tennie at 2025-03-07T08:34:58+01:00 RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738) J_TBL result in local jumps, there should not deallocate stack slots (see Note [extra spill slots].) J is for non-local jumps, these may need to deallocate stack slots. - - - - - 3 changed files: - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/RV64/CodeGen.hs ===================================== @@ -1481,7 +1481,7 @@ assignReg_FltCode = assignReg_IntCode genJump :: CmmExpr {-the branch target-} -> NatM InstrBlock genJump expr = do (target, _format, code) <- getSomeReg expr - return (code `appOL` unitOL (annExpr expr (B (TReg target)))) + return (code `appOL` unitOL (annExpr expr (J (TReg target)))) -- ----------------------------------------------------------------------------- -- Unconditional branches @@ -2217,6 +2217,7 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks = -- jumps to registers have size 1 BCOND {} -> long_bc_jump_size B (TBlock _) -> long_b_jump_size + J _ -> 1 B (TReg _) -> 1 BL _ _ -> 1 J_TBL {} -> 1 ===================================== compiler/GHC/CmmToAsm/RV64/Instr.hs ===================================== @@ -97,6 +97,7 @@ regUsageOfInstr platform instr = case instr of ORI dst src1 _ -> usage (regOp src1, regOp dst) XORI dst src1 _ -> usage (regOp src1, regOp dst) J_TBL _ _ t -> usage ([t], []) + J t -> usage (regTarget t, []) B t -> usage (regTarget t, []) BCOND _ l r t -> usage (regTarget t ++ regOp l ++ regOp r, []) BL t ps -> usage (t : ps, callerSavedRegisters) @@ -195,6 +196,7 @@ patchRegsOfInstr instr env = case instr of ORI o1 o2 o3 -> ORI (patchOp o1) (patchOp o2) (patchOp o3) XORI o1 o2 o3 -> XORI (patchOp o1) (patchOp o2) (patchOp o3) J_TBL ids mbLbl t -> J_TBL ids mbLbl (env t) + J t -> J (patchTarget t) B t -> B (patchTarget t) BL t ps -> BL (patchReg t) ps BCOND c o1 o2 t -> BCOND c (patchOp o1) (patchOp o2) (patchTarget t) @@ -235,6 +237,7 @@ isJumpishInstr :: Instr -> Bool isJumpishInstr instr = case instr of ANN _ i -> isJumpishInstr i J_TBL {} -> True + J {} -> True B {} -> True BL {} -> True BCOND {} -> True @@ -243,6 +246,7 @@ isJumpishInstr instr = case instr of canFallthroughTo :: Instr -> BlockId -> Bool canFallthroughTo insn bid = case insn of + J (TBlock target) -> bid == target B (TBlock target) -> bid == target BCOND _ _ _ (TBlock target) -> bid == target J_TBL targets _ _ -> all isTargetBid targets @@ -256,6 +260,7 @@ canFallthroughTo insn bid = jumpDestsOfInstr :: Instr -> [BlockId] jumpDestsOfInstr (ANN _ i) = jumpDestsOfInstr i jumpDestsOfInstr (J_TBL ids _mbLbl _r) = catMaybes ids +jumpDestsOfInstr (J t) = [id | TBlock id <- [t]] jumpDestsOfInstr (B t) = [id | TBlock id <- [t]] jumpDestsOfInstr (BCOND _ _ _ t) = [id | TBlock id <- [t]] jumpDestsOfInstr _ = [] @@ -269,6 +274,7 @@ patchJumpInstr instr patchF = case instr of ANN d i -> ANN d (patchJumpInstr i patchF) J_TBL ids mbLbl r -> J_TBL (map (fmap patchF) ids) mbLbl r + J (TBlock bid) -> J (TBlock (patchF bid)) B (TBlock bid) -> B (TBlock (patchF bid)) BCOND c o1 o2 (TBlock bid) -> BCOND c o1 o2 (TBlock (patchF bid)) _ -> panic $ "patchJumpInstr: " ++ instrCon instr @@ -475,7 +481,7 @@ allocMoreStack platform slots proc@(CmmProc info lbl live (ListGraph code)) = do block' = foldr insert_dealloc [] insns insert_dealloc insn r = case insn of - J_TBL {} -> dealloc ++ (insn : r) + J {} -> dealloc ++ (insn : r) ANN _ e -> insert_dealloc e r _other | jumpDestsOfInstr insn /= [] -> @@ -591,6 +597,8 @@ data Instr -- -- @if(o2 cond o3) op <- 1 else op <- 0@ CSET Operand Operand Operand Cond + -- | like B, but only generated from genJump. Used to distinguish genJumps from others. + | J Target | -- | A jump instruction with data for switch/jump tables J_TBL [Maybe BlockId] (Maybe CLabel) Reg | -- | Unconditional jump (no linking) @@ -663,6 +671,7 @@ instrCon i = LDRU {} -> "LDRU" CSET {} -> "CSET" J_TBL {} -> "J_TBL" + J {} -> "J" B {} -> "B" BL {} -> "BL" BCOND {} -> "BCOND" ===================================== compiler/GHC/CmmToAsm/RV64/Ppr.hs ===================================== @@ -543,6 +543,7 @@ pprInstr platform instr = case instr of | otherwise -> op3 (text "\taddi") o1 o2 (OpImm (ImmInt 0)) ORI o1 o2 o3 -> op3 (text "\tori") o1 o2 o3 XORI o1 o2 o3 -> op3 (text "\txori") o1 o2 o3 + J o1 -> pprInstr platform (B o1) J_TBL _ _ r -> pprInstr platform (B (TReg r)) B l | isLabel l -> line $ text "\tjal" <+> pprOp platform x0 <> comma <+> getLabel platform l B (TReg r) -> line $ text "\tjalr" <+> pprOp platform x0 <> comma <+> pprReg W64 r <> comma <+> text "0" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e24e647affd10fb29d5f93a6ac0e74e270f03f7b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e24e647affd10fb29d5f93a6ac0e74e270f03f7b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/15789dea/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 07:40:51 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Fri, 07 Mar 2025 02:40:51 -0500 Subject: [Git][ghc/ghc][wip/supersven/riscv-fix-switch-jump-tables] 29 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67caa3034c5e0_385d8d181e394118575@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-fix-switch-jump-tables at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 1263d40a by Sven Tennie at 2025-03-07T08:40:37+01:00 RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738) J_TBL result in local jumps, there should not deallocate stack slots (see Note [extra spill slots].) J is for non-local jumps, these may need to deallocate stack slots. - - - - - 125 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/include/RtsAPI.h - rts/wasm/JSFFI.c - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e24e647affd10fb29d5f93a6ac0e74e270f03f7b...1263d40ad2072f9eb4eff2ed5938115cdcfebe9a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e24e647affd10fb29d5f93a6ac0e74e270f03f7b...1263d40ad2072f9eb4eff2ed5938115cdcfebe9a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/bb042de1/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 10:43:42 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 07 Mar 2025 05:43:42 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/fix_arm_linking Message-ID: <67cacddeb25e4_15c30a0cea4887e@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/fix_arm_linking at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/fix_arm_linking You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/da1b8b8d/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 11:03:52 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Fri, 07 Mar 2025 06:03:52 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/supersven/format-riscv-ncg-files Message-ID: <67cad298cf7df_15c30da7b7c116d6@gitlab.mail> Sven Tennie pushed new branch wip/supersven/format-riscv-ncg-files at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/format-riscv-ncg-files You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/524318b3/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 11:31:59 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 07 Mar 2025 06:31:59 -0500 Subject: [Git][ghc/ghc][wip/andreask/fix_arm_linking] Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." Message-ID: <67cad92f50cc6_15c30114933414513@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/fix_arm_linking at Glasgow Haskell Compiler / GHC Commits: e90e2dac by Andreas Klebinger at 2025-03-07T12:09:44+01:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 14 changed files: - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Unique/Supply.hs Changes: ===================================== compiler/GHC/Cmm/ThreadSanitizer.hs ===================================== @@ -145,7 +145,7 @@ mkUnsafeCall env ftgt formals args = -- arguments as Cmm-Lint checks this. To accomplish this we instead bind -- the arguments to local registers. arg_regs :: [CmmReg] - arg_regs = zipWith arg_reg (uniqListFromSupply arg_us) args + arg_regs = zipWith arg_reg (uniqsFromSupply arg_us) args where arg_reg :: Unique -> CmmExpr -> CmmReg arg_reg u expr = CmmLocal $ LocalReg u (cmmExprType (platform env) expr) @@ -169,7 +169,7 @@ saveRestoreCallerRegs us platform = nodes :: [(CmmNode O O, CmmNode O O)] nodes = - zipWith mk_reg regs_to_save (uniqListFromSupply us) + zipWith mk_reg regs_to_save (uniqsFromSupply us) where mk_reg :: GlobalReg -> Unique -> (CmmNode O O, CmmNode O O) mk_reg reg u = ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -1,6 +1,5 @@ {-# language GADTs, LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE LambdaCase #-} module GHC.CmmToAsm.AArch64.CodeGen ( cmmTopCodeGen , generateJumpTableForInstr @@ -51,9 +50,7 @@ import GHC.Types.Unique.DSM import GHC.Data.OrdList import GHC.Utils.Outputable -import Control.Monad ( join, mapAndUnzipM ) -import Data.List.NonEmpty ( NonEmpty (..), nonEmpty ) -import qualified Data.List.NonEmpty as NE +import Control.Monad ( mapAndUnzipM ) import GHC.Float import GHC.Types.Basic @@ -1590,7 +1587,7 @@ genCondJump bid expr = do _ -> pprPanic "AArch64.genCondJump: " (text $ show expr) -- A conditional jump with at least +/-128M jump range -genCondFarJump :: MonadGetUnique m => Cond -> Target -> m (NonEmpty Instr) +genCondFarJump :: MonadGetUnique m => Cond -> Target -> m InstrBlock genCondFarJump cond far_target = do skip_lbl_id <- newBlockId jmp_lbl_id <- newBlockId @@ -1600,13 +1597,11 @@ genCondFarJump cond far_target = do -- need to consider float orderings. -- So we take the hit of the additional jump in the false -- case for now. - pure - ( BCOND cond (TBlock jmp_lbl_id) :| - B (TBlock skip_lbl_id) : - NEWBLOCK jmp_lbl_id : - B far_target : - NEWBLOCK skip_lbl_id : - [] ) + return $ toOL [ BCOND cond (TBlock jmp_lbl_id) + , B (TBlock skip_lbl_id) + , NEWBLOCK jmp_lbl_id + , B far_target + , NEWBLOCK skip_lbl_id] genCondBranch :: BlockId -- the true branch target -> BlockId -- the false branch target @@ -2462,49 +2457,48 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks = -- Replace out of range conditional jumps with unconditional jumps. replace_blk :: LabelMap Int -> Int -> GenBasicBlock Instr -> UniqDSM (Int, [GenBasicBlock Instr]) - replace_blk !m !pos (BasicBlock lbl instrs) = case nonEmpty instrs of - Nothing -> pure (0, []) - Just instrs -> do - -- Account for a potential info table before the label. - let !block_pos = pos + infoTblSize_maybe lbl - (!pos', instrs') <- mapAccumLM (replace_jump m) block_pos instrs - let instrs'' = join instrs' - -- We might have introduced new labels, so split the instructions into basic blocks again if neccesary. - let (top, split_blocks, no_data) = foldr mkBlocks ([],[],[]) instrs'' - -- There should be no data in the instruction stream at this point - massert (null no_data) - - let final_blocks = BasicBlock lbl top : split_blocks - pure (pos', final_blocks) - - replace_jump :: LabelMap Int -> Int -> Instr -> UniqDSM (Int, NonEmpty Instr) + replace_blk !m !pos (BasicBlock lbl instrs) = do + -- Account for a potential info table before the label. + let !block_pos = pos + infoTblSize_maybe lbl + (!pos', instrs') <- mapAccumLM (replace_jump m) block_pos instrs + let instrs'' = concat instrs' + -- We might have introduced new labels, so split the instructions into basic blocks again if neccesary. + let (top, split_blocks, no_data) = foldr mkBlocks ([],[],[]) instrs'' + -- There should be no data in the instruction stream at this point + massert (null no_data) + + let final_blocks = BasicBlock lbl top : split_blocks + pure (pos', final_blocks) + + replace_jump :: LabelMap Int -> Int -> Instr -> UniqDSM (Int, [Instr]) replace_jump !m !pos instr = do case instr of ANN ann instr -> do - replace_jump m pos instr >>= \ - (idx,instr':|instrs') -> - pure (idx, ANN ann instr':|instrs') + replace_jump m pos instr >>= \case + (idx,instr':instrs') -> + pure (idx, ANN ann instr':instrs') + (idx,[]) -> pprPanic "replace_jump" (text "empty return list for " <+> ppr idx) BCOND cond t -> case target_in_range m t pos of - InRange -> pure (pos+long_bc_jump_size, NE.singleton instr) + InRange -> pure (pos+long_bc_jump_size,[instr]) NotInRange far_target -> do jmp_code <- genCondFarJump cond far_target - pure (pos+long_bc_jump_size, jmp_code) + pure (pos+long_bc_jump_size, fromOL jmp_code) CBZ op t -> long_zero_jump op t EQ CBNZ op t -> long_zero_jump op t NE instr - | isMetaInstr instr -> pure (pos, NE.singleton instr) - | otherwise -> pure (pos+1, NE.singleton instr) + | isMetaInstr instr -> pure (pos,[instr]) + | otherwise -> pure (pos+1, [instr]) where -- cmp_op: EQ = CBZ, NEQ = CBNZ long_zero_jump op t cmp_op = case target_in_range m t pos of - InRange -> pure (pos+long_bz_jump_size, NE.singleton instr) + InRange -> pure (pos+long_bz_jump_size,[instr]) NotInRange far_target -> do jmp_code <- genCondFarJump cmp_op far_target -- TODO: Fix zero reg so we can use it here - pure (pos + long_bz_jump_size, CMP op (OpImm (ImmInt 0)) NE.<| jmp_code) + pure (pos + long_bz_jump_size, CMP op (OpImm (ImmInt 0)) : fromOL jmp_code) target_in_range :: LabelMap Int -> Target -> Int -> BlockInRange ===================================== compiler/GHC/Core/Opt/SetLevels.hs ===================================== @@ -1,5 +1,7 @@ {-# LANGUAGE PatternSynonyms #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + {- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 @@ -118,16 +120,12 @@ import GHC.Builtin.Types import GHC.Builtin.Names ( runRWKey ) import GHC.Data.FastString -import GHC.Data.Pair ( Pair (..) ) import GHC.Utils.FV import GHC.Utils.Misc import GHC.Utils.Outputable import GHC.Utils.Panic -import Data.Foldable ( toList ) -import Data.Functor.Identity ( Identity (..) ) -import Data.List.NonEmpty ( NonEmpty (..) ) import Data.Maybe {- @@ -453,14 +451,14 @@ lvlCase env scrut_fvs scrut' case_bndr ty alts , ManyTy <- idMult case_bndr -- See Note [Floating linear case] = -- Always float the case if possible -- Unlike lets we don't insist that it escapes a value lambda - do { (env1, case_bndr' :| bs') <- cloneCaseBndrs env dest_lvl (case_bndr :| bs) + do { (env1, (case_bndr' : bs')) <- cloneCaseBndrs env dest_lvl (case_bndr : bs) ; let rhs_env = extendCaseBndrEnv env1 case_bndr scrut' ; body' <- lvlMFE rhs_env True body ; let alt' = Alt con (map (stayPut dest_lvl) bs') body' ; return (Case scrut' (TB case_bndr' (FloatMe dest_lvl)) ty' [alt']) } | otherwise -- Stays put - = do { let (alts_env1, Identity case_bndr') = substAndLvlBndrs NonRecursive env incd_lvl (Identity case_bndr) + = do { let (alts_env1, [case_bndr']) = substAndLvlBndrs NonRecursive env incd_lvl [case_bndr] alts_env = extendCaseBndrEnv alts_env1 case_bndr scrut' ; alts' <- mapM (lvl_alt alts_env) alts ; return (Case scrut' case_bndr' ty' alts') } @@ -651,7 +649,7 @@ lvlMFE env strict_ctxt ann_expr -- See Note [Test cheapness with exprOkForSpeculation] , BI_Box { bi_data_con = box_dc, bi_inst_con = boxing_expr , bi_boxed_type = box_ty } <- boxingDataCon expr_ty - , let Pair bx_bndr ubx_bndr = mkTemplateLocals (Pair box_ty expr_ty) + , let [bx_bndr, ubx_bndr] = mkTemplateLocals [box_ty, expr_ty] = do { expr1 <- lvlExpr rhs_env ann_expr ; let l1r = incMinorLvlFrom rhs_env float_rhs = mkLams abs_vars_w_lvls $ @@ -1229,7 +1227,7 @@ lvlBind env (AnnNonRec bndr rhs) = -- No float do { rhs' <- lvlRhs env NonRecursive is_bot_lam mb_join_arity rhs ; let bind_lvl = incMinorLvl (le_ctxt_lvl env) - (env', Identity bndr') = substAndLvlBndrs NonRecursive env bind_lvl (Identity bndr) + (env', [bndr']) = substAndLvlBndrs NonRecursive env bind_lvl [bndr] ; return (NonRec bndr' rhs', env') } -- Otherwise we are going to float @@ -1237,7 +1235,7 @@ lvlBind env (AnnNonRec bndr rhs) = do { -- No type abstraction; clone existing binder rhs' <- lvlFloatRhs [] dest_lvl env NonRecursive is_bot_lam NotJoinPoint rhs - ; (env', Identity bndr') <- cloneLetVars NonRecursive env dest_lvl (Identity bndr) + ; (env', [bndr']) <- cloneLetVars NonRecursive env dest_lvl [bndr] ; let bndr2 = annotateBotStr bndr' 0 mb_bot_str ; return (NonRec (TB bndr2 (FloatMe dest_lvl)) rhs', env') } @@ -1245,7 +1243,7 @@ lvlBind env (AnnNonRec bndr rhs) = do { -- Yes, type abstraction; create a new binder, extend substitution, etc rhs' <- lvlFloatRhs abs_vars dest_lvl env NonRecursive is_bot_lam NotJoinPoint rhs - ; (env', Identity bndr') <- newPolyBndrs dest_lvl env abs_vars (Identity bndr) + ; (env', [bndr']) <- newPolyBndrs dest_lvl env abs_vars [bndr] ; let bndr2 = annotateBotStr bndr' n_extra mb_bot_str ; return (NonRec (TB bndr2 (FloatMe dest_lvl)) rhs', env') } @@ -1303,13 +1301,13 @@ lvlBind env (AnnRec pairs) let (rhs_env, abs_vars_w_lvls) = lvlLamBndrs env dest_lvl abs_vars rhs_lvl = le_ctxt_lvl rhs_env - (rhs_env', Identity new_bndr) <- cloneLetVars Recursive rhs_env rhs_lvl (Identity bndr) + (rhs_env', [new_bndr]) <- cloneLetVars Recursive rhs_env rhs_lvl [bndr] let (lam_bndrs, rhs_body) = collectAnnBndrs rhs (body_env1, lam_bndrs1) = substBndrsSL NonRecursive rhs_env' lam_bndrs (body_env2, lam_bndrs2) = lvlLamBndrs body_env1 rhs_lvl lam_bndrs1 new_rhs_body <- lvlRhs body_env2 Recursive is_bot NotJoinPoint rhs_body - (poly_env, Identity poly_bndr) <- newPolyBndrs dest_lvl env abs_vars (Identity bndr) + (poly_env, [poly_bndr]) <- newPolyBndrs dest_lvl env abs_vars [bndr] return (Rec [(TB poly_bndr (FloatMe dest_lvl) , mkLams abs_vars_w_lvls $ mkLams lam_bndrs2 $ @@ -1481,26 +1479,24 @@ Use lvlExpr otherwise. A little subtle, and I got it wrong at least twice ************************************************************************ -} -substAndLvlBndrs :: Traversable f => RecFlag -> LevelEnv -> Level -> f InVar -> (LevelEnv, f LevelledBndr) +substAndLvlBndrs :: RecFlag -> LevelEnv -> Level -> [InVar] -> (LevelEnv, [LevelledBndr]) substAndLvlBndrs is_rec env lvl bndrs = lvlBndrs subst_env lvl subst_bndrs where (subst_env, subst_bndrs) = substBndrsSL is_rec env bndrs -{-# INLINE substAndLvlBndrs #-} -substBndrsSL :: Traversable f => RecFlag -> LevelEnv -> f InVar -> (LevelEnv, f OutVar) +substBndrsSL :: RecFlag -> LevelEnv -> [InVar] -> (LevelEnv, [OutVar]) -- So named only to avoid the name clash with GHC.Core.Subst.substBndrs substBndrsSL is_rec env@(LE { le_subst = subst, le_env = id_env }) bndrs = ( env { le_subst = subst' - , le_env = foldl' add_id id_env (toList bndrs `zip` toList bndrs') } + , le_env = foldl' add_id id_env (bndrs `zip` bndrs') } , bndrs') where (subst', bndrs') = case is_rec of NonRecursive -> substBndrs subst bndrs Recursive -> substRecBndrs subst bndrs -{-# INLINE substBndrsSL #-} -lvlLamBndrs :: Traversable f => LevelEnv -> Level -> f OutVar -> (LevelEnv, f LevelledBndr) +lvlLamBndrs :: LevelEnv -> Level -> [OutVar] -> (LevelEnv, [LevelledBndr]) -- Compute the levels for the binders of a lambda group lvlLamBndrs env lvl bndrs = lvlBndrs env new_lvl bndrs @@ -1514,18 +1510,17 @@ lvlLamBndrs env lvl bndrs -- true of a type variable -- there is no point in floating -- out of a big lambda. -- See Note [Computing one-shot info] in GHC.Types.Demand -{-# INLINE lvlLamBndrs #-} -lvlJoinBndrs :: Traversable f => LevelEnv -> Level -> RecFlag -> f OutVar - -> (LevelEnv, f LevelledBndr) -lvlJoinBndrs env lvl rec = lvlBndrs env new_lvl +lvlJoinBndrs :: LevelEnv -> Level -> RecFlag -> [OutVar] + -> (LevelEnv, [LevelledBndr]) +lvlJoinBndrs env lvl rec bndrs + = lvlBndrs env new_lvl bndrs where new_lvl | isRec rec = incMajorLvl lvl | otherwise = incMinorLvl lvl -- Non-recursive join points are one-shot; recursive ones are not -{-# INLINE lvlJoinBndrs #-} -lvlBndrs :: Traversable f => LevelEnv -> Level -> f CoreBndr -> (LevelEnv, f LevelledBndr) +lvlBndrs :: LevelEnv -> Level -> [CoreBndr] -> (LevelEnv, [LevelledBndr]) -- The binders returned are exactly the same as the ones passed, -- apart from applying the substitution, but they are now paired -- with a (StayPut level) @@ -1538,8 +1533,7 @@ lvlBndrs :: Traversable f => LevelEnv -> Level -> f CoreBndr -> (LevelEnv, f Lev lvlBndrs env@(LE { le_lvl_env = lvl_env }) new_lvl bndrs = ( env { le_ctxt_lvl = new_lvl , le_lvl_env = addLvls new_lvl lvl_env bndrs } - , fmap (stayPut new_lvl) bndrs) -{-# INLINE lvlBndrs #-} + , map (stayPut new_lvl) bndrs) stayPut :: Level -> OutVar -> LevelledBndr stayPut new_lvl bndr = TB bndr (StayPut new_lvl) @@ -1699,8 +1693,8 @@ initialEnv float_lams binds addLvl :: Level -> VarEnv Level -> OutVar -> VarEnv Level addLvl dest_lvl env v' = extendVarEnv env v' dest_lvl -addLvls :: Foldable f => Level -> VarEnv Level -> f OutVar -> VarEnv Level -addLvls = foldl' . addLvl +addLvls :: Level -> VarEnv Level -> [OutVar] -> VarEnv Level +addLvls dest_lvl env vs = foldl' (addLvl dest_lvl) env vs floatLams :: LevelEnv -> Maybe Int floatLams le = floatOutLambdas (le_switches le) @@ -1798,15 +1792,17 @@ type LvlM result = UniqSM result initLvl :: UniqSupply -> UniqSM a -> a initLvl = initUs_ -newPolyBndrs :: (MonadUnique m, Traversable t) => Level -> LevelEnv -> [OutVar] -> t InId -> m (LevelEnv, t OutId) +newPolyBndrs :: Level -> LevelEnv -> [OutVar] -> [InId] + -> LvlM (LevelEnv, [OutId]) -- The envt is extended to bind the new bndrs to dest_lvl, but -- the le_ctxt_lvl is unaffected newPolyBndrs dest_lvl env@(LE { le_lvl_env = lvl_env, le_subst = subst, le_env = id_env }) abs_vars bndrs = assert (all (not . isCoVar) bndrs) $ -- What would we add to the CoSubst in this case. No easy answer. - do { bndr_prs <- withUniquesM (\ uniq bndr -> (bndr, mk_poly_bndr bndr uniq)) bndrs - ; let new_bndrs = fmap snd bndr_prs + do { uniqs <- getUniquesM + ; let new_bndrs = zipWith mk_poly_bndr bndrs uniqs + bndr_prs = bndrs `zip` new_bndrs env' = env { le_lvl_env = addLvls dest_lvl lvl_env new_bndrs , le_subst = foldl' add_subst subst bndr_prs , le_env = foldl' add_id id_env bndr_prs } @@ -1832,10 +1828,6 @@ newPolyBndrs dest_lvl = new_bndr `asJoinId` join_arity + length abs_vars | otherwise = new_bndr -{-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> [InId] -> m (LevelEnv, [OutId]) #-} -{-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> Identity InId -> m (LevelEnv, Identity OutId) #-} -{-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> NonEmpty InId -> m (LevelEnv, NonEmpty OutId) #-} -{-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> Pair InId -> m (LevelEnv, Pair OutId) #-} newLvlVar :: LevelledExpr -- The RHS of the new binding -> JoinPointHood -- Its join arity, if it is a join point @@ -1859,7 +1851,7 @@ newLvlVar lvld_rhs join_arity_maybe is_mk_static = mkSysLocal (mkFastString "lvl") uniq ManyTy rhs_ty -- | Clone the binders bound by a single-alternative case. -cloneCaseBndrs :: Traversable t => LevelEnv -> Level -> t Var -> LvlM (LevelEnv, t Var) +cloneCaseBndrs :: LevelEnv -> Level -> [Var] -> LvlM (LevelEnv, [Var]) cloneCaseBndrs env@(LE { le_subst = subst, le_lvl_env = lvl_env, le_env = id_env }) new_lvl vs = do { (subst', vs') <- cloneBndrsM subst vs @@ -1868,11 +1860,12 @@ cloneCaseBndrs env@(LE { le_subst = subst, le_lvl_env = lvl_env, le_env = id_env -- See Note [Setting levels when floating single-alternative cases]. ; let env' = env { le_lvl_env = addLvls new_lvl lvl_env vs' , le_subst = subst' - , le_env = foldl' add_id id_env (toList vs `zip` toList vs') } + , le_env = foldl' add_id id_env (vs `zip` vs') } + ; return (env', vs') } -cloneLetVars - :: Traversable t => RecFlag -> LevelEnv -> Level -> t InVar -> LvlM (LevelEnv, t OutVar) +cloneLetVars :: RecFlag -> LevelEnv -> Level -> [InVar] + -> LvlM (LevelEnv, [OutVar]) -- See Note [Need for cloning during float-out] -- Works for Ids bound by let(rec) -- The dest_lvl is attributed to the binders in the new env, @@ -1880,12 +1873,12 @@ cloneLetVars cloneLetVars is_rec env@(LE { le_subst = subst, le_lvl_env = lvl_env, le_env = id_env }) dest_lvl vs - = do { let vs1 = fmap zap vs + = do { let vs1 = map zap vs ; (subst', vs2) <- case is_rec of NonRecursive -> cloneBndrsM subst vs1 Recursive -> cloneRecIdBndrsM subst vs1 - ; let prs = toList vs `zip` toList vs2 + ; let prs = vs `zip` vs2 env' = env { le_lvl_env = addLvls dest_lvl lvl_env vs2 , le_subst = subst' , le_env = foldl' add_id id_env prs } @@ -1901,10 +1894,6 @@ cloneLetVars is_rec -- See Note [Zapping JoinId when floating] zap_join | isTopLvl dest_lvl = zapJoinId | otherwise = id -{-# SPECIALIZE cloneLetVars :: RecFlag -> LevelEnv -> Level -> [InVar] -> LvlM (LevelEnv, [OutVar]) #-} -{-# SPECIALIZE cloneLetVars :: RecFlag -> LevelEnv -> Level -> Identity InVar -> LvlM (LevelEnv, Identity OutVar) #-} -{-# SPECIALIZE cloneLetVars :: RecFlag -> LevelEnv -> Level -> NonEmpty InVar -> LvlM (LevelEnv, NonEmpty OutVar) #-} -{-# SPECIALIZE cloneLetVars :: RecFlag -> LevelEnv -> Level -> Pair InVar -> LvlM (LevelEnv, Pair OutVar) #-} add_id :: IdEnv ([Var], LevelledExpr) -> (Var, Var) -> IdEnv ([Var], LevelledExpr) add_id id_env (v, v1) ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -2414,7 +2414,7 @@ prepareAlts :: OutExpr -> InId -> [InAlt] -> SimplM ([AltCon], [InAlt]) -- Note that case_bndr is an InId; see Note [Shadowing in prepareAlts] prepareAlts scrut case_bndr alts | Just (tc, tys) <- splitTyConApp_maybe (idType case_bndr) - = do { us <- getUniqueListM + = do { us <- getUniquesM ; let (idcs1, alts1) = filterAlts tc tys imposs_cons alts (yes2, alts2) = refineDefaultAlt us (idMult case_bndr) tc tys idcs1 alts1 -- The multiplicity on case_bndr's is the multiplicity of the @@ -2765,7 +2765,7 @@ mkCase2 mode scrut bndr alts_ty alts | not (isNullaryRepDataCon dc) = -- For non-nullary data cons we must invent some fake binders -- See Note [caseRules for dataToTag] in GHC.Core.Opt.ConstantFold - do { us <- getUniqueListM + do { us <- getUniquesM ; let (ex_tvs, arg_ids) = dataConRepInstPat us (idMult new_bndr) dc (tyConAppArgs (idType new_bndr)) ; return (ex_tvs ++ arg_ids) } ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -971,7 +971,7 @@ unbox_one_arg :: WwOpts unbox_one_arg opts arg_var DataConPatContext { dcpc_dc = dc, dcpc_tc_args = tc_args , dcpc_co = co, dcpc_args = ds } - = do { pat_bndrs_uniqs <- getUniqueListM + = do { pat_bndrs_uniqs <- getUniquesM ; let ex_name_fss = map getOccFS $ dataConExTyCoVars dc -- Create new arguments we get when unboxing dc @@ -1563,7 +1563,7 @@ unbox_one_result opts res_bndr -- ( case i of I# a -> ) | -- ( case j of I# b -> ) | ( (<i>, <j>) ) -- ( <hole> ) | - pat_bndrs_uniqs <- getUniqueListM + pat_bndrs_uniqs <- getUniquesM let (_exs, arg_ids) = dataConRepFSInstPat (repeat ww_prefix) pat_bndrs_uniqs cprCaseBndrMult dc tc_args massert (null _exs) -- Should have been caught by canUnboxResult ===================================== compiler/GHC/Core/Subst.hs ===================================== @@ -415,23 +415,20 @@ cloneIdBndr subst us old_id -- | Applies 'cloneIdBndr' to a number of 'Id's, accumulating a final -- substitution from left to right -- Discards non-Stable unfoldings -cloneIdBndrs :: Traversable t => Subst -> UniqSupply -> t Id -> (Subst, t Id) +cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) cloneIdBndrs subst us ids - = mapAccumL (clone_id subst) subst (withUniques (flip (,)) us ids) -{-# SPECIALIZE cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) #-} + = mapAccumL (clone_id subst) subst (ids `zip` uniqsFromSupply us) -cloneBndrs :: Traversable t => Subst -> UniqSupply -> t Var -> (Subst, t Var) +cloneBndrs :: Subst -> UniqSupply -> [Var] -> (Subst, [Var]) -- Works for all kinds of variables (typically case binders) -- not just Ids cloneBndrs subst us vs - = mapAccumL (\subst (v, u) -> cloneBndr subst u v) subst (withUniques (flip (,)) us vs) -{-# SPECIALIZE cloneBndrs :: Subst -> UniqSupply -> [Var] -> (Subst, [Var]) #-} + = mapAccumL (\subst (v, u) -> cloneBndr subst u v) subst (vs `zip` uniqsFromSupply us) -cloneBndrsM :: (Traversable t, MonadUnique m) => Subst -> t Var -> m (Subst, t Var) +cloneBndrsM :: MonadUnique m => Subst -> [Var] -> m (Subst, [Var]) -- Works for all kinds of variables (typically case binders) -- not just Ids cloneBndrsM subst vs = cloneBndrs subst `flip` vs <$> getUniqueSupplyM -{-# INLINE cloneBndrsM #-} cloneBndr :: Subst -> Unique -> Var -> (Subst, Var) cloneBndr subst uniq v @@ -439,16 +436,14 @@ cloneBndr subst uniq v | otherwise = clone_id subst subst (v,uniq) -- Works for coercion variables too -- | Clone a mutually recursive group of 'Id's -cloneRecIdBndrs :: Traversable t => Subst -> UniqSupply -> t Id -> (Subst, t Id) +cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) cloneRecIdBndrs subst us ids = - let x@(subst', _) = mapAccumL (clone_id subst') subst (withUniques (flip (,)) us ids) + let x@(subst', _) = mapAccumL (clone_id subst') subst (ids `zip` uniqsFromSupply us) in x -{-# SPECIALIZE cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) #-} -- | Clone a mutually recursive group of 'Id's -cloneRecIdBndrsM :: (Traversable t, MonadUnique m) => Subst -> t Id -> m (Subst, t Id) +cloneRecIdBndrsM :: MonadUnique m => Subst -> [Id] -> m (Subst, [Id]) cloneRecIdBndrsM subst ids = cloneRecIdBndrs subst `flip` ids <$> getUniqueSupplyM -{-# INLINE cloneRecIdBndrsM #-} -- Just like substIdBndr, except that it always makes a new unique -- It is given the unique to use ===================================== compiler/GHC/Iface/Env.hs ===================================== @@ -262,9 +262,11 @@ newIfaceName occ = do { uniq <- newUnique ; return $! mkInternalName uniq occ noSrcSpan } -newIfaceNames :: Traversable t => t OccName -> IfL (t Name) -newIfaceNames = withUniquesM (\ uniq occ -> mkInternalName uniq occ noSrcSpan) -{-# INLINE newIfaceNames #-} +newIfaceNames :: [OccName] -> IfL [Name] +newIfaceNames occs + = do { uniqs <- getUniquesM + ; return [ mkInternalName uniq occ noSrcSpan + | (occ,uniq) <- occs `zip` uniqs] } trace_if :: Logger -> SDoc -> IO () {-# INLINE trace_if #-} -- see Note [INLINE conditional tracing utilities] ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -1722,7 +1722,7 @@ tcIfaceAlt scrut mult (tycon, inst_tys) (IfaceAlt (IfaceDataAlt data_occ) arg_st tcIfaceDataAlt :: Mult -> DataCon -> [Type] -> [IfLclName] -> IfaceExpr -> IfL CoreAlt tcIfaceDataAlt mult con inst_tys arg_strs rhs - = do { uniqs <- getUniqueListM + = do { uniqs <- getUniquesM ; let (ex_tvs, arg_ids) = dataConRepFSInstPat (map ifLclNameFS arg_strs) uniqs mult con inst_tys ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -629,7 +629,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do newTyVars :: UniqSupply -> [TcTyVar] -> Subst -- Similarly, clone the type variables mentioned in the types -- we have here, *and* make them all RuntimeUnk tyvars - newTyVars us tvs = foldl' new_tv emptySubst (tvs `zip` uniqListFromSupply us) + newTyVars us tvs = foldl' new_tv emptySubst (tvs `zip` uniqsFromSupply us) new_tv subst (tv,uniq) = extendTCvSubstWithClone subst tv new_tv where new_tv = mkRuntimeUnkTyVar (setNameUnique (tyVarName tv) uniq) ===================================== compiler/GHC/Stg/Unarise.hs ===================================== @@ -731,8 +731,7 @@ unariseAlts rho (MultiValAlt _) bndr [GenStgAlt{ alt_con = DEFAULT unariseAlts rho (MultiValAlt _) bndr alts | isUnboxedSumBndr bndr - = do (rho_sum_bndrs, scrt_bndrs) <- unariseConArgBinder rho bndr - let tag_bndr:|real_bndrs = expectNonEmpty scrt_bndrs + = do (rho_sum_bndrs, scrt_bndrs@(tag_bndr : real_bndrs)) <- unariseConArgBinder rho bndr alts' <- unariseSumAlts rho_sum_bndrs (map StgVarArg real_bndrs) alts let inner_case = StgCase (StgApp tag_bndr []) tag_bndr tagAltTy alts' return [GenStgAlt{ alt_con = DataAlt (tupleDataCon Unboxed (length scrt_bndrs)) @@ -850,7 +849,7 @@ mapSumIdBinders alt_bndr args rhs rho0 mkCastInput :: (Id,PrimRep,UniqSupply) -> ([(PrimOp,Type,Unique)],Id,Id) mkCastInput (id,rep,bndr_us) = let (ops,types) = unzip $ getCasts (typePrimRepU $ idType id) rep - cst_opts = zip3 ops types $ uniqListFromSupply bndr_us + cst_opts = zip3 ops types $ uniqsFromSupply bndr_us out_id = case cst_opts of [] -> id _ -> let (_,ty,uq) = last cst_opts @@ -961,7 +960,7 @@ mkUbxSum dc ty_args args0 us , (ops,types) <- unzip $ getCasts (stgArgRepU arg) $ slotPrimRep slot_ty , not . null $ ops = let (us1,us2) = splitUniqSupply us - cast_uqs = uniqListFromSupply us1 + cast_uqs = uniqsFromSupply us1 cast_opts = zip3 ops types cast_uqs (_op,out_ty,out_uq) = last cast_opts casts = castArgRename cast_opts arg :: StgExpr -> StgExpr ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -3939,7 +3939,9 @@ splitTyConKind skol_info in_scope avoid_occs kind name = mkInternalName uniq occ loc tv = mkTcTyVar name arg' details subst' = extendSubstInScope subst tv - Inf uniq uniqs' = uniqs + (uniq,uniqs') = case uniqs of + uniq:uniqs' -> (uniq,uniqs') + _ -> panic "impossible" Inf occ occs' = occs Just (Named (Bndr tv vis), kind') ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -745,9 +745,11 @@ newSysLocalId fs w ty = do { u <- newUnique ; return (mkSysLocal fs u w ty) } -newSysLocalIds :: (Traversable t) => FastString -> t (Scaled TcType) -> TcRnIf gbl lcl (t TcId) -newSysLocalIds fs = withUniquesM (\ u (Scaled w t) -> mkSysLocal fs u w t) -{-# INLINE newSysLocalIds #-} +newSysLocalIds :: FastString -> [Scaled TcType] -> TcRnIf gbl lcl [TcId] +newSysLocalIds fs tys + = do { us <- getUniquesM + ; let mkId' n (Scaled w t) = mkSysLocal fs n w t + ; return (zipWith mkId' us tys) } instance MonadUnique (IOEnv (Env gbl lcl)) where getUniqueM = newUnique ===================================== compiler/GHC/Types/Id.hs ===================================== @@ -172,8 +172,6 @@ import GHC.Utils.Misc import GHC.Utils.Outputable import GHC.Utils.Panic -import Control.Monad.Trans.State (evalState, state) - -- infixl so you can say (id `set` a `set` b) infixl 1 `setIdUnfolding`, `setIdArity`, @@ -400,14 +398,12 @@ mkScaledTemplateLocal i (Scaled w ty) = mkSysLocalOrCoVar (fsLit "v") (mkBuiltin -- and "~" and "~~" have coercion "superclasses". -- | Create a template local for a series of types -mkTemplateLocals :: Traversable f => f Type -> f Id +mkTemplateLocals :: [Type] -> [Id] mkTemplateLocals = mkTemplateLocalsNum 1 -{-# SPECIALIZE mkTemplateLocals :: [Type] -> [Id] #-} -- | Create a template local for a series of type, but start from a specified template local -mkTemplateLocalsNum :: Traversable f => Int -> f Type -> f Id -mkTemplateLocalsNum n = flip evalState n . traverse (state . \ ty n -> (mkTemplateLocal n ty, succ n)) -{-# SPECIALIZE mkTemplateLocalsNum :: Int -> [Type] -> [Id] #-} +mkTemplateLocalsNum :: Int -> [Type] -> [Id] +mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys {- Note [Exported LocalIds] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Types/Unique/Supply.hs ===================================== @@ -14,14 +14,12 @@ module GHC.Types.Unique.Supply ( UniqSupply, -- Abstractly -- ** Operations on supplies - uniqFromSupply, uniqsFromSupply, uniqListFromSupply, -- basic ops + uniqFromSupply, uniqsFromSupply, -- basic ops takeUniqFromSupply, uniqFromTag, mkSplitUniqSupply, splitUniqSupply, listSplitUniqSupply, - withUniques, withUniquesM, - -- * Unique supply monad and its abstraction UniqSM, MonadUnique(..), @@ -29,26 +27,23 @@ module GHC.Types.Unique.Supply ( initUs, initUs_, -- * Set supply strategy - initUniqSupply, + initUniqSupply ) where import GHC.Prelude -import GHC.Data.List.Infinite import GHC.Types.Unique +import GHC.Utils.Panic.Plain import GHC.IO import GHC.Utils.Monad +import Control.Monad import Data.Word import GHC.Exts( Ptr(..), noDuplicate#, oneShot ) import Foreign.Storable import GHC.Utils.Monad.State.Strict as Strict -#if defined(DEBUG) -import GHC.Utils.Panic.Plain -#endif - #include "MachDeps.h" #if WORD_SIZE_IN_BITS != 64 @@ -297,9 +292,7 @@ listSplitUniqSupply :: UniqSupply -> [UniqSupply] -- ^ Create an infinite list of 'UniqSupply' from a single one uniqFromSupply :: UniqSupply -> Unique -- ^ Obtain the 'Unique' from this particular 'UniqSupply' -uniqsFromSupply :: UniqSupply -> Infinite Unique --- ^ Obtain an infinite list of 'Unique' that can be generated by constant splitting of the supply -uniqListFromSupply :: UniqSupply -> [Unique] +uniqsFromSupply :: UniqSupply -> [Unique] -- Infinite -- ^ Obtain an infinite list of 'Unique' that can be generated by constant splitting of the supply takeUniqFromSupply :: UniqSupply -> (Unique, UniqSupply) -- ^ Obtain the 'Unique' from this particular 'UniqSupply', and a new supply @@ -308,24 +301,11 @@ splitUniqSupply (MkSplitUniqSupply _ s1 s2) = (s1, s2) listSplitUniqSupply (MkSplitUniqSupply _ s1 s2) = s1 : listSplitUniqSupply s2 uniqFromSupply (MkSplitUniqSupply n _ _) = mkUniqueGrimily n -uniqsFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily n `Inf` uniqsFromSupply s2 -uniqListFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily n : uniqListFromSupply s2 +uniqsFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily n : uniqsFromSupply s2 takeUniqFromSupply (MkSplitUniqSupply n s1 _) = (mkUniqueGrimily n, s1) {-# INLINE splitUniqSupply #-} -withUniques :: Traversable t => (Unique -> a -> b) -> UniqSupply -> t a -> t b -withUniques f us = initUs_ us . traverse (\ a -> flip f a <$> getUniqueUs) -{-# INLINE withUniques #-} - -withUniquesM :: (MonadUnique m, Traversable t) => (Unique -> a -> b) -> t a -> m (t b) -withUniquesM f = \ as -> ($ as) <$> withUniquesM' f -{-# INLINE withUniquesM #-} - -withUniquesM' :: (MonadUnique m, Traversable t) => (Unique -> a -> b) -> m (t a -> t b) -withUniquesM' f = withUniques f <$> getUniqueSupplyM -{-# INLINE withUniquesM' #-} - {- ************************************************************************ * * @@ -350,6 +330,10 @@ mkUniqSM :: (UniqSupply -> UniqResult a) -> UniqSM a mkUniqSM f = USM (oneShot f) {-# INLINE mkUniqSM #-} +-- TODO: try to get rid of this instance +instance MonadFail UniqSM where + fail = panic + -- | Run the 'UniqSM' action, returning the final 'UniqSupply' initUs :: UniqSupply -> UniqSM a -> (a, UniqSupply) initUs init_us m = case unUSM m init_us of { UniqResult r us -> (r, us) } @@ -374,17 +358,14 @@ class Monad m => MonadUnique m where -- | Get a new unique identifier getUniqueM :: m Unique -- | Get an infinite list of new unique identifiers - getUniquesM :: m (Infinite Unique) - -- | Get an infinite list of new unique identifiers - getUniqueListM :: m [Unique] + getUniquesM :: m [Unique] -- This default definition of getUniqueM, while correct, is not as -- efficient as it could be since it needlessly generates and throws away -- an extra Unique. For your instances consider providing an explicit -- definition for 'getUniqueM' which uses 'takeUniqFromSupply' directly. - getUniqueM = fmap uniqFromSupply getUniqueSupplyM - getUniquesM = fmap uniqsFromSupply getUniqueSupplyM - getUniqueListM = fmap uniqListFromSupply getUniqueSupplyM + getUniqueM = liftM uniqFromSupply getUniqueSupplyM + getUniquesM = liftM uniqsFromSupply getUniqueSupplyM instance MonadUnique UniqSM where getUniqueSupplyM = getUs @@ -395,6 +376,6 @@ getUniqueUs :: UniqSM Unique getUniqueUs = mkUniqSM (\us0 -> case takeUniqFromSupply us0 of (u,us1) -> UniqResult u us1) -getUniquesUs :: UniqSM (Infinite Unique) +getUniquesUs :: UniqSM [Unique] getUniquesUs = mkUniqSM (\us0 -> case splitUniqSupply us0 of (us1,us2) -> UniqResult (uniqsFromSupply us1) us2) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e90e2dacb24ef486cc2e3a270a229e847f87eed3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e90e2dacb24ef486cc2e3a270a229e847f87eed3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/a2ddccb0/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 11:57:41 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 07 Mar 2025 06:57:41 -0500 Subject: [Git][ghc/ghc][wip/T24359] new plan from March 7 Message-ID: <67cadf35b75d_15c30128e064161f3@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 9a61f685 by sheaf at 2025-03-07T12:57:26+01:00 new plan from March 7 - - - - - 9 changed files: - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Types/Evidence.hs - testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs Changes: ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -39,7 +39,7 @@ import GHC.Tc.Gen.HsType import GHC.Tc.Solver( reportUnsolvedEqualities, pushLevelAndSolveEqualitiesX , emitResidualConstraints ) import GHC.Tc.Solver.Solve( solveWanteds ) -import GHC.Tc.Solver.Monad( runTcS, runTcSWithEvBinds ) +import GHC.Tc.Solver.Monad( runTcS, runTcSFullySolve ) import GHC.Tc.Validity ( checkValidType ) import GHC.Tc.Utils.Monad @@ -1029,40 +1029,26 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) <- tcRuleBndrs skol_info rule_bndrs $ tcInferRho spec_e - -- (2) Clone these Wanteds, solve them, and zonk the original - -- Wanteds, in order to benefit from any unifications. - - ; throwaway_ev_binds_var <- newTcEvBinds - ; spec_e_wanted_clone <- cloneWC spec_e_wanted - ; _ <- setTcLevel rhs_tclvl $ - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds spec_e_wanted_clone + -- (2) Solve the resulting wanteds in TcSFullySolve mode. + ; ev_binds_var <- newTcEvBinds + ; spec_e_wanted <- setTcLevel rhs_tclvl $ + runTcSFullySolve ev_binds_var $ + solveWanteds spec_e_wanted ; spec_e_wanted <- liftZonkM $ zonkWC spec_e_wanted -- (3) Compute which constraints to quantify over. - -- (a) Compute quantification candidates - ; ev_binds_var <- newTcEvBinds ; (quant_cands, residual_wc) <- getRuleQuantCts spec_e_wanted - -- (b) Compute fully soluble constraints - -- See Note [Fully solving constraints for specialisation] - ; traceTc "tcSpecPrag SpecSigE: computing fully soluble Wanteds {" empty - ; fully_soluble_evids <- - setTcLevel rhs_tclvl $ - mkVarSet <$> - mapMaybeM fullySolveCt_maybe (bagToList quant_cands) - ; let (fully_soluble_cts, quant_cts) = partitionBag ((`elemVarSet` fully_soluble_evids) . ctEvId) quant_cands - -- (c) Compute constraints to quantify over using 'mkMinimalBySCs' - qevs = map ctEvId (bagToList quant_cts) - ; traceTc "tcSpecPrag SpecSigE: computed fully soluble Wanteds }" (ppr fully_soluble_cts) - -- (4) Emit the residual constraints (that we are not quantifying over) ; let tv_bndrs = filter isTyVar rule_bndrs' + qevs = map ctEvId (bagToList quant_cands) ; emitResidualConstraints rhs_tclvl skol_info_anon ev_binds_var emptyVarSet tv_bndrs qevs - (residual_wc `addSimples` fully_soluble_cts) + residual_wc ; let lhs_call = mkLHsWrap (WpLet (TcEvBinds ev_binds_var)) tc_spec_e + ; ev_binds <- getTcEvBindsMap ev_binds_var + ; traceTc "tcSpecPrag SpecSigE }" $ vcat [ text "nm:" <+> ppr nm , text "rule_bndrs':" <+> ppr rule_bndrs' @@ -1070,9 +1056,11 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) , text "spec_e:" <+> ppr tc_spec_e , text "inl:" <+> ppr inl , text "spec_e_wanted:" <+> ppr spec_e_wanted - , text "quant_cts:" <+> ppr quant_cts + , text "quant_cands:" <+> ppr quant_cands , text "residual_wc:" <+> ppr residual_wc - , text "fully_soluble_wanteds:" <+> ppr fully_soluble_cts + , text (replicate 80 '-') + , text "ev_binds_var:" <+> ppr ev_binds_var + , text "ev_binds:" <+> ppr ev_binds ] -- (5) Store the results in a SpecPragE record, which will be @@ -1087,24 +1075,6 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) tcSpecPrag _ prag = pprPanic "tcSpecPrag" (ppr prag) --- | Try to fully solve a constraint. -fullySolveCt_maybe :: Ct -> TcM (Maybe EvId) -fullySolveCt_maybe ct = do - throwaway_ev_binds_var <- newTcEvBinds - res_wc <- - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds $ emptyWC { wc_simple = unitBag ct } - -- NB: don't use 'solveSimpleWanteds', as this will not - -- fully solve quantified constraints. - traceTc "fullySolveCt_maybe" $ - vcat [ text "ct:" <+> ppr ct - , text "res_wc:" <+> ppr res_wc - ] - return $ - if isSolvedWC res_wc - then Just $ ctEvId ct - else Nothing - -------------- tcSpecWrapper :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper -- A simpler variant of tcSubType, used for SPECIALISE pragmas ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -61,6 +61,7 @@ import Data.Void( Void ) import Control.Monad.Trans.Maybe( MaybeT, runMaybeT ) import Control.Monad.Trans.Class( lift ) import Control.Monad +import {-# SOURCE #-} GHC.Tc.Solver.Solve (solveCompletelyIfRequired) {- ********************************************************************* @@ -101,26 +102,6 @@ solveDict dict_ct@(DictCt { di_ev = ev, di_cls = cls, di_tys = tys }) ; simpleStage (updInertDicts dict_ct) ; stopWithStage (dictCtEvidence dict_ct) "Kept inert DictCt" } -updInertDicts :: DictCt -> TcS () -updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys }) - = do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls <+> ppr tys) - - ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys - -> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters] - -- Update /both/ inert_cans /and/ inert_solved_dicts. - updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) -> - inerts { inert_cans = updDicts (filterDicts (not_ip_for str_ty)) ics - , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved } - | otherwise - -> return () - - -- Add the new constraint to the inert set - ; updInertCans (updDicts (addDict dict_ct)) } - where - not_ip_for :: Type -> DictCt -> Bool - not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys }) - = not (mentionsIP str_ty cls tys) - canDictCt :: CtEvidence -> Class -> [Type] -> SolverStage DictCt -- Once-only processing of Dict constraints: -- * expand superclasses @@ -868,7 +849,8 @@ shortCutSolver dflags ev_w ev_i tryInstances :: DictCt -> SolverStage () tryInstances dict_ct = Stage $ do { inerts <- getInertSet - ; try_instances inerts dict_ct } + ; solveCompletelyIfRequired (continueWith ()) $ + try_instances inerts dict_ct } try_instances :: InertSet -> DictCt -> TcS (StopOrContinue ()) -- Try to use type-class instance declarations to simplify the constraint ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeApplications #-} @@ -16,6 +17,7 @@ module GHC.Tc.Solver.InertSet ( InertSet(..), InertCans(..), emptyInert, + partitionInerts, andInertSet, noGivenNewtypeReprEqs, updGivenEqs, prohibitedSuperClassSolve, @@ -54,7 +56,7 @@ import GHC.Tc.Types.Constraint import GHC.Tc.Types.Origin import GHC.Tc.Types.CtLoc( CtLoc, ctLocOrigin, ctLocSpan, ctLocLevel ) import GHC.Tc.Solver.Types -import GHC.Tc.Utils.TcType +import GHC.Tc.Utils.TcType hiding () -- Make sure maxTcLevel is imported import GHC.Types.Var import GHC.Types.Var.Env @@ -73,10 +75,11 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Data.Bag +import Control.Monad ( forM_ ) +import Data.List ( partition ) import Data.List.NonEmpty ( NonEmpty(..), (<|) ) -import Data.Function ( on ) +import Data.Function ( on ) -import Control.Monad ( forM_ ) {- ************************************************************************ @@ -286,9 +289,9 @@ extendWorkListCts :: Cts -> WorkList -> WorkList extendWorkListCts cts wl = foldr extendWorkListCt wl cts isEmptyWorkList :: WorkList -> Bool -isEmptyWorkList (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X +isEmptyWorkList (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X, wl_rw_eqs = rw_eqs , wl_rest = rest, wl_implics = implics }) - = null eqs_N && null eqs_X && null rest && isEmptyBag implics + = null eqs_N && null eqs_X && null rw_eqs && null rest && isEmptyBag implics emptyWorkList :: WorkList emptyWorkList = WL { wl_eqs_N = [], wl_eqs_X = [] @@ -390,7 +393,6 @@ emptyInert , inert_famapp_cache = emptyFunEqs , inert_solved_dicts = emptyDictMap } - {- Note [Solved dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When we apply a top-level instance declaration, we add the "solved" @@ -2214,3 +2216,115 @@ Wrong! The level-check ensures that the inner implicit parameter wins. (Actually I think that the order in which the work-list is processed means that this chain of events won't happen, but that's very fragile.) -} + +-- | Partition the inert set according to a predicate. +partitionInerts :: (Ct -> Bool) -> InertSet -> (InertSet, InertSet) +partitionInerts pred is@(IS { inert_cans = cans }) + = (is { inert_cans = givens_cans }, is { inert_cans = wanteds_cans }) + where + -- Helper functions to convert between Ct and specific constraint types + eqPred :: EqCt -> Bool + eqPred eq = pred (CEqCan eq) + + dictPred :: DictCt -> Bool + dictPred dict = pred (CDictCan dict) + + irredPred :: IrredCt -> Bool + irredPred irred = pred (CIrredCan irred) + + qciPred :: QCInst -> Bool + qciPred qci = pred (CQuantCan qci) + + -- Partition the inert constraints + (eq_givens_list, eq_wanteds) = partitionInertEqs eqPred (inert_eqs cans) + (funeq_givens_list, funeq_wanteds) = partitionFunEqs eqPred (inert_funeqs cans) + (dict_givens_bag, dict_wanteds) = partitionDicts dictPred (inert_dicts cans) + (safehask_givens_bag, safehask_wanteds) = partitionDicts dictPred (inert_safehask cans) + (insts_givens, insts_wanteds) = partition qciPred (inert_insts cans) + (irreds_givens, irreds_wanteds) = partitionBag irredPred (inert_irreds cans) + + -- Convert lists to the appropriate container types + eq_givens = foldr addInertEqs emptyTyEqs eq_givens_list + funeq_givens = foldr addFunEqs emptyFunEqs funeq_givens_list + + givens_cans = emptyInertCans { + inert_eqs = eq_givens, + inert_funeqs = funeq_givens, + inert_dicts = dictsToDictMap dict_givens_bag, + inert_safehask = dictsToDictMap safehask_givens_bag, + inert_insts = insts_givens, + inert_irreds = irreds_givens, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + + wanteds_cans = emptyInertCans { + inert_eqs = eq_wanteds, + inert_funeqs = funeq_wanteds, + inert_dicts = dict_wanteds, + inert_safehask = safehask_wanteds, + inert_insts = insts_wanteds, + inert_irreds = irreds_wanteds, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + +-- | Convert a Bag of DictCts to a DictMap +dictsToDictMap :: Bag DictCt -> DictMap DictCt +dictsToDictMap = foldr addDict emptyDictMap . bagToList + +-- | Union two DictMaps +unionDictMap :: DictMap DictCt -> DictMap DictCt -> DictMap DictCt +unionDictMap dm1 dm2 = foldrTcAppMap addDict dm1 dm2 + +-- | Union two InertEqs +unionTyEqs :: InertEqs -> InertEqs -> InertEqs +unionTyEqs eqs1 eqs2 = foldrTyEqs addInertEqs eqs1 eqs2 + +-- | Union two InertFunEqs +unionFunEqs :: InertFunEqs -> InertFunEqs -> InertFunEqs +unionFunEqs feqs1 feqs2 = foldrFunEqs addFunEqs feqs1 feqs2 + +-- | Union two FunEqMap Reductions +unionFunEqMap :: FunEqMap Reduction -> FunEqMap Reduction -> FunEqMap Reduction +unionFunEqMap m1 m2 = foldTcAppMap (\r acc -> + let ty = reductionReducedType r + in case tcSplitTyConApp_maybe ty of + Just (tc, args) -> insertTcApp acc tc args r + Nothing -> acc) + m1 m2 + +-- | Fold over a TcAppMap with a function +foldrTcAppMap :: (a -> b -> b) -> TcAppMap a -> b -> b +foldrTcAppMap k m z = foldTcAppMap (\x acc -> k x acc) m z + +-- | Fold over FunEqs with a function +foldrFunEqs :: (EqCt -> b -> b) -> InertFunEqs -> b -> b +foldrFunEqs k feqs z = foldFunEqs (\eq acc -> k eq acc) feqs z + +-- | Fold over TyEqs with a function +foldrTyEqs :: (EqCt -> b -> b) -> InertEqs -> b -> b +foldrTyEqs k eqs z = foldTyEqs (\eq acc -> k eq acc) eqs z + +-- | Combine two 'InertSet's in a monoidal manner. +andInertSet :: InertSet -> InertSet -> InertSet +andInertSet is1 is2 + = IS { inert_cans = combinedCans, + inert_cycle_breakers = inert_cycle_breakers is1, -- Keep the first one's cycle breakers + inert_famapp_cache = unionFunEqMap (inert_famapp_cache is1) (inert_famapp_cache is2), + inert_solved_dicts = unionDictMap (inert_solved_dicts is1) (inert_solved_dicts is2) + } + where + cans1 = inert_cans is1 + cans2 = inert_cans is2 + + combinedCans = IC { + inert_eqs = unionTyEqs (inert_eqs cans1) (inert_eqs cans2), + inert_funeqs = unionFunEqs (inert_funeqs cans1) (inert_funeqs cans2), + inert_dicts = unionDictMap (inert_dicts cans1) (inert_dicts cans2), + inert_safehask = unionDictMap (inert_safehask cans1) (inert_safehask cans2), + inert_insts = inert_insts cans1 ++ inert_insts cans2, + inert_irreds = unionBags (inert_irreds cans1) (inert_irreds cans2), + inert_given_eq_lvl = maxTcLevel (inert_given_eq_lvl cans1) (inert_given_eq_lvl cans2), + inert_given_eqs = inert_given_eqs cans1 || inert_given_eqs cans2 + } ===================================== compiler/GHC/Tc/Solver/Irred.hs ===================================== @@ -39,10 +39,6 @@ solveIrred irred ; simpleStage (updInertIrreds irred) ; stopWithStage (irredCtEvidence irred) "Kept inert IrredCt" } -updInertIrreds :: IrredCt -> TcS () -updInertIrreds irred - = do { tc_lvl <- getTcLevel - ; updInertCans $ addIrredToCans tc_lvl irred } {- ********************************************************************* * * ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -14,7 +14,9 @@ module GHC.Tc.Solver.Monad ( -- The TcS monad - TcS, runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + TcS(..), TcSEnv(..), TcSMode(..), + runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + runTcSFullySolve, failTcS, warnTcS, addErrTcS, wrapTcS, ctLocWarnTcS, runTcSEqualities, nestTcS, nestImplicTcS, setEvBindsTcS, @@ -71,9 +73,10 @@ module GHC.Tc.Solver.Monad ( getInertEqs, getInertCans, getInertGivens, getInertInsols, getInnermostGivenEqLevel, getInertSet, setInertSet, - getUnsolvedInerts, + getUnsolvedInerts, getUnsolvedInerts2, removeInertCts, getPendingGivenScs, insertFunEq, addInertForAll, + updInertDicts, updInertIrreds, emitWorkNC, emitWork, lookupInertDict, @@ -202,13 +205,14 @@ import GHC.Exts (oneShot) import Control.Monad import Data.Foldable hiding ( foldr1 ) import Data.IORef -import Data.List ( mapAccumL ) +import Data.List ( mapAccumL, unfoldr ) import Data.List.NonEmpty ( nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) import qualified Data.Semigroup as S import GHC.Types.SrcLoc import GHC.Rename.Env +--import GHC.Tc.Solver.Solve (solveWanteds) #if defined(DEBUG) import GHC.Types.Unique.Set (nonDetEltsUniqSet) @@ -369,6 +373,31 @@ duplicates, is explained in Note [Use only the best matching quantified constrai in GHC.Tc.Solver.Dict. -} +updInertDicts :: DictCt -> TcS () +updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys }) + = do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls <+> ppr tys) + + ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys + -> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters] + -- Update /both/ inert_cans /and/ inert_solved_dicts. + updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) -> + inerts { inert_cans = updDicts (filterDicts (not_ip_for str_ty)) ics + , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved } + | otherwise + -> return () + + -- Add the new constraint to the inert set + ; updInertCans (updDicts (addDict dict_ct)) } + where + not_ip_for :: Type -> DictCt -> Bool + not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys }) + = not (mentionsIP str_ty cls tys) + +updInertIrreds :: IrredCt -> TcS () +updInertIrreds irred + = do { tc_lvl <- getTcLevel + ; updInertCans $ addIrredToCans tc_lvl irred } + {- ********************************************************************* * * Kicking out @@ -579,7 +608,7 @@ getInertGivens :: TcS [Ct] getInertGivens = do { inerts <- getInertCans ; let all_cts = foldIrreds ((:) . CIrredCan) (inert_irreds inerts) - $ foldDicts ((:) . CDictCan) (inert_dicts inerts) + $ foldDicts ((:) . CDictCan) (inert_dicts inerts) $ foldFunEqs ((:) . CEqCan) (inert_funeqs inerts) $ foldTyEqs ((:) . CEqCan) (inert_eqs inerts) $ [] @@ -679,6 +708,45 @@ getUnsolvedInerts where ct = mk_ct thing +getUnsolvedInerts2 :: TcS ( Bag Implication, Cts ) +getUnsolvedInerts2 + = do { IC { inert_eqs = tv_eqs + , inert_funeqs = fun_eqs + , inert_irreds = irreds + , inert_dicts = idicts + } <- getInertCans + + ; let unsolved_tv_eqs = foldTyEqs (add_if_unsolved CEqCan) tv_eqs emptyCts + unsolved_fun_eqs = foldFunEqs (add_if_unsolved CEqCan) fun_eqs emptyCts + unsolved_irreds = foldr (add_if_unsolved CIrredCan) emptyCts irreds + unsolved_dicts = foldDicts (add_if_unsolved CDictCan) idicts emptyCts + + ; wl_var <- getTcSWorkListRef + ; wl_curr <- readTcRef wl_var + ; implics <- getWorkListImplics + ; let wl_simpls = listToBag $ unfoldr selectWorkItem wl_curr + + ; traceTcS "getUnsolvedInerts" $ + vcat [ text " tv eqs =" <+> ppr unsolved_tv_eqs + , text "fun eqs =" <+> ppr unsolved_fun_eqs + , text "dicts =" <+> ppr unsolved_dicts + , text "irreds =" <+> ppr unsolved_irreds + , text "implics =" <+> ppr implics ] + + ; return ( implics, unsolved_tv_eqs `unionBags` + unsolved_fun_eqs `unionBags` + unsolved_irreds `unionBags` + unsolved_dicts `unionBags` + wl_simpls) } + where + add_if_unsolved :: (a -> Ct) -> a -> Cts -> Cts + add_if_unsolved mk_ct thing cts + | isWantedCt ct = ct `consCts` cts + | otherwise = cts + where + ct = mk_ct thing + + getHasGivenEqs :: TcLevel -- TcLevel of this implication -> TcS ( HasGivenEqs -- are there Given equalities? , InertIrreds ) -- Insoluble equalities arising from givens @@ -824,6 +892,27 @@ for it, so TcS carries a mutable location where the binding can be added. This is initialised from the innermost implication constraint. -} +-- | See Note [TcSMode] +data TcSMode + = TcSVanilla -- ^ Normal constraint solving + | TcSEarlyAbort -- ^ Abort early on insoluble constraints + | TcSFullySolve -- ^ Fully solve all constraints + deriving (Eq) + +{- Note [TcSMode] +~~~~~~~~~~~~~~~~~ +The constraint solver can operate in different modes: + +* TcSVanilla: Normal constraint solving mode. This is the default. + +* TcSEarlyAbort: Abort (fail in the monad) as soon as we come across an + insoluble constraint. This is used to fail-fast when checking for hole-fits. + See Note [Speeding up valid hole-fits]. + +* TcSFullySolve: Fully solve all constraints. This mode is not currently used + but is included for future extensions. +-} + data TcSEnv = TcSEnv { tcs_ev_binds :: EvBindsVar, @@ -843,13 +932,11 @@ data TcSEnv tcs_inerts :: IORef InertSet, -- Current inert set - -- Whether to throw an exception if we come across an insoluble constraint. - -- Used to fail-fast when checking for hole-fits. See Note [Speeding up - -- valid hole-fits]. - tcs_abort_on_insoluble :: Bool, + -- | The mode of operation for the constraint solver. + -- See Note [TcSMode] + tcs_mode :: TcSMode, - -- See Note [WorkList priorities] in GHC.Tc.Solver.InertSet - tcs_worklist :: IORef WorkList -- Current worklist + tcs_worklist :: IORef WorkList } --------------- @@ -920,9 +1007,9 @@ addErrTcS = wrapTcS . TcM.addErr panicTcS doc = pprPanic "GHC.Tc.Solver.Monad" doc tryEarlyAbortTcS :: TcS () --- Abort (fail in the monad) if the abort_on_insoluble flag is on +-- Abort (fail in the monad) if the mode is TcSEarlyAbort tryEarlyAbortTcS - = mkTcS (\env -> when (tcs_abort_on_insoluble env) TcM.failM) + = mkTcS (\env -> when (tcs_mode env == TcSEarlyAbort) TcM.failM) -- | Emit a warning within the 'TcS' monad at the location given by the 'CtLoc'. ctLocWarnTcS :: CtLoc -> TcRnMessage -> TcS () @@ -992,7 +1079,15 @@ runTcS tcs runTcSEarlyAbort :: TcS a -> TcM a runTcSEarlyAbort tcs = do { ev_binds_var <- TcM.newTcEvBinds - ; runTcSWithEvBinds' True True ev_binds_var tcs } + ; runTcSWithEvBinds' True TcSEarlyAbort ev_binds_var tcs } + +-- | Run the TcS monad in 'TcSFullySolve' mode, +-- which attempts to fully solve all constraints. +-- +-- See Note [Fully solving constraints for specialisation] +runTcSFullySolve :: EvBindsVar -> TcS a -> TcM a +runTcSFullySolve ev_binds_var tcs + = runTcSWithEvBinds' True TcSFullySolve ev_binds_var tcs -- | This can deal only with equality constraints. runTcSEqualities :: TcS a -> TcM a @@ -1005,7 +1100,7 @@ runTcSEqualities thing_inside runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet) runTcSInerts inerts tcs = do ev_binds_var <- TcM.newTcEvBinds - runTcSWithEvBinds' False False ev_binds_var $ do + runTcSWithEvBinds' False TcSVanilla ev_binds_var $ do setInertSet inerts a <- tcs new_inerts <- getInertSet @@ -1014,17 +1109,17 @@ runTcSInerts inerts tcs = do runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds = runTcSWithEvBinds' True False +runTcSWithEvBinds = runTcSWithEvBinds' True TcSVanilla -runTcSWithEvBinds' :: Bool -- ^ Restore type variable cycles afterwards? +runTcSWithEvBinds' :: Bool -- True <=> restore type equality cycles -- Don't if you want to reuse the InertSet. -- See also Note [Type equality cycles] -- in GHC.Tc.Solver.Equality - -> Bool + -> TcSMode -> EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs +runTcSWithEvBinds' restore_cycles mode ev_binds_var tcs = do { unified_var <- TcM.newTcRef 0 ; step_count <- TcM.newTcRef 0 ; inert_var <- TcM.newTcRef emptyInert @@ -1035,7 +1130,7 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs , tcs_unif_lvl = unif_lvl_var , tcs_count = step_count , tcs_inerts = inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = wl_var } -- Run the computation @@ -1059,29 +1154,25 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs ---------------------------- #if defined(DEBUG) checkForCyclicBinds :: EvBindMap -> TcM () -checkForCyclicBinds ev_binds_map - | null cycles - = return () - | null coercion_cycles - = TcM.traceTc "Cycle in evidence binds" $ ppr cycles - | otherwise - = pprPanic "Cycle in coercion bindings" $ ppr coercion_cycles +checkForCyclicBinds ev_binds_map = do + edges <- liftIO $ traverse get_edge (bagToList $ evBindMapBinds ev_binds_map) + let cycles = [c | CyclicSCC c <- stronglyConnCompFromEdgedVerticesUniq edges] + coercion_cycles = [c | c <- cycles, any is_co_bind c] + is_co_bind (EvBind { eb_lhs = b }) = isEqPred (varType b) + if null cycles + then return () + else if null coercion_cycles + then TcM.traceTc "Cycle in evidence binds" $ ppr cycles + else pprPanic "Cycle in coercion bindings" $ ppr coercion_cycles where - ev_binds = evBindMapBinds ev_binds_map - - cycles :: [[EvBind]] - cycles = [c | CyclicSCC c <- stronglyConnCompFromEdgedVerticesUniq edges] - - coercion_cycles = [c | c <- cycles, any is_co_bind c] - is_co_bind (EvBind { eb_lhs = b }) = isEqPred (varType b) - - edges :: [ Node EvVar EvBind ] - edges = [ DigraphNode bind bndr (nonDetEltsUniqSet (evVarsOfTerm rhs)) - | bind@(EvBind { eb_lhs = bndr, eb_rhs = rhs}) <- bagToList ev_binds ] - -- It's OK to use nonDetEltsUFM here as - -- stronglyConnCompFromEdgedVertices is still deterministic even - -- if the edges are in nondeterministic order as explained in - -- Note [Deterministic SCC] in GHC.Data.Graph.Directed. + get_edge :: EvBind -> IO (Node EvVar EvBind) + get_edge bind@(EvBind { eb_lhs = bndr, eb_rhs = rhs}) = do + vars <- evVarsOfTerm rhs + return $ DigraphNode bind bndr (nonDetEltsUniqSet vars) + -- It's OK to use nonDetEltsUFM here as + -- stronglyConnCompFromEdgedVertices is still deterministic even + -- if the edges are in nondeterministic order as explained in + -- Note [Deterministic SCC] in GHC.Data.Graph.Directed. #endif ---------------------------- @@ -1097,7 +1188,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_inerts = old_inert_var , tcs_count = count , tcs_unif_lvl = unif_lvl - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode } -> do { inerts <- TcM.readTcRef old_inert_var ; let nest_inert = inerts { inert_cycle_breakers = pushCycleBreakerVarStack @@ -1112,7 +1203,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_ev_binds = ref , tcs_unified = unified_var , tcs_inerts = new_inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = new_wl_var } ; res <- TcM.setTcLevel inner_tclvl $ thing_inside nest_env @@ -1127,7 +1218,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) #endif ; return res } -nestTcS :: TcS a -> TcS a +nestTcS :: TcS a -> TcS a -- Use the current untouchables, augmenting the current -- evidence bindings, and solved dictionaries -- But have no effect on the InertCans, or on the inert_famapp_cache ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RecursiveDo #-} module GHC.Tc.Solver.Solve ( @@ -5,6 +6,7 @@ module GHC.Tc.Solver.Solve ( solveWanteds, -- Solves WantedConstraints solveSimpleGivens, -- Solves [Ct] solveSimpleWanteds, -- Solves Cts + solveCompletelyIfRequired, setImplicationStatus ) where @@ -51,6 +53,7 @@ import GHC.Driver.Session import Data.List( deleteFirstsBy ) import Control.Monad +import Data.Foldable ( for_ ) import qualified Data.Semigroup as S import Data.Void( Void ) @@ -546,13 +549,13 @@ neededEvVars implic@(Implic { ic_given = givens = do { ev_binds <- TcS.getTcEvBindsMap ev_binds_var ; tcvs <- TcS.getTcEvTyCoVars ev_binds_var - ; let seeds1 = foldr add_implic_seeds old_needs implics - seeds2 = nonDetStrictFoldEvBindMap add_wanted seeds1 ev_binds - -- It's OK to use a non-deterministic fold here - -- because add_wanted is commutative - seeds3 = seeds2 `unionVarSet` tcvs - need_inner = findNeededEvVars ev_binds seeds3 - live_ev_binds = filterEvBindMap (needed_ev_bind need_inner) ev_binds + ; let seeds1 = foldr add_implic_seeds old_needs implics + -- It's OK to use a non-deterministic fold here + -- because add_wanted is commutative + ; seeds2 <- wrapTcS $ foldEvBindMap add_wanted (pure seeds1) ev_binds + ; let seeds3 = seeds2 `unionVarSet` tcvs + ; need_inner <- liftIO $ findNeededEvVars ev_binds seeds3 + ; let live_ev_binds = filterEvBindMap (needed_ev_bind need_inner) ev_binds need_outer = varSetMinusEvBindMap need_inner live_ev_binds `delVarSetList` givens @@ -577,10 +580,10 @@ neededEvVars implic@(Implic { ic_given = givens | EvBindGiven{} <- info = ev_var `elemVarSet` needed | otherwise = True -- Keep all wanted bindings - add_wanted :: EvBind -> VarSet -> VarSet + add_wanted :: EvBind -> TcM VarSet -> TcM VarSet add_wanted (EvBind { eb_info = info, eb_rhs = rhs }) needs | EvBindGiven{} <- info = needs -- Add the rhs vars of the Wanted bindings only - | otherwise = evVarsOfTerm rhs `unionVarSet` needs + | otherwise = unionVarSet <$> liftIO (evVarsOfTerm rhs) <*> needs ------------------------------------------------- simplifyDelayedErrors :: Bag DelayedError -> TcS (Bag DelayedError) @@ -1214,6 +1217,7 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo tvs theta pred _fuel = -- See Note [Solving a Wanted forall-constraint] TcS.setSrcSpan (getCtLocEnvLoc $ ctLocEnv loc) $ + solveCompletelyIfRequired add_inert_wanted_qc $ -- This setSrcSpan is important: the emitImplicationTcS uses that -- TcLclEnv for the implication, and that in turn sets the location -- for the Givens when solving the constraint (#21006) @@ -1251,6 +1255,10 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo ; stopWith ev "Wanted forall-constraint" } where + add_inert_wanted_qc = + do { updInertIrreds (IrredCt ev IrredShapeReason) + ; stopWith ev "Wanted QC not fully solved" + } -- Getting the size of the head is a bit horrible -- because of the special treament for class predicates get_size pred = case classifyPredType pred of @@ -1298,7 +1306,7 @@ Note [Solving a Given forall-constraint] For a Given constraint [G] df :: forall ab. (Eq a, Ord b) => C x a b we just add it to TcS's local InstEnv of known instances, -via addInertForall. Then, if we look up (C x Int Bool), say, +via addInertForAll. Then, if we look up (C x Int Bool), say, we'll find a match in the InstEnv. @@ -1539,3 +1547,121 @@ runTcPluginSolvers solvers all_cts CtWanted {} -> (givens, (ev,ct):wanteds) +-------------------------------------------------------------------------------- + +-- | If the mode is 'TcSFullySolve', attempt to fully solve the Wanted +-- constraints that arise from 'thing_inside'; returning whether this was +-- successful. +-- +-- If not in 'TcSFullySolve' mode, simply run 'thing_inside'. +solveCompletelyIfRequired :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) +solveCompletelyIfRequired not_fully_solved_action (TcS thing_inside) + = TcS $ \ env@(TcSEnv { tcs_ev_binds = outer_ev_binds_var + , tcs_unified = outer_unified_var + , tcs_inerts = outer_inert_var + , tcs_count = outer_count + , tcs_mode = mode + }) -> + case mode of + TcSFullySolve -> + do { traceTc "solveCompletelyIfRequired {" empty + -- Create a fresh environment for the inner computation + ; outer_inerts <- TcM.readTcRef outer_inert_var + ; let (outer_givens, outer_wanteds) = + partitionInerts isGivenCt outer_inerts + -- Keep the ambient Given inerts, but drop the Wanteds. + ; new_inert_var <- TcM.newTcRef outer_givens + ; new_wl_var <- TcM.newTcRef emptyWorkList + ; new_ev_binds_var <- TcM.newTcEvBinds + ; new_unified_var <- TcM.newTcRef 0 + ; new_count <- TcM.newTcRef 0 + ; new_unif_lvl <- TcM.newTcRef Nothing + + ; let + inner_env = + TcSEnv + -- KEY part: recur with TcSVanilla + { tcs_mode = TcSVanilla + + -- Use new variables for the inner computation, because + -- we may want to discard its state entirely. + , tcs_count = new_count + , tcs_unif_lvl = new_unif_lvl + , tcs_ev_binds = new_ev_binds_var + , tcs_unified = new_unified_var + , tcs_inerts = new_inert_var + , tcs_worklist = new_wl_var + } + -- Run the inner computation + ; traceTc "solveCompletelyIfRequired thing_inside {{" empty + ; r <- thing_inside inner_env + ; wl <- TcM.readTcRef new_wl_var + ; traceTc "solveCompletelyIfRequired thing_inside }}" $ + vcat [ text "work list:" <+> ppr wl ] + + -- Now attempt to solve the resulting constraints using 'solveWanteds' + ; (implics, simples) <- unTcS getUnsolvedInerts2 inner_env + ; let wc = emptyWC { wc_simple = simples, wc_impl = implics } + ; traceTc "solveCompletelyIfRequired solveWanteds" $ + vcat [ text "wc:" <+> ppr wc + ] + ; solved_wc <- unTcS (solveWanteds wc) inner_env + + ; traceTc "solveCompletelyIfRequired solveWanteds done" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc + , text "outer_givens:" <+> ppr outer_givens + , text "outer_wanteds:" <+> ppr outer_wanteds + ] + + ; if isSolvedWC solved_wc + then + do { -- The constraint was fully solved. Continue with + -- the inner solved state. + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + + -- Add new evidence bindings to the existing ones + ; inner_ev_binds <- TcM.getTcEvBindsMap new_ev_binds_var + ; outer_ev_binds <- TcM.getTcEvBindsMap outer_ev_binds_var + ; let merged_ev_binds = outer_ev_binds `unionEvBindMap` inner_ev_binds + ; TcM.setTcEvBindsMap outer_ev_binds_var merged_ev_binds + + -- Use the new inert set, adding back on the outer Wanteds + ; new_inerts <- TcM.readTcRef new_inert_var + ; let combined_cans = (new_inerts `andInertSet` outer_wanteds) + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "outer_ev_binds_var:" <+> ppr outer_ev_binds_var + , text "inner_ev_binds_var:" <+> ppr new_ev_binds_var + , text "outer_inerts" <+> ppr outer_inerts + , text "new_inerts" <+> ppr new_inerts + , text "combined_cans:" <+> ppr combined_cans + , text "inner_ev_binds:" <+> ppr inner_ev_binds + , text "outer_ev_binds:" <+> ppr outer_ev_binds + , text "merged_ev_binds:" <+> ppr merged_ev_binds + ] + ; TcM.writeTcRef outer_inert_var combined_cans + + -- Update the outer unified, count, and unif_lvl variables + ; inner_unified <- TcM.readTcRef new_unified_var + ; inner_count <- TcM.readTcRef new_count + ; inner_unif_lvl <- TcM.readTcRef new_unif_lvl + ; TcM.updTcRef outer_unified_var (+ inner_unified) + ; TcM.updTcRef outer_count (+ inner_count) + ; for_ inner_unif_lvl $ \inner_lvl -> + unTcS (setUnificationFlag inner_lvl) env + + -- No need to update the outer work list: the inner work list + -- is empty by now (after 'solveWanteds'). + ; return r } + else + do { traceTc "solveCompletelyIfRequired: unsolved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + ; -- Failed to fully solve the constraint. + -- Discard the inner solver state and continue. + ; unTcS not_fully_solved_action env + } } + _notFullySolveMode -> + thing_inside env ===================================== compiler/GHC/Tc/Solver/Solve.hs-boot ===================================== @@ -0,0 +1,6 @@ +module GHC.Tc.Solver.Solve where + +import GHC.Tc.Solver.Monad (StopOrContinue, TcS) + +solveCompletelyIfRequired + :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) ===================================== compiler/GHC/Tc/Types/Evidence.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Tc.Types.Evidence ( -- * Evidence bindings TcEvBinds(..), EvBindsVar(..), - EvBindMap(..), emptyEvBindMap, extendEvBinds, + EvBindMap(..), emptyEvBindMap, extendEvBinds, unionEvBindMap, lookupEvBind, evBindMapBinds, foldEvBindMap, nonDetStrictFoldEvBindMap, filterEvBindMap, @@ -79,14 +79,17 @@ import GHC.Utils.Outputable import GHC.Data.Bag import GHC.Data.FastString -import qualified Data.Data as Data import GHC.Types.SrcLoc -import Data.IORef( IORef ) import GHC.Types.Unique.Set import GHC.Core.Multiplicity +import qualified Data.Data as Data + +import Control.Monad (foldM) +import Data.IORef( IORef, readIORef ) import qualified Data.Semigroup as S + {- Note [TcCoercions] ~~~~~~~~~~~~~~~~~~ @@ -433,6 +436,11 @@ extendEvBinds bs ev_bind (eb_lhs ev_bind) ev_bind } +unionEvBindMap :: EvBindMap -> EvBindMap -> EvBindMap +unionEvBindMap bs1 bs2 + = EvBindMap { ev_bind_varenv = plusDVarEnv (ev_bind_varenv bs1) + (ev_bind_varenv bs2) } + isEmptyEvBindMap :: EvBindMap -> Bool isEmptyEvBindMap (EvBindMap m) = isEmptyDVarEnv m @@ -765,9 +773,6 @@ Wrinkles So isPushCallStackOrigin_maybe has a fall-through for "anything else", and assumes that we should adopt plan PUSH for it. - However we should /not/ take this fall-through for Given constraints - (#25675). So isPushCallStackOrigin_maybe identifies Givens as plan NORMAL. - (CS2) GHC should NEVER report an insoluble CallStack constraint. (CS3) GHC should NEVER infer a CallStack constraint unless one was requested @@ -860,37 +865,74 @@ evTermCoercion tm = case evTermCoercion_maybe tm of * * ********************************************************************* -} -findNeededEvVars :: EvBindMap -> VarSet -> VarSet +findNeededEvVars :: EvBindMap -> VarSet -> IO VarSet -- Find all the Given evidence needed by seeds, -- looking transitively through binds findNeededEvVars ev_binds seeds - = transCloVarSet also_needs seeds + = transCloVarSetIO also_needs seeds where - also_needs :: VarSet -> VarSet - also_needs needs = nonDetStrictFoldUniqSet add emptyVarSet needs + also_needs :: VarSet -> IO VarSet + also_needs needs = foldM add emptyVarSet (nonDetEltsUniqSet needs) -- It's OK to use a non-deterministic fold here because we immediately -- forget about the ordering by creating a set - add :: Var -> VarSet -> VarSet - add v needs + add :: VarSet -> Var -> IO VarSet + add needs v | Just ev_bind <- lookupEvBind ev_binds v , EvBind { eb_info = EvBindGiven, eb_rhs = rhs } <- ev_bind - = evVarsOfTerm rhs `unionVarSet` needs + = do + rhs_vars <- evVarsOfTerm rhs + return (rhs_vars `unionVarSet` needs) | otherwise - = needs - -evVarsOfTerm :: EvTerm -> VarSet -evVarsOfTerm (EvExpr e) = exprSomeFreeVars isEvVar e + = return needs + +-- | Compute the transitive closure of a set in a monad +transCloVarSetIO :: (VarSet -> IO VarSet) -> VarSet -> IO VarSet +transCloVarSetIO f vs + = do + vs' <- f vs + let vs_new = vs' `minusVarSet` vs + if isEmptyVarSet vs_new + then return vs + else do + vs_rest <- transCloVarSetIO f vs_new + return (vs `unionVarSet` vs_rest) + +evVarsOfTerm :: EvTerm -> IO VarSet +evVarsOfTerm (EvExpr e) = pure $ exprSomeFreeVars isEvVar e evVarsOfTerm (EvTypeable _ ev) = evVarsOfTypeable ev -evVarsOfTerm (EvFun {}) = emptyVarSet -- See Note [Free vars of EvFun] - -evVarsOfTerms :: [EvTerm] -> VarSet -evVarsOfTerms = mapUnionVarSet evVarsOfTerm - -evVarsOfTypeable :: EvTypeable -> VarSet +evVarsOfTerm (EvFun { et_given = givens, et_binds = binds, et_body = body_id }) + = do { rhs_binds <- + case binds of + TcEvBinds (EvBindsVar { ebv_binds = ev_binds_ref }) -> + eltsUDFM . ev_bind_varenv <$> readIORef ev_binds_ref + TcEvBinds (CoEvBindsVar {}) -> + pure [] + EvBinds ev_bag -> + return $ bagToList ev_bag + ; let lhs_evvars = mkVarSet $ map eb_lhs rhs_binds + -- Get the RHS variables + ; rhs_evvars <- foldM (\acc bind -> do + vars <- evVarsOfTerm (eb_rhs bind) + pure (vars `unionVarSet` acc)) + emptyVarSet rhs_binds + -- Variables needed by the body, excluding the given variables and LHS variables + ; let needed_vars = (unitVarSet body_id `unionVarSet` rhs_evvars) + `minusVarSet` mkVarSet givens + `minusVarSet` lhs_evvars + ; pure needed_vars } + +evVarsOfTerms :: [EvTerm] -> IO VarSet +evVarsOfTerms [] = pure emptyVarSet +evVarsOfTerms (t:ts) = do + vars1 <- evVarsOfTerm t + vars2 <- evVarsOfTerms ts + pure (vars1 `unionVarSet` vars2) + +evVarsOfTypeable :: EvTypeable -> IO VarSet evVarsOfTypeable ev = case ev of - EvTypeableTyCon _ e -> mapUnionVarSet evVarsOfTerm e + EvTypeableTyCon _ e -> evVarsOfTerms e EvTypeableTyApp e1 e2 -> evVarsOfTerms [e1,e2] EvTypeableTrFun em e1 e2 -> evVarsOfTerms [em,e1,e2] EvTypeableTyLit e -> evVarsOfTerm e ===================================== testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs ===================================== @@ -17,7 +17,6 @@ import Data.Proxy f1 :: ( Num a, Eq b ) => a -> b -> Int f1 _ _ = 111 - -- Make sure we don't generate a rule with an LHS of the form -- -- forall @e (d :: Eq e). f1 @[e] ($fEqList d) = ... @@ -56,12 +55,18 @@ f3 z = z == z -------------------------------------------------------------------------------- -f4 :: Monad m => a -> m a +f4 :: (Eq a, Monad m) => a -> m a f4 = return -- Check we can deal with locally quantified variables in constraints, -- in this case 'Monad (ST s)'. -{-# SPECIALISE f4 :: b -> ST s b #-} +{-# SPECIALISE f4 :: forall s b. Eq b => b -> ST s b #-} + +f4_qc :: (Eq a, forall m. Monad m => Monad (t m)) => t m a -> () +f4_qc _ = () + +-- Like 'f4' but with a quantified constraint. +{-# SPECIALISE f4_qc :: forall r n b. (forall m. Monad m => Monad (r m)) => r n Int -> () #-} -------------------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9a61f68527d79a21c09b09be09d336db459a6dc3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9a61f68527d79a21c09b09be09d336db459a6dc3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/98b38f39/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 13:11:06 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 07 Mar 2025 08:11:06 -0500 Subject: [Git][ghc/ghc][wip/T24359] 4 commits: move updInertDicts, updInertIrreds Message-ID: <67caf06a3304e_54e997cdae4674c6@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 63d03cf3 by sheaf at 2025-03-07T13:41:53+01:00 move updInertDicts, updInertIrreds - - - - - 02627924 by sheaf at 2025-03-07T13:41:56+01:00 fix isEmptyWorkList - - - - - 0d777eff by sheaf at 2025-03-07T13:42:16+01:00 fix EvVarsOfTerm - - - - - 34f8b525 by sheaf at 2025-03-07T14:10:50+01:00 new plan from March 7 - - - - - 9 changed files: - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Types/Evidence.hs - testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs Changes: ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -39,7 +39,7 @@ import GHC.Tc.Gen.HsType import GHC.Tc.Solver( reportUnsolvedEqualities, pushLevelAndSolveEqualitiesX , emitResidualConstraints ) import GHC.Tc.Solver.Solve( solveWanteds ) -import GHC.Tc.Solver.Monad( runTcS, runTcSWithEvBinds ) +import GHC.Tc.Solver.Monad( runTcS, runTcSFullySolve ) import GHC.Tc.Validity ( checkValidType ) import GHC.Tc.Utils.Monad @@ -761,16 +761,11 @@ This is done in three parts. (1) Typecheck the expression, capturing its constraints - (2) Clone these Wanteds, solve them, and zonk the original Wanteds. - This is the same thing that we do for RULES: see Step 1 in - Note [The SimplifyRule Plan]. + (2) Solve these constraints, but in special TcSFullySolve mode which ensures + each original Wanted is either fully solved or left untouched. + See Note [Fully solving constraints for specialisation]. - (3) Compute the constraints to quantify over. - - a. 'getRuleQuantCts' computes the initial quantification candidates - b. Filter out the fully soluble constraints; these are the constraints - we are specialising away. - See Note [Fully solving constraints for specialisation]. + (3) Compute the constraints to quantify over, using `getRuleQuantCts`. (4) Emit the residual (non-quantified) constraints, and wrap the expression in a let binding for those constraints. @@ -850,9 +845,8 @@ The conclusion is this: - fully solved (no free evidence variables), or - left untouched. -To achieve this, we quantify over all constraints that are **not fully soluble** -(see 'fullySolveCt_maybe'), although we still call 'mkMinimalBySCs' on this set -to avoid e.g. quantifying over both `Eq a` and `Ord a`. +To achieve this, we run the solver in a special "all-or-nothing" solving mode, +described in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. Note [Handling old-form SPECIALISE pragmas] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1029,40 +1023,26 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) <- tcRuleBndrs skol_info rule_bndrs $ tcInferRho spec_e - -- (2) Clone these Wanteds, solve them, and zonk the original - -- Wanteds, in order to benefit from any unifications. - - ; throwaway_ev_binds_var <- newTcEvBinds - ; spec_e_wanted_clone <- cloneWC spec_e_wanted - ; _ <- setTcLevel rhs_tclvl $ - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds spec_e_wanted_clone + -- (2) Solve the resulting wanteds in TcSFullySolve mode. + ; ev_binds_var <- newTcEvBinds + ; spec_e_wanted <- setTcLevel rhs_tclvl $ + runTcSFullySolve ev_binds_var $ + solveWanteds spec_e_wanted ; spec_e_wanted <- liftZonkM $ zonkWC spec_e_wanted -- (3) Compute which constraints to quantify over. - -- (a) Compute quantification candidates - ; ev_binds_var <- newTcEvBinds ; (quant_cands, residual_wc) <- getRuleQuantCts spec_e_wanted - -- (b) Compute fully soluble constraints - -- See Note [Fully solving constraints for specialisation] - ; traceTc "tcSpecPrag SpecSigE: computing fully soluble Wanteds {" empty - ; fully_soluble_evids <- - setTcLevel rhs_tclvl $ - mkVarSet <$> - mapMaybeM fullySolveCt_maybe (bagToList quant_cands) - ; let (fully_soluble_cts, quant_cts) = partitionBag ((`elemVarSet` fully_soluble_evids) . ctEvId) quant_cands - -- (c) Compute constraints to quantify over using 'mkMinimalBySCs' - qevs = map ctEvId (bagToList quant_cts) - ; traceTc "tcSpecPrag SpecSigE: computed fully soluble Wanteds }" (ppr fully_soluble_cts) - -- (4) Emit the residual constraints (that we are not quantifying over) ; let tv_bndrs = filter isTyVar rule_bndrs' + qevs = map ctEvId (bagToList quant_cands) ; emitResidualConstraints rhs_tclvl skol_info_anon ev_binds_var emptyVarSet tv_bndrs qevs - (residual_wc `addSimples` fully_soluble_cts) + residual_wc ; let lhs_call = mkLHsWrap (WpLet (TcEvBinds ev_binds_var)) tc_spec_e + ; ev_binds <- getTcEvBindsMap ev_binds_var + ; traceTc "tcSpecPrag SpecSigE }" $ vcat [ text "nm:" <+> ppr nm , text "rule_bndrs':" <+> ppr rule_bndrs' @@ -1070,9 +1050,11 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) , text "spec_e:" <+> ppr tc_spec_e , text "inl:" <+> ppr inl , text "spec_e_wanted:" <+> ppr spec_e_wanted - , text "quant_cts:" <+> ppr quant_cts + , text "quant_cands:" <+> ppr quant_cands , text "residual_wc:" <+> ppr residual_wc - , text "fully_soluble_wanteds:" <+> ppr fully_soluble_cts + , text (replicate 80 '-') + , text "ev_binds_var:" <+> ppr ev_binds_var + , text "ev_binds:" <+> ppr ev_binds ] -- (5) Store the results in a SpecPragE record, which will be @@ -1087,24 +1069,6 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) tcSpecPrag _ prag = pprPanic "tcSpecPrag" (ppr prag) --- | Try to fully solve a constraint. -fullySolveCt_maybe :: Ct -> TcM (Maybe EvId) -fullySolveCt_maybe ct = do - throwaway_ev_binds_var <- newTcEvBinds - res_wc <- - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds $ emptyWC { wc_simple = unitBag ct } - -- NB: don't use 'solveSimpleWanteds', as this will not - -- fully solve quantified constraints. - traceTc "fullySolveCt_maybe" $ - vcat [ text "ct:" <+> ppr ct - , text "res_wc:" <+> ppr res_wc - ] - return $ - if isSolvedWC res_wc - then Just $ ctEvId ct - else Nothing - -------------- tcSpecWrapper :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper -- A simpler variant of tcSubType, used for SPECIALISE pragmas ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -61,6 +61,7 @@ import Data.Void( Void ) import Control.Monad.Trans.Maybe( MaybeT, runMaybeT ) import Control.Monad.Trans.Class( lift ) import Control.Monad +import {-# SOURCE #-} GHC.Tc.Solver.Solve (solveCompletelyIfRequired) {- ********************************************************************* @@ -101,26 +102,6 @@ solveDict dict_ct@(DictCt { di_ev = ev, di_cls = cls, di_tys = tys }) ; simpleStage (updInertDicts dict_ct) ; stopWithStage (dictCtEvidence dict_ct) "Kept inert DictCt" } -updInertDicts :: DictCt -> TcS () -updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys }) - = do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls <+> ppr tys) - - ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys - -> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters] - -- Update /both/ inert_cans /and/ inert_solved_dicts. - updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) -> - inerts { inert_cans = updDicts (filterDicts (not_ip_for str_ty)) ics - , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved } - | otherwise - -> return () - - -- Add the new constraint to the inert set - ; updInertCans (updDicts (addDict dict_ct)) } - where - not_ip_for :: Type -> DictCt -> Bool - not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys }) - = not (mentionsIP str_ty cls tys) - canDictCt :: CtEvidence -> Class -> [Type] -> SolverStage DictCt -- Once-only processing of Dict constraints: -- * expand superclasses @@ -868,7 +849,13 @@ shortCutSolver dflags ev_w ev_i tryInstances :: DictCt -> SolverStage () tryInstances dict_ct = Stage $ do { inerts <- getInertSet - ; try_instances inerts dict_ct } + + -- We are about to do something irreversible (using an instance + -- declaration), so we wrap 'try_instances' in solveCompletelyIfRequired + -- to ensure we can roll back if we can't solve the constraint fully. + -- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. + ; solveCompletelyIfRequired (continueWith ()) $ + try_instances inerts dict_ct } try_instances :: InertSet -> DictCt -> TcS (StopOrContinue ()) -- Try to use type-class instance declarations to simplify the constraint ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeApplications #-} @@ -24,6 +25,7 @@ module GHC.Tc.Solver.InertSet ( InertEqs, foldTyEqs, delEq, findEq, partitionInertEqs, partitionFunEqs, + partitionInerts, andInertSet, foldFunEqs, addEqToCans, -- * Inert Dicts @@ -73,10 +75,11 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Data.Bag +import Control.Monad ( forM_ ) +import Data.List ( partition ) import Data.List.NonEmpty ( NonEmpty(..), (<|) ) -import Data.Function ( on ) +import Data.Function ( on ) -import Control.Monad ( forM_ ) {- ************************************************************************ @@ -286,9 +289,9 @@ extendWorkListCts :: Cts -> WorkList -> WorkList extendWorkListCts cts wl = foldr extendWorkListCt wl cts isEmptyWorkList :: WorkList -> Bool -isEmptyWorkList (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X +isEmptyWorkList (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X, wl_rw_eqs = rw_eqs , wl_rest = rest, wl_implics = implics }) - = null eqs_N && null eqs_X && null rest && isEmptyBag implics + = null eqs_N && null eqs_X && null rw_eqs && null rest && isEmptyBag implics emptyWorkList :: WorkList emptyWorkList = WL { wl_eqs_N = [], wl_eqs_X = [] @@ -390,7 +393,6 @@ emptyInert , inert_famapp_cache = emptyFunEqs , inert_solved_dicts = emptyDictMap } - {- Note [Solved dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When we apply a top-level instance declaration, we add the "solved" @@ -2214,3 +2216,115 @@ Wrong! The level-check ensures that the inner implicit parameter wins. (Actually I think that the order in which the work-list is processed means that this chain of events won't happen, but that's very fragile.) -} + +-- | Partition the inert set according to a predicate. +partitionInerts :: (Ct -> Bool) -> InertSet -> (InertSet, InertSet) +partitionInerts pred is@(IS { inert_cans = cans }) + = (is { inert_cans = givens_cans }, is { inert_cans = wanteds_cans }) + where + -- Helper functions to convert between Ct and specific constraint types + eqPred :: EqCt -> Bool + eqPred eq = pred (CEqCan eq) + + dictPred :: DictCt -> Bool + dictPred dict = pred (CDictCan dict) + + irredPred :: IrredCt -> Bool + irredPred irred = pred (CIrredCan irred) + + qciPred :: QCInst -> Bool + qciPred qci = pred (CQuantCan qci) + + -- Partition the inert constraints + (eq_givens_list, eq_wanteds) = partitionInertEqs eqPred (inert_eqs cans) + (funeq_givens_list, funeq_wanteds) = partitionFunEqs eqPred (inert_funeqs cans) + (dict_givens_bag, dict_wanteds) = partitionDicts dictPred (inert_dicts cans) + (safehask_givens_bag, safehask_wanteds) = partitionDicts dictPred (inert_safehask cans) + (insts_givens, insts_wanteds) = partition qciPred (inert_insts cans) + (irreds_givens, irreds_wanteds) = partitionBag irredPred (inert_irreds cans) + + -- Convert lists to the appropriate container types + eq_givens = foldr addInertEqs emptyTyEqs eq_givens_list + funeq_givens = foldr addFunEqs emptyFunEqs funeq_givens_list + + givens_cans = emptyInertCans { + inert_eqs = eq_givens, + inert_funeqs = funeq_givens, + inert_dicts = dictsToDictMap dict_givens_bag, + inert_safehask = dictsToDictMap safehask_givens_bag, + inert_insts = insts_givens, + inert_irreds = irreds_givens, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + + wanteds_cans = emptyInertCans { + inert_eqs = eq_wanteds, + inert_funeqs = funeq_wanteds, + inert_dicts = dict_wanteds, + inert_safehask = safehask_wanteds, + inert_insts = insts_wanteds, + inert_irreds = irreds_wanteds, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + +-- | Convert a Bag of DictCts to a DictMap +dictsToDictMap :: Bag DictCt -> DictMap DictCt +dictsToDictMap = foldr addDict emptyDictMap . bagToList + +-- | Union two DictMaps +unionDictMap :: DictMap DictCt -> DictMap DictCt -> DictMap DictCt +unionDictMap dm1 dm2 = foldrTcAppMap addDict dm1 dm2 + +-- | Union two InertEqs +unionTyEqs :: InertEqs -> InertEqs -> InertEqs +unionTyEqs eqs1 eqs2 = foldrTyEqs addInertEqs eqs1 eqs2 + +-- | Union two InertFunEqs +unionFunEqs :: InertFunEqs -> InertFunEqs -> InertFunEqs +unionFunEqs feqs1 feqs2 = foldrFunEqs addFunEqs feqs1 feqs2 + +-- | Union two FunEqMap Reductions +unionFunEqMap :: FunEqMap Reduction -> FunEqMap Reduction -> FunEqMap Reduction +unionFunEqMap m1 m2 = foldTcAppMap (\r acc -> + let ty = reductionReducedType r + in case tcSplitTyConApp_maybe ty of + Just (tc, args) -> insertTcApp acc tc args r + Nothing -> acc) + m1 m2 + +-- | Fold over a TcAppMap with a function +foldrTcAppMap :: (a -> b -> b) -> TcAppMap a -> b -> b +foldrTcAppMap k m z = foldTcAppMap (\x acc -> k x acc) m z + +-- | Fold over FunEqs with a function +foldrFunEqs :: (EqCt -> b -> b) -> InertFunEqs -> b -> b +foldrFunEqs k feqs z = foldFunEqs (\eq acc -> k eq acc) feqs z + +-- | Fold over TyEqs with a function +foldrTyEqs :: (EqCt -> b -> b) -> InertEqs -> b -> b +foldrTyEqs k eqs z = foldTyEqs (\eq acc -> k eq acc) eqs z + +-- | Combine two 'InertSet's in a monoidal manner. +andInertSet :: InertSet -> InertSet -> InertSet +andInertSet is1 is2 + = IS { inert_cans = combinedCans, + inert_cycle_breakers = inert_cycle_breakers is1, -- Keep the first one's cycle breakers + inert_famapp_cache = unionFunEqMap (inert_famapp_cache is1) (inert_famapp_cache is2), + inert_solved_dicts = unionDictMap (inert_solved_dicts is1) (inert_solved_dicts is2) + } + where + cans1 = inert_cans is1 + cans2 = inert_cans is2 + + combinedCans = IC { + inert_eqs = unionTyEqs (inert_eqs cans1) (inert_eqs cans2), + inert_funeqs = unionFunEqs (inert_funeqs cans1) (inert_funeqs cans2), + inert_dicts = unionDictMap (inert_dicts cans1) (inert_dicts cans2), + inert_safehask = unionDictMap (inert_safehask cans1) (inert_safehask cans2), + inert_insts = inert_insts cans1 ++ inert_insts cans2, + inert_irreds = unionBags (inert_irreds cans1) (inert_irreds cans2), + inert_given_eq_lvl = maxTcLevel (inert_given_eq_lvl cans1) (inert_given_eq_lvl cans2), + inert_given_eqs = inert_given_eqs cans1 || inert_given_eqs cans2 + } ===================================== compiler/GHC/Tc/Solver/Irred.hs ===================================== @@ -39,10 +39,6 @@ solveIrred irred ; simpleStage (updInertIrreds irred) ; stopWithStage (irredCtEvidence irred) "Kept inert IrredCt" } -updInertIrreds :: IrredCt -> TcS () -updInertIrreds irred - = do { tc_lvl <- getTcLevel - ; updInertCans $ addIrredToCans tc_lvl irred } {- ********************************************************************* * * ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -14,7 +14,9 @@ module GHC.Tc.Solver.Monad ( -- The TcS monad - TcS, runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + TcS(..), TcSEnv(..), TcSMode(..), + runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + runTcSFullySolve, failTcS, warnTcS, addErrTcS, wrapTcS, ctLocWarnTcS, runTcSEqualities, nestTcS, nestImplicTcS, setEvBindsTcS, @@ -71,9 +73,10 @@ module GHC.Tc.Solver.Monad ( getInertEqs, getInertCans, getInertGivens, getInertInsols, getInnermostGivenEqLevel, getInertSet, setInertSet, - getUnsolvedInerts, + getUnsolvedInerts, getUnsolvedInerts2, removeInertCts, getPendingGivenScs, insertFunEq, addInertForAll, + updInertDicts, updInertIrreds, emitWorkNC, emitWork, lookupInertDict, @@ -202,13 +205,14 @@ import GHC.Exts (oneShot) import Control.Monad import Data.Foldable hiding ( foldr1 ) import Data.IORef -import Data.List ( mapAccumL ) +import Data.List ( mapAccumL, unfoldr ) import Data.List.NonEmpty ( nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) import qualified Data.Semigroup as S import GHC.Types.SrcLoc import GHC.Rename.Env +--import GHC.Tc.Solver.Solve (solveWanteds) #if defined(DEBUG) import GHC.Types.Unique.Set (nonDetEltsUniqSet) @@ -369,6 +373,31 @@ duplicates, is explained in Note [Use only the best matching quantified constrai in GHC.Tc.Solver.Dict. -} +updInertDicts :: DictCt -> TcS () +updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys }) + = do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls <+> ppr tys) + + ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys + -> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters] + -- Update /both/ inert_cans /and/ inert_solved_dicts. + updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) -> + inerts { inert_cans = updDicts (filterDicts (not_ip_for str_ty)) ics + , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved } + | otherwise + -> return () + + -- Add the new constraint to the inert set + ; updInertCans (updDicts (addDict dict_ct)) } + where + not_ip_for :: Type -> DictCt -> Bool + not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys }) + = not (mentionsIP str_ty cls tys) + +updInertIrreds :: IrredCt -> TcS () +updInertIrreds irred + = do { tc_lvl <- getTcLevel + ; updInertCans $ addIrredToCans tc_lvl irred } + {- ********************************************************************* * * Kicking out @@ -579,7 +608,7 @@ getInertGivens :: TcS [Ct] getInertGivens = do { inerts <- getInertCans ; let all_cts = foldIrreds ((:) . CIrredCan) (inert_irreds inerts) - $ foldDicts ((:) . CDictCan) (inert_dicts inerts) + $ foldDicts ((:) . CDictCan) (inert_dicts inerts) $ foldFunEqs ((:) . CEqCan) (inert_funeqs inerts) $ foldTyEqs ((:) . CEqCan) (inert_eqs inerts) $ [] @@ -679,6 +708,45 @@ getUnsolvedInerts where ct = mk_ct thing +getUnsolvedInerts2 :: TcS ( Bag Implication, Cts ) +getUnsolvedInerts2 + = do { IC { inert_eqs = tv_eqs + , inert_funeqs = fun_eqs + , inert_irreds = irreds + , inert_dicts = idicts + } <- getInertCans + + ; let unsolved_tv_eqs = foldTyEqs (add_if_unsolved CEqCan) tv_eqs emptyCts + unsolved_fun_eqs = foldFunEqs (add_if_unsolved CEqCan) fun_eqs emptyCts + unsolved_irreds = foldr (add_if_unsolved CIrredCan) emptyCts irreds + unsolved_dicts = foldDicts (add_if_unsolved CDictCan) idicts emptyCts + + ; wl_var <- getTcSWorkListRef + ; wl_curr <- readTcRef wl_var + ; implics <- getWorkListImplics + ; let wl_simpls = listToBag $ unfoldr selectWorkItem wl_curr + + ; traceTcS "getUnsolvedInerts" $ + vcat [ text " tv eqs =" <+> ppr unsolved_tv_eqs + , text "fun eqs =" <+> ppr unsolved_fun_eqs + , text "dicts =" <+> ppr unsolved_dicts + , text "irreds =" <+> ppr unsolved_irreds + , text "implics =" <+> ppr implics ] + + ; return ( implics, unsolved_tv_eqs `unionBags` + unsolved_fun_eqs `unionBags` + unsolved_irreds `unionBags` + unsolved_dicts `unionBags` + wl_simpls) } + where + add_if_unsolved :: (a -> Ct) -> a -> Cts -> Cts + add_if_unsolved mk_ct thing cts + | isWantedCt ct = ct `consCts` cts + | otherwise = cts + where + ct = mk_ct thing + + getHasGivenEqs :: TcLevel -- TcLevel of this implication -> TcS ( HasGivenEqs -- are there Given equalities? , InertIrreds ) -- Insoluble equalities arising from givens @@ -824,6 +892,31 @@ for it, so TcS carries a mutable location where the binding can be added. This is initialised from the innermost implication constraint. -} +-- | See Note [TcSMode] +data TcSMode + = TcSVanilla -- ^ Normal constraint solving + | TcSEarlyAbort -- ^ Abort early on insoluble constraints + | TcSFullySolve -- ^ Fully solve all constraints + deriving (Eq) + +{- Note [TcSMode] +~~~~~~~~~~~~~~~~~ +The constraint solver can operate in different modes: + +* TcSVanilla: Normal constraint solving mode. This is the default. + +* TcSEarlyAbort: Abort (fail in the monad) as soon as we come across an + insoluble constraint. This is used to fail-fast when checking for hole-fits. + See Note [Speeding up valid hole-fits]. + +* TcSFullySolve: Solve constraints fully or not at all. This is described in + Note [TcSFullySolve]. + + This mode is currently used in one place only: when solving constraints + arising from specialise pragmas. + See Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. +-} + data TcSEnv = TcSEnv { tcs_ev_binds :: EvBindsVar, @@ -843,13 +936,11 @@ data TcSEnv tcs_inerts :: IORef InertSet, -- Current inert set - -- Whether to throw an exception if we come across an insoluble constraint. - -- Used to fail-fast when checking for hole-fits. See Note [Speeding up - -- valid hole-fits]. - tcs_abort_on_insoluble :: Bool, + -- | The mode of operation for the constraint solver. + -- See Note [TcSMode] + tcs_mode :: TcSMode, - -- See Note [WorkList priorities] in GHC.Tc.Solver.InertSet - tcs_worklist :: IORef WorkList -- Current worklist + tcs_worklist :: IORef WorkList } --------------- @@ -920,9 +1011,9 @@ addErrTcS = wrapTcS . TcM.addErr panicTcS doc = pprPanic "GHC.Tc.Solver.Monad" doc tryEarlyAbortTcS :: TcS () --- Abort (fail in the monad) if the abort_on_insoluble flag is on +-- Abort (fail in the monad) if the mode is TcSEarlyAbort tryEarlyAbortTcS - = mkTcS (\env -> when (tcs_abort_on_insoluble env) TcM.failM) + = mkTcS (\env -> when (tcs_mode env == TcSEarlyAbort) TcM.failM) -- | Emit a warning within the 'TcS' monad at the location given by the 'CtLoc'. ctLocWarnTcS :: CtLoc -> TcRnMessage -> TcS () @@ -992,7 +1083,60 @@ runTcS tcs runTcSEarlyAbort :: TcS a -> TcM a runTcSEarlyAbort tcs = do { ev_binds_var <- TcM.newTcEvBinds - ; runTcSWithEvBinds' True True ev_binds_var tcs } + ; runTcSWithEvBinds' True TcSEarlyAbort ev_binds_var tcs } + +-- | Run the 'TcS' monad in 'TcSFullySolve' mode, which either fully solves +-- each individual constraint or leaves it alone. See Note [TcSFullySolve]. +runTcSFullySolve :: EvBindsVar -> TcS a -> TcM a +runTcSFullySolve ev_binds_var tcs + = runTcSWithEvBinds' True TcSFullySolve ev_binds_var tcs + +{- Note [TcSFullySolve] +~~~~~~~~~~~~~~~~~~~~~~~ +The TcSFullySolve mode is a specialized constraint solving mode that guarantees +each constraint is either: + - Fully solved with no free evidence variables, or + - Left completely untouched (no simplification at all) + +Examples: + + * [W] Eq [a]. + + In TcSFullySolve mode, we **do not** simplify this constraint to [W] Eq a, + using the top-level Eq instance; instead we leave it alone as [W] Eq [a]. + + * [W] forall x. Eq x => Eq (f x). + + In TcSFullySolve mode, we **do not** process this quantified constraint by + creating a new implication constraint; we leave it alone instead. + + * [W] Eq (Maybe Int). + + This constraint is solved fully, using two top-level Eq instances. + + * [W] forall x. Eq x => Eq [x]. + + This constraint is solved fully as well, using the Eq instance for lists. + +The main observation is that, in TcSFullySolve mode, we should not take any +**irreversible** steps. We can't run instances in reverse, nor recover the +original quantified constraint from the generated implication, so in these +two cases (and these two cases only), in the solver, we call the special +function `solveCompletelyIfRequired`. This function recursively calls the +solver but in TcSVanilla mode (i.e. full-blown solving, with no restrictions). +If this recursive call manages to solve all the remaining constraints fully, +then we proceed with that outcome (i.e. we continue with that inert set, etc). +Otherwise, discard everything that happened in the recursive call, and continue +with the original constraint unchanged. + +This functionality is crucially used by the specialiser, for which such +irreversible constraint solving steps are actively harmful, as described in +Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. + +In the future, we could consider re-using this functionality for the short-cut +solver (see Note [The shortcut solver] in GHC.Tc.Solver), but we would have to +be wary of the performance implications. +-} -- | This can deal only with equality constraints. runTcSEqualities :: TcS a -> TcM a @@ -1005,7 +1149,7 @@ runTcSEqualities thing_inside runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet) runTcSInerts inerts tcs = do ev_binds_var <- TcM.newTcEvBinds - runTcSWithEvBinds' False False ev_binds_var $ do + runTcSWithEvBinds' False TcSVanilla ev_binds_var $ do setInertSet inerts a <- tcs new_inerts <- getInertSet @@ -1014,17 +1158,17 @@ runTcSInerts inerts tcs = do runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds = runTcSWithEvBinds' True False +runTcSWithEvBinds = runTcSWithEvBinds' True TcSVanilla -runTcSWithEvBinds' :: Bool -- ^ Restore type variable cycles afterwards? +runTcSWithEvBinds' :: Bool -- True <=> restore type equality cycles -- Don't if you want to reuse the InertSet. -- See also Note [Type equality cycles] -- in GHC.Tc.Solver.Equality - -> Bool + -> TcSMode -> EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs +runTcSWithEvBinds' restore_cycles mode ev_binds_var tcs = do { unified_var <- TcM.newTcRef 0 ; step_count <- TcM.newTcRef 0 ; inert_var <- TcM.newTcRef emptyInert @@ -1035,7 +1179,7 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs , tcs_unif_lvl = unif_lvl_var , tcs_count = step_count , tcs_inerts = inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = wl_var } -- Run the computation @@ -1059,29 +1203,25 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs ---------------------------- #if defined(DEBUG) checkForCyclicBinds :: EvBindMap -> TcM () -checkForCyclicBinds ev_binds_map - | null cycles - = return () - | null coercion_cycles - = TcM.traceTc "Cycle in evidence binds" $ ppr cycles - | otherwise - = pprPanic "Cycle in coercion bindings" $ ppr coercion_cycles +checkForCyclicBinds ev_binds_map = do + edges <- liftIO $ traverse get_edge (bagToList $ evBindMapBinds ev_binds_map) + let cycles = [c | CyclicSCC c <- stronglyConnCompFromEdgedVerticesUniq edges] + coercion_cycles = [c | c <- cycles, any is_co_bind c] + is_co_bind (EvBind { eb_lhs = b }) = isEqPred (varType b) + if null cycles + then return () + else if null coercion_cycles + then TcM.traceTc "Cycle in evidence binds" $ ppr cycles + else pprPanic "Cycle in coercion bindings" $ ppr coercion_cycles where - ev_binds = evBindMapBinds ev_binds_map - - cycles :: [[EvBind]] - cycles = [c | CyclicSCC c <- stronglyConnCompFromEdgedVerticesUniq edges] - - coercion_cycles = [c | c <- cycles, any is_co_bind c] - is_co_bind (EvBind { eb_lhs = b }) = isEqPred (varType b) - - edges :: [ Node EvVar EvBind ] - edges = [ DigraphNode bind bndr (nonDetEltsUniqSet (evVarsOfTerm rhs)) - | bind@(EvBind { eb_lhs = bndr, eb_rhs = rhs}) <- bagToList ev_binds ] - -- It's OK to use nonDetEltsUFM here as - -- stronglyConnCompFromEdgedVertices is still deterministic even - -- if the edges are in nondeterministic order as explained in - -- Note [Deterministic SCC] in GHC.Data.Graph.Directed. + get_edge :: EvBind -> IO (Node EvVar EvBind) + get_edge bind@(EvBind { eb_lhs = bndr, eb_rhs = rhs}) = do + vars <- evVarsOfTerm rhs + return $ DigraphNode bind bndr (nonDetEltsUniqSet vars) + -- It's OK to use nonDetEltsUFM here as + -- stronglyConnCompFromEdgedVertices is still deterministic even + -- if the edges are in nondeterministic order as explained in + -- Note [Deterministic SCC] in GHC.Data.Graph.Directed. #endif ---------------------------- @@ -1097,7 +1237,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_inerts = old_inert_var , tcs_count = count , tcs_unif_lvl = unif_lvl - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode } -> do { inerts <- TcM.readTcRef old_inert_var ; let nest_inert = inerts { inert_cycle_breakers = pushCycleBreakerVarStack @@ -1112,7 +1252,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_ev_binds = ref , tcs_unified = unified_var , tcs_inerts = new_inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = new_wl_var } ; res <- TcM.setTcLevel inner_tclvl $ thing_inside nest_env @@ -1127,7 +1267,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) #endif ; return res } -nestTcS :: TcS a -> TcS a +nestTcS :: TcS a -> TcS a -- Use the current untouchables, augmenting the current -- evidence bindings, and solved dictionaries -- But have no effect on the InertCans, or on the inert_famapp_cache ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RecursiveDo #-} module GHC.Tc.Solver.Solve ( @@ -5,6 +6,7 @@ module GHC.Tc.Solver.Solve ( solveWanteds, -- Solves WantedConstraints solveSimpleGivens, -- Solves [Ct] solveSimpleWanteds, -- Solves Cts + solveCompletelyIfRequired, setImplicationStatus ) where @@ -51,6 +53,7 @@ import GHC.Driver.Session import Data.List( deleteFirstsBy ) import Control.Monad +import Data.Foldable ( for_ ) import qualified Data.Semigroup as S import Data.Void( Void ) @@ -546,13 +549,13 @@ neededEvVars implic@(Implic { ic_given = givens = do { ev_binds <- TcS.getTcEvBindsMap ev_binds_var ; tcvs <- TcS.getTcEvTyCoVars ev_binds_var - ; let seeds1 = foldr add_implic_seeds old_needs implics - seeds2 = nonDetStrictFoldEvBindMap add_wanted seeds1 ev_binds - -- It's OK to use a non-deterministic fold here - -- because add_wanted is commutative - seeds3 = seeds2 `unionVarSet` tcvs - need_inner = findNeededEvVars ev_binds seeds3 - live_ev_binds = filterEvBindMap (needed_ev_bind need_inner) ev_binds + ; let seeds1 = foldr add_implic_seeds old_needs implics + -- It's OK to use a non-deterministic fold here + -- because add_wanted is commutative + ; seeds2 <- wrapTcS $ foldEvBindMap add_wanted (pure seeds1) ev_binds + ; let seeds3 = seeds2 `unionVarSet` tcvs + ; need_inner <- liftIO $ findNeededEvVars ev_binds seeds3 + ; let live_ev_binds = filterEvBindMap (needed_ev_bind need_inner) ev_binds need_outer = varSetMinusEvBindMap need_inner live_ev_binds `delVarSetList` givens @@ -577,10 +580,10 @@ neededEvVars implic@(Implic { ic_given = givens | EvBindGiven{} <- info = ev_var `elemVarSet` needed | otherwise = True -- Keep all wanted bindings - add_wanted :: EvBind -> VarSet -> VarSet + add_wanted :: EvBind -> TcM VarSet -> TcM VarSet add_wanted (EvBind { eb_info = info, eb_rhs = rhs }) needs | EvBindGiven{} <- info = needs -- Add the rhs vars of the Wanted bindings only - | otherwise = evVarsOfTerm rhs `unionVarSet` needs + | otherwise = unionVarSet <$> liftIO (evVarsOfTerm rhs) <*> needs ------------------------------------------------- simplifyDelayedErrors :: Bag DelayedError -> TcS (Bag DelayedError) @@ -1217,6 +1220,12 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo -- This setSrcSpan is important: the emitImplicationTcS uses that -- TcLclEnv for the implication, and that in turn sets the location -- for the Givens when solving the constraint (#21006) + + -- We are about to do something irreversible (turning a quantified constraint + -- into an implication), so wrap the inner call in solveCompletelyIfRequired + -- to ensure we can roll back if we can't solve the implication fully. + -- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. + solveCompletelyIfRequired add_inert_wanted_qc $ do { let empty_subst = mkEmptySubst $ mkInScopeSet $ tyCoVarsOfTypes (pred:theta) `delVarSetList` tvs is_qc = IsQC (ctLocOrigin loc) @@ -1251,6 +1260,10 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo ; stopWith ev "Wanted forall-constraint" } where + add_inert_wanted_qc = + do { updInertIrreds (IrredCt ev IrredShapeReason) + ; stopWith ev "Wanted QC not fully solved" + } -- Getting the size of the head is a bit horrible -- because of the special treament for class predicates get_size pred = case classifyPredType pred of @@ -1298,7 +1311,7 @@ Note [Solving a Given forall-constraint] For a Given constraint [G] df :: forall ab. (Eq a, Ord b) => C x a b we just add it to TcS's local InstEnv of known instances, -via addInertForall. Then, if we look up (C x Int Bool), say, +via addInertForAll. Then, if we look up (C x Int Bool), say, we'll find a match in the InstEnv. @@ -1539,3 +1552,123 @@ runTcPluginSolvers solvers all_cts CtWanted {} -> (givens, (ev,ct):wanteds) +-------------------------------------------------------------------------------- + +-- | If the mode is 'TcSFullySolve', attempt to fully solve the Wanted +-- constraints that arise from 'thing_inside'; returning whether this was +-- successful. +-- +-- If not in 'TcSFullySolve' mode, simply run 'thing_inside'. +-- +-- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. +solveCompletelyIfRequired :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) +solveCompletelyIfRequired not_fully_solved_action (TcS thing_inside) + = TcS $ \ env@(TcSEnv { tcs_ev_binds = outer_ev_binds_var + , tcs_unified = outer_unified_var + , tcs_inerts = outer_inert_var + , tcs_count = outer_count + , tcs_mode = mode + }) -> + case mode of + TcSFullySolve -> + do { traceTc "solveCompletelyIfRequired {" empty + -- Create a fresh environment for the inner computation + ; outer_inerts <- TcM.readTcRef outer_inert_var + ; let (outer_givens, outer_wanteds) = + partitionInerts isGivenCt outer_inerts + -- Keep the ambient Given inerts, but drop the Wanteds. + ; new_inert_var <- TcM.newTcRef outer_givens + ; new_wl_var <- TcM.newTcRef emptyWorkList + ; new_ev_binds_var <- TcM.newTcEvBinds + ; new_unified_var <- TcM.newTcRef 0 + ; new_count <- TcM.newTcRef 0 + ; new_unif_lvl <- TcM.newTcRef Nothing + + ; let + inner_env = + TcSEnv + -- KEY part: recur with TcSVanilla + { tcs_mode = TcSVanilla + + -- Use new variables for the inner computation, because + -- we may want to discard its state entirely. + , tcs_count = new_count + , tcs_unif_lvl = new_unif_lvl + , tcs_ev_binds = new_ev_binds_var + , tcs_unified = new_unified_var + , tcs_inerts = new_inert_var + , tcs_worklist = new_wl_var + } + -- Run the inner computation + ; traceTc "solveCompletelyIfRequired thing_inside {{" empty + ; r <- thing_inside inner_env + ; wl <- TcM.readTcRef new_wl_var + ; traceTc "solveCompletelyIfRequired thing_inside }}" $ + vcat [ text "work list:" <+> ppr wl ] + + -- Now attempt to solve the resulting constraints using 'solveWanteds' + ; (implics, simples) <- unTcS getUnsolvedInerts2 inner_env + ; let wc = emptyWC { wc_simple = simples, wc_impl = implics } + ; traceTc "solveCompletelyIfRequired solveWanteds" $ + vcat [ text "wc:" <+> ppr wc + ] + ; solved_wc <- unTcS (solveWanteds wc) inner_env + + ; traceTc "solveCompletelyIfRequired solveWanteds done" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc + , text "outer_givens:" <+> ppr outer_givens + , text "outer_wanteds:" <+> ppr outer_wanteds + ] + + ; if isSolvedWC solved_wc + then + do { -- The constraint was fully solved. Continue with + -- the inner solved state. + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + + -- Add new evidence bindings to the existing ones + ; inner_ev_binds <- TcM.getTcEvBindsMap new_ev_binds_var + ; outer_ev_binds <- TcM.getTcEvBindsMap outer_ev_binds_var + ; let merged_ev_binds = outer_ev_binds `unionEvBindMap` inner_ev_binds + ; TcM.setTcEvBindsMap outer_ev_binds_var merged_ev_binds + + -- Use the new inert set, adding back on the outer Wanteds + ; new_inerts <- TcM.readTcRef new_inert_var + ; let combined_cans = (new_inerts `andInertSet` outer_wanteds) + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "outer_ev_binds_var:" <+> ppr outer_ev_binds_var + , text "inner_ev_binds_var:" <+> ppr new_ev_binds_var + , text "outer_inerts" <+> ppr outer_inerts + , text "new_inerts" <+> ppr new_inerts + , text "combined_cans:" <+> ppr combined_cans + , text "inner_ev_binds:" <+> ppr inner_ev_binds + , text "outer_ev_binds:" <+> ppr outer_ev_binds + , text "merged_ev_binds:" <+> ppr merged_ev_binds + ] + ; TcM.writeTcRef outer_inert_var combined_cans + + -- Update the outer unified, count, and unif_lvl variables + ; inner_unified <- TcM.readTcRef new_unified_var + ; inner_count <- TcM.readTcRef new_count + ; inner_unif_lvl <- TcM.readTcRef new_unif_lvl + ; TcM.updTcRef outer_unified_var (+ inner_unified) + ; TcM.updTcRef outer_count (+ inner_count) + ; for_ inner_unif_lvl $ \inner_lvl -> + unTcS (setUnificationFlag inner_lvl) env + + -- No need to update the outer work list: the inner work list + -- is empty by now (after 'solveWanteds'). + ; return r } + else + do { traceTc "solveCompletelyIfRequired: unsolved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + ; -- Failed to fully solve the constraint. + -- Discard the inner solver state and continue. + ; unTcS not_fully_solved_action env + } } + _notFullySolveMode -> + thing_inside env ===================================== compiler/GHC/Tc/Solver/Solve.hs-boot ===================================== @@ -0,0 +1,6 @@ +module GHC.Tc.Solver.Solve where + +import GHC.Tc.Solver.Monad (StopOrContinue, TcS) + +solveCompletelyIfRequired + :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) ===================================== compiler/GHC/Tc/Types/Evidence.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Tc.Types.Evidence ( -- * Evidence bindings TcEvBinds(..), EvBindsVar(..), - EvBindMap(..), emptyEvBindMap, extendEvBinds, + EvBindMap(..), emptyEvBindMap, extendEvBinds, unionEvBindMap, lookupEvBind, evBindMapBinds, foldEvBindMap, nonDetStrictFoldEvBindMap, filterEvBindMap, @@ -79,14 +79,17 @@ import GHC.Utils.Outputable import GHC.Data.Bag import GHC.Data.FastString -import qualified Data.Data as Data import GHC.Types.SrcLoc -import Data.IORef( IORef ) import GHC.Types.Unique.Set import GHC.Core.Multiplicity +import qualified Data.Data as Data + +import Control.Monad (foldM) +import Data.IORef( IORef, readIORef ) import qualified Data.Semigroup as S + {- Note [TcCoercions] ~~~~~~~~~~~~~~~~~~ @@ -433,6 +436,11 @@ extendEvBinds bs ev_bind (eb_lhs ev_bind) ev_bind } +unionEvBindMap :: EvBindMap -> EvBindMap -> EvBindMap +unionEvBindMap bs1 bs2 + = EvBindMap { ev_bind_varenv = plusDVarEnv (ev_bind_varenv bs1) + (ev_bind_varenv bs2) } + isEmptyEvBindMap :: EvBindMap -> Bool isEmptyEvBindMap (EvBindMap m) = isEmptyDVarEnv m @@ -860,37 +868,74 @@ evTermCoercion tm = case evTermCoercion_maybe tm of * * ********************************************************************* -} -findNeededEvVars :: EvBindMap -> VarSet -> VarSet +findNeededEvVars :: EvBindMap -> VarSet -> IO VarSet -- Find all the Given evidence needed by seeds, -- looking transitively through binds findNeededEvVars ev_binds seeds - = transCloVarSet also_needs seeds + = transCloVarSetIO also_needs seeds where - also_needs :: VarSet -> VarSet - also_needs needs = nonDetStrictFoldUniqSet add emptyVarSet needs + also_needs :: VarSet -> IO VarSet + also_needs needs = foldM add emptyVarSet (nonDetEltsUniqSet needs) -- It's OK to use a non-deterministic fold here because we immediately -- forget about the ordering by creating a set - add :: Var -> VarSet -> VarSet - add v needs + add :: VarSet -> Var -> IO VarSet + add needs v | Just ev_bind <- lookupEvBind ev_binds v , EvBind { eb_info = EvBindGiven, eb_rhs = rhs } <- ev_bind - = evVarsOfTerm rhs `unionVarSet` needs + = do + rhs_vars <- evVarsOfTerm rhs + return (rhs_vars `unionVarSet` needs) | otherwise - = needs - -evVarsOfTerm :: EvTerm -> VarSet -evVarsOfTerm (EvExpr e) = exprSomeFreeVars isEvVar e + = return needs + +-- | Compute the transitive closure of a set in a monad +transCloVarSetIO :: (VarSet -> IO VarSet) -> VarSet -> IO VarSet +transCloVarSetIO f vs + = do + vs' <- f vs + let vs_new = vs' `minusVarSet` vs + if isEmptyVarSet vs_new + then return vs + else do + vs_rest <- transCloVarSetIO f vs_new + return (vs `unionVarSet` vs_rest) + +evVarsOfTerm :: EvTerm -> IO VarSet +evVarsOfTerm (EvExpr e) = pure $ exprSomeFreeVars isEvVar e evVarsOfTerm (EvTypeable _ ev) = evVarsOfTypeable ev -evVarsOfTerm (EvFun {}) = emptyVarSet -- See Note [Free vars of EvFun] - -evVarsOfTerms :: [EvTerm] -> VarSet -evVarsOfTerms = mapUnionVarSet evVarsOfTerm - -evVarsOfTypeable :: EvTypeable -> VarSet +evVarsOfTerm (EvFun { et_given = givens, et_binds = binds, et_body = body_id }) + = do { rhs_binds <- + case binds of + TcEvBinds (EvBindsVar { ebv_binds = ev_binds_ref }) -> + eltsUDFM . ev_bind_varenv <$> readIORef ev_binds_ref + TcEvBinds (CoEvBindsVar {}) -> + pure [] + EvBinds ev_bag -> + return $ bagToList ev_bag + ; let lhs_evvars = mkVarSet $ map eb_lhs rhs_binds + -- Get the RHS variables + ; rhs_evvars <- foldM (\acc bind -> do + vars <- evVarsOfTerm (eb_rhs bind) + pure (vars `unionVarSet` acc)) + emptyVarSet rhs_binds + -- Variables needed by the body, excluding the given variables and LHS variables + ; let needed_vars = (unitVarSet body_id `unionVarSet` rhs_evvars) + `minusVarSet` mkVarSet givens + `minusVarSet` lhs_evvars + ; pure needed_vars } + +evVarsOfTerms :: [EvTerm] -> IO VarSet +evVarsOfTerms [] = pure emptyVarSet +evVarsOfTerms (t:ts) = do + vars1 <- evVarsOfTerm t + vars2 <- evVarsOfTerms ts + pure (vars1 `unionVarSet` vars2) + +evVarsOfTypeable :: EvTypeable -> IO VarSet evVarsOfTypeable ev = case ev of - EvTypeableTyCon _ e -> mapUnionVarSet evVarsOfTerm e + EvTypeableTyCon _ e -> evVarsOfTerms e EvTypeableTyApp e1 e2 -> evVarsOfTerms [e1,e2] EvTypeableTrFun em e1 e2 -> evVarsOfTerms [em,e1,e2] EvTypeableTyLit e -> evVarsOfTerm e ===================================== testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs ===================================== @@ -17,7 +17,6 @@ import Data.Proxy f1 :: ( Num a, Eq b ) => a -> b -> Int f1 _ _ = 111 - -- Make sure we don't generate a rule with an LHS of the form -- -- forall @e (d :: Eq e). f1 @[e] ($fEqList d) = ... @@ -56,12 +55,18 @@ f3 z = z == z -------------------------------------------------------------------------------- -f4 :: Monad m => a -> m a +f4 :: (Eq a, Monad m) => a -> m a f4 = return -- Check we can deal with locally quantified variables in constraints, -- in this case 'Monad (ST s)'. -{-# SPECIALISE f4 :: b -> ST s b #-} +{-# SPECIALISE f4 :: forall s b. Eq b => b -> ST s b #-} + +f4_qc :: (Eq a, forall m. Monad m => Monad (t m)) => t m a -> () +f4_qc _ = () + +-- Like 'f4' but with a quantified constraint. +{-# SPECIALISE f4_qc :: forall r n b. (forall m. Monad m => Monad (r m)) => r n Int -> () #-} -------------------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9a61f68527d79a21c09b09be09d336db459a6dc3...34f8b5253dd1c7c8bdfe80dcfb52b2a3ceef0a94 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9a61f68527d79a21c09b09be09d336db459a6dc3...34f8b5253dd1c7c8bdfe80dcfb52b2a3ceef0a94 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/274586aa/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 13:26:10 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 07 Mar 2025 08:26:10 -0500 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Account for EvFun in evVarsOfTerm Message-ID: <67caf3f2227e9_54e9979ec587092@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: f9cec084 by sheaf at 2025-03-07T14:25:51+01:00 Account for EvFun in evVarsOfTerm evVarsOfTerm used to return an empty set in the EvFun case. This was a hack that worked around the fact that IO was required in order to collect bindings stored within evidence binding variables. Note [Free vars of EvFun] (now deleted) justified this behaviour with an explanation relating to bindings stored inside implication constraints, but this is fragile and caused evidence bindings used within EvFun bindings to be dropped in my work on implementing [GHC proposal 493](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-specialise-expressions.rst) - - - - - e35aac40 by sheaf at 2025-03-07T14:25:52+01:00 new plan from March 7 - - - - - 10 changed files: - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Types/Var/Set.hs - testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs Changes: ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -39,7 +39,7 @@ import GHC.Tc.Gen.HsType import GHC.Tc.Solver( reportUnsolvedEqualities, pushLevelAndSolveEqualitiesX , emitResidualConstraints ) import GHC.Tc.Solver.Solve( solveWanteds ) -import GHC.Tc.Solver.Monad( runTcS, runTcSWithEvBinds ) +import GHC.Tc.Solver.Monad( runTcS, runTcSFullySolve ) import GHC.Tc.Validity ( checkValidType ) import GHC.Tc.Utils.Monad @@ -761,16 +761,11 @@ This is done in three parts. (1) Typecheck the expression, capturing its constraints - (2) Clone these Wanteds, solve them, and zonk the original Wanteds. - This is the same thing that we do for RULES: see Step 1 in - Note [The SimplifyRule Plan]. + (2) Solve these constraints, but in special TcSFullySolve mode which ensures + each original Wanted is either fully solved or left untouched. + See Note [Fully solving constraints for specialisation]. - (3) Compute the constraints to quantify over. - - a. 'getRuleQuantCts' computes the initial quantification candidates - b. Filter out the fully soluble constraints; these are the constraints - we are specialising away. - See Note [Fully solving constraints for specialisation]. + (3) Compute the constraints to quantify over, using `getRuleQuantCts`. (4) Emit the residual (non-quantified) constraints, and wrap the expression in a let binding for those constraints. @@ -850,9 +845,8 @@ The conclusion is this: - fully solved (no free evidence variables), or - left untouched. -To achieve this, we quantify over all constraints that are **not fully soluble** -(see 'fullySolveCt_maybe'), although we still call 'mkMinimalBySCs' on this set -to avoid e.g. quantifying over both `Eq a` and `Ord a`. +To achieve this, we run the solver in a special "all-or-nothing" solving mode, +described in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. Note [Handling old-form SPECIALISE pragmas] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1029,40 +1023,26 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) <- tcRuleBndrs skol_info rule_bndrs $ tcInferRho spec_e - -- (2) Clone these Wanteds, solve them, and zonk the original - -- Wanteds, in order to benefit from any unifications. - - ; throwaway_ev_binds_var <- newTcEvBinds - ; spec_e_wanted_clone <- cloneWC spec_e_wanted - ; _ <- setTcLevel rhs_tclvl $ - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds spec_e_wanted_clone + -- (2) Solve the resulting wanteds in TcSFullySolve mode. + ; ev_binds_var <- newTcEvBinds + ; spec_e_wanted <- setTcLevel rhs_tclvl $ + runTcSFullySolve ev_binds_var $ + solveWanteds spec_e_wanted ; spec_e_wanted <- liftZonkM $ zonkWC spec_e_wanted -- (3) Compute which constraints to quantify over. - -- (a) Compute quantification candidates - ; ev_binds_var <- newTcEvBinds ; (quant_cands, residual_wc) <- getRuleQuantCts spec_e_wanted - -- (b) Compute fully soluble constraints - -- See Note [Fully solving constraints for specialisation] - ; traceTc "tcSpecPrag SpecSigE: computing fully soluble Wanteds {" empty - ; fully_soluble_evids <- - setTcLevel rhs_tclvl $ - mkVarSet <$> - mapMaybeM fullySolveCt_maybe (bagToList quant_cands) - ; let (fully_soluble_cts, quant_cts) = partitionBag ((`elemVarSet` fully_soluble_evids) . ctEvId) quant_cands - -- (c) Compute constraints to quantify over using 'mkMinimalBySCs' - qevs = map ctEvId (bagToList quant_cts) - ; traceTc "tcSpecPrag SpecSigE: computed fully soluble Wanteds }" (ppr fully_soluble_cts) - -- (4) Emit the residual constraints (that we are not quantifying over) ; let tv_bndrs = filter isTyVar rule_bndrs' + qevs = map ctEvId (bagToList quant_cands) ; emitResidualConstraints rhs_tclvl skol_info_anon ev_binds_var emptyVarSet tv_bndrs qevs - (residual_wc `addSimples` fully_soluble_cts) + residual_wc ; let lhs_call = mkLHsWrap (WpLet (TcEvBinds ev_binds_var)) tc_spec_e + ; ev_binds <- getTcEvBindsMap ev_binds_var + ; traceTc "tcSpecPrag SpecSigE }" $ vcat [ text "nm:" <+> ppr nm , text "rule_bndrs':" <+> ppr rule_bndrs' @@ -1070,9 +1050,11 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) , text "spec_e:" <+> ppr tc_spec_e , text "inl:" <+> ppr inl , text "spec_e_wanted:" <+> ppr spec_e_wanted - , text "quant_cts:" <+> ppr quant_cts + , text "quant_cands:" <+> ppr quant_cands , text "residual_wc:" <+> ppr residual_wc - , text "fully_soluble_wanteds:" <+> ppr fully_soluble_cts + , text (replicate 80 '-') + , text "ev_binds_var:" <+> ppr ev_binds_var + , text "ev_binds:" <+> ppr ev_binds ] -- (5) Store the results in a SpecPragE record, which will be @@ -1087,24 +1069,6 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) tcSpecPrag _ prag = pprPanic "tcSpecPrag" (ppr prag) --- | Try to fully solve a constraint. -fullySolveCt_maybe :: Ct -> TcM (Maybe EvId) -fullySolveCt_maybe ct = do - throwaway_ev_binds_var <- newTcEvBinds - res_wc <- - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds $ emptyWC { wc_simple = unitBag ct } - -- NB: don't use 'solveSimpleWanteds', as this will not - -- fully solve quantified constraints. - traceTc "fullySolveCt_maybe" $ - vcat [ text "ct:" <+> ppr ct - , text "res_wc:" <+> ppr res_wc - ] - return $ - if isSolvedWC res_wc - then Just $ ctEvId ct - else Nothing - -------------- tcSpecWrapper :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper -- A simpler variant of tcSubType, used for SPECIALISE pragmas ===================================== compiler/GHC/Tc/Solver.hs ===================================== @@ -70,6 +70,7 @@ import GHC.Data.Bag import qualified GHC.LanguageExtensions as LangExt import Control.Monad +import Data.Functor.Identity (Identity(..)) import Data.List ( partition ) import GHC.Data.Maybe ( mapMaybe ) @@ -1909,7 +1910,7 @@ growThetaTyVars :: ThetaType -> TyCoVarSet -> TyCoVarSet -- See Note [growThetaTyVars vs closeWrtFunDeps] growThetaTyVars theta tcvs | null theta = tcvs - | otherwise = transCloVarSet mk_next seed_tcvs + | otherwise = runIdentity $ transCloVarSet (Identity . mk_next) seed_tcvs where seed_tcvs = tcvs `unionVarSet` tyCoVarsOfTypes ips (ips, non_ips) = partition isIPLikePred theta ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -61,6 +61,7 @@ import Data.Void( Void ) import Control.Monad.Trans.Maybe( MaybeT, runMaybeT ) import Control.Monad.Trans.Class( lift ) import Control.Monad +import {-# SOURCE #-} GHC.Tc.Solver.Solve (solveCompletelyIfRequired) {- ********************************************************************* @@ -848,7 +849,13 @@ shortCutSolver dflags ev_w ev_i tryInstances :: DictCt -> SolverStage () tryInstances dict_ct = Stage $ do { inerts <- getInertSet - ; try_instances inerts dict_ct } + + -- We are about to do something irreversible (using an instance + -- declaration), so we wrap 'try_instances' in solveCompletelyIfRequired + -- to ensure we can roll back if we can't solve the constraint fully. + -- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. + ; solveCompletelyIfRequired (continueWith ()) $ + try_instances inerts dict_ct } try_instances :: InertSet -> DictCt -> TcS (StopOrContinue ()) -- Try to use type-class instance declarations to simplify the constraint ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -25,6 +25,7 @@ module GHC.Tc.Solver.InertSet ( InertEqs, foldTyEqs, delEq, findEq, partitionInertEqs, partitionFunEqs, + partitionInerts, andInertSet, foldFunEqs, addEqToCans, -- * Inert Dicts @@ -75,6 +76,7 @@ import GHC.Utils.Panic import GHC.Data.Bag import Control.Monad ( forM_ ) +import Data.List ( partition ) import Data.List.NonEmpty ( NonEmpty(..), (<|) ) import Data.Function ( on ) @@ -391,7 +393,6 @@ emptyInert , inert_famapp_cache = emptyFunEqs , inert_solved_dicts = emptyDictMap } - {- Note [Solved dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When we apply a top-level instance declaration, we add the "solved" @@ -2215,3 +2216,115 @@ Wrong! The level-check ensures that the inner implicit parameter wins. (Actually I think that the order in which the work-list is processed means that this chain of events won't happen, but that's very fragile.) -} + +-- | Partition the inert set according to a predicate. +partitionInerts :: (Ct -> Bool) -> InertSet -> (InertSet, InertSet) +partitionInerts pred is@(IS { inert_cans = cans }) + = (is { inert_cans = givens_cans }, is { inert_cans = wanteds_cans }) + where + -- Helper functions to convert between Ct and specific constraint types + eqPred :: EqCt -> Bool + eqPred eq = pred (CEqCan eq) + + dictPred :: DictCt -> Bool + dictPred dict = pred (CDictCan dict) + + irredPred :: IrredCt -> Bool + irredPred irred = pred (CIrredCan irred) + + qciPred :: QCInst -> Bool + qciPred qci = pred (CQuantCan qci) + + -- Partition the inert constraints + (eq_givens_list, eq_wanteds) = partitionInertEqs eqPred (inert_eqs cans) + (funeq_givens_list, funeq_wanteds) = partitionFunEqs eqPred (inert_funeqs cans) + (dict_givens_bag, dict_wanteds) = partitionDicts dictPred (inert_dicts cans) + (safehask_givens_bag, safehask_wanteds) = partitionDicts dictPred (inert_safehask cans) + (insts_givens, insts_wanteds) = partition qciPred (inert_insts cans) + (irreds_givens, irreds_wanteds) = partitionBag irredPred (inert_irreds cans) + + -- Convert lists to the appropriate container types + eq_givens = foldr addInertEqs emptyTyEqs eq_givens_list + funeq_givens = foldr addFunEqs emptyFunEqs funeq_givens_list + + givens_cans = emptyInertCans { + inert_eqs = eq_givens, + inert_funeqs = funeq_givens, + inert_dicts = dictsToDictMap dict_givens_bag, + inert_safehask = dictsToDictMap safehask_givens_bag, + inert_insts = insts_givens, + inert_irreds = irreds_givens, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + + wanteds_cans = emptyInertCans { + inert_eqs = eq_wanteds, + inert_funeqs = funeq_wanteds, + inert_dicts = dict_wanteds, + inert_safehask = safehask_wanteds, + inert_insts = insts_wanteds, + inert_irreds = irreds_wanteds, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + +-- | Convert a Bag of DictCts to a DictMap +dictsToDictMap :: Bag DictCt -> DictMap DictCt +dictsToDictMap = foldr addDict emptyDictMap . bagToList + +-- | Union two DictMaps +unionDictMap :: DictMap DictCt -> DictMap DictCt -> DictMap DictCt +unionDictMap dm1 dm2 = foldrTcAppMap addDict dm1 dm2 + +-- | Union two InertEqs +unionTyEqs :: InertEqs -> InertEqs -> InertEqs +unionTyEqs eqs1 eqs2 = foldrTyEqs addInertEqs eqs1 eqs2 + +-- | Union two InertFunEqs +unionFunEqs :: InertFunEqs -> InertFunEqs -> InertFunEqs +unionFunEqs feqs1 feqs2 = foldrFunEqs addFunEqs feqs1 feqs2 + +-- | Union two FunEqMap Reductions +unionFunEqMap :: FunEqMap Reduction -> FunEqMap Reduction -> FunEqMap Reduction +unionFunEqMap m1 m2 = foldTcAppMap (\r acc -> + let ty = reductionReducedType r + in case tcSplitTyConApp_maybe ty of + Just (tc, args) -> insertTcApp acc tc args r + Nothing -> acc) + m1 m2 + +-- | Fold over a TcAppMap with a function +foldrTcAppMap :: (a -> b -> b) -> TcAppMap a -> b -> b +foldrTcAppMap k m z = foldTcAppMap (\x acc -> k x acc) m z + +-- | Fold over FunEqs with a function +foldrFunEqs :: (EqCt -> b -> b) -> InertFunEqs -> b -> b +foldrFunEqs k feqs z = foldFunEqs (\eq acc -> k eq acc) feqs z + +-- | Fold over TyEqs with a function +foldrTyEqs :: (EqCt -> b -> b) -> InertEqs -> b -> b +foldrTyEqs k eqs z = foldTyEqs (\eq acc -> k eq acc) eqs z + +-- | Combine two 'InertSet's in a monoidal manner. +andInertSet :: InertSet -> InertSet -> InertSet +andInertSet is1 is2 + = IS { inert_cans = combinedCans, + inert_cycle_breakers = inert_cycle_breakers is1, -- Keep the first one's cycle breakers + inert_famapp_cache = unionFunEqMap (inert_famapp_cache is1) (inert_famapp_cache is2), + inert_solved_dicts = unionDictMap (inert_solved_dicts is1) (inert_solved_dicts is2) + } + where + cans1 = inert_cans is1 + cans2 = inert_cans is2 + + combinedCans = IC { + inert_eqs = unionTyEqs (inert_eqs cans1) (inert_eqs cans2), + inert_funeqs = unionFunEqs (inert_funeqs cans1) (inert_funeqs cans2), + inert_dicts = unionDictMap (inert_dicts cans1) (inert_dicts cans2), + inert_safehask = unionDictMap (inert_safehask cans1) (inert_safehask cans2), + inert_insts = inert_insts cans1 ++ inert_insts cans2, + inert_irreds = unionBags (inert_irreds cans1) (inert_irreds cans2), + inert_given_eq_lvl = maxTcLevel (inert_given_eq_lvl cans1) (inert_given_eq_lvl cans2), + inert_given_eqs = inert_given_eqs cans1 || inert_given_eqs cans2 + } ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -14,7 +14,9 @@ module GHC.Tc.Solver.Monad ( -- The TcS monad - TcS, runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + TcS(..), TcSEnv(..), TcSMode(..), + runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + runTcSFullySolve, failTcS, warnTcS, addErrTcS, wrapTcS, ctLocWarnTcS, runTcSEqualities, nestTcS, nestImplicTcS, setEvBindsTcS, @@ -71,7 +73,7 @@ module GHC.Tc.Solver.Monad ( getInertEqs, getInertCans, getInertGivens, getInertInsols, getInnermostGivenEqLevel, getInertSet, setInertSet, - getUnsolvedInerts, + getUnsolvedInerts, getUnsolvedInerts2, removeInertCts, getPendingGivenScs, insertFunEq, addInertForAll, updInertDicts, updInertIrreds, @@ -203,13 +205,14 @@ import GHC.Exts (oneShot) import Control.Monad import Data.Foldable hiding ( foldr1 ) import Data.IORef -import Data.List ( mapAccumL ) +import Data.List ( mapAccumL, unfoldr ) import Data.List.NonEmpty ( nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) import qualified Data.Semigroup as S import GHC.Types.SrcLoc import GHC.Rename.Env +--import GHC.Tc.Solver.Solve (solveWanteds) #if defined(DEBUG) import GHC.Types.Unique.Set (nonDetEltsUniqSet) @@ -705,6 +708,45 @@ getUnsolvedInerts where ct = mk_ct thing +getUnsolvedInerts2 :: TcS ( Bag Implication, Cts ) +getUnsolvedInerts2 + = do { IC { inert_eqs = tv_eqs + , inert_funeqs = fun_eqs + , inert_irreds = irreds + , inert_dicts = idicts + } <- getInertCans + + ; let unsolved_tv_eqs = foldTyEqs (add_if_unsolved CEqCan) tv_eqs emptyCts + unsolved_fun_eqs = foldFunEqs (add_if_unsolved CEqCan) fun_eqs emptyCts + unsolved_irreds = foldr (add_if_unsolved CIrredCan) emptyCts irreds + unsolved_dicts = foldDicts (add_if_unsolved CDictCan) idicts emptyCts + + ; wl_var <- getTcSWorkListRef + ; wl_curr <- readTcRef wl_var + ; implics <- getWorkListImplics + ; let wl_simpls = listToBag $ unfoldr selectWorkItem wl_curr + + ; traceTcS "getUnsolvedInerts" $ + vcat [ text " tv eqs =" <+> ppr unsolved_tv_eqs + , text "fun eqs =" <+> ppr unsolved_fun_eqs + , text "dicts =" <+> ppr unsolved_dicts + , text "irreds =" <+> ppr unsolved_irreds + , text "implics =" <+> ppr implics ] + + ; return ( implics, unsolved_tv_eqs `unionBags` + unsolved_fun_eqs `unionBags` + unsolved_irreds `unionBags` + unsolved_dicts `unionBags` + wl_simpls) } + where + add_if_unsolved :: (a -> Ct) -> a -> Cts -> Cts + add_if_unsolved mk_ct thing cts + | isWantedCt ct = ct `consCts` cts + | otherwise = cts + where + ct = mk_ct thing + + getHasGivenEqs :: TcLevel -- TcLevel of this implication -> TcS ( HasGivenEqs -- are there Given equalities? , InertIrreds ) -- Insoluble equalities arising from givens @@ -850,6 +892,31 @@ for it, so TcS carries a mutable location where the binding can be added. This is initialised from the innermost implication constraint. -} +-- | See Note [TcSMode] +data TcSMode + = TcSVanilla -- ^ Normal constraint solving + | TcSEarlyAbort -- ^ Abort early on insoluble constraints + | TcSFullySolve -- ^ Fully solve all constraints + deriving (Eq) + +{- Note [TcSMode] +~~~~~~~~~~~~~~~~~ +The constraint solver can operate in different modes: + +* TcSVanilla: Normal constraint solving mode. This is the default. + +* TcSEarlyAbort: Abort (fail in the monad) as soon as we come across an + insoluble constraint. This is used to fail-fast when checking for hole-fits. + See Note [Speeding up valid hole-fits]. + +* TcSFullySolve: Solve constraints fully or not at all. This is described in + Note [TcSFullySolve]. + + This mode is currently used in one place only: when solving constraints + arising from specialise pragmas. + See Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. +-} + data TcSEnv = TcSEnv { tcs_ev_binds :: EvBindsVar, @@ -869,13 +936,11 @@ data TcSEnv tcs_inerts :: IORef InertSet, -- Current inert set - -- Whether to throw an exception if we come across an insoluble constraint. - -- Used to fail-fast when checking for hole-fits. See Note [Speeding up - -- valid hole-fits]. - tcs_abort_on_insoluble :: Bool, + -- | The mode of operation for the constraint solver. + -- See Note [TcSMode] + tcs_mode :: TcSMode, - -- See Note [WorkList priorities] in GHC.Tc.Solver.InertSet - tcs_worklist :: IORef WorkList -- Current worklist + tcs_worklist :: IORef WorkList } --------------- @@ -946,9 +1011,9 @@ addErrTcS = wrapTcS . TcM.addErr panicTcS doc = pprPanic "GHC.Tc.Solver.Monad" doc tryEarlyAbortTcS :: TcS () --- Abort (fail in the monad) if the abort_on_insoluble flag is on +-- Abort (fail in the monad) if the mode is TcSEarlyAbort tryEarlyAbortTcS - = mkTcS (\env -> when (tcs_abort_on_insoluble env) TcM.failM) + = mkTcS (\env -> when (tcs_mode env == TcSEarlyAbort) TcM.failM) -- | Emit a warning within the 'TcS' monad at the location given by the 'CtLoc'. ctLocWarnTcS :: CtLoc -> TcRnMessage -> TcS () @@ -1018,7 +1083,60 @@ runTcS tcs runTcSEarlyAbort :: TcS a -> TcM a runTcSEarlyAbort tcs = do { ev_binds_var <- TcM.newTcEvBinds - ; runTcSWithEvBinds' True True ev_binds_var tcs } + ; runTcSWithEvBinds' True TcSEarlyAbort ev_binds_var tcs } + +-- | Run the 'TcS' monad in 'TcSFullySolve' mode, which either fully solves +-- each individual constraint or leaves it alone. See Note [TcSFullySolve]. +runTcSFullySolve :: EvBindsVar -> TcS a -> TcM a +runTcSFullySolve ev_binds_var tcs + = runTcSWithEvBinds' True TcSFullySolve ev_binds_var tcs + +{- Note [TcSFullySolve] +~~~~~~~~~~~~~~~~~~~~~~~ +The TcSFullySolve mode is a specialized constraint solving mode that guarantees +each constraint is either: + - Fully solved with no free evidence variables, or + - Left completely untouched (no simplification at all) + +Examples: + + * [W] Eq [a]. + + In TcSFullySolve mode, we **do not** simplify this constraint to [W] Eq a, + using the top-level Eq instance; instead we leave it alone as [W] Eq [a]. + + * [W] forall x. Eq x => Eq (f x). + + In TcSFullySolve mode, we **do not** process this quantified constraint by + creating a new implication constraint; we leave it alone instead. + + * [W] Eq (Maybe Int). + + This constraint is solved fully, using two top-level Eq instances. + + * [W] forall x. Eq x => Eq [x]. + + This constraint is solved fully as well, using the Eq instance for lists. + +The main observation is that, in TcSFullySolve mode, we should not take any +**irreversible** steps. We can't run instances in reverse, nor recover the +original quantified constraint from the generated implication, so in these +two cases (and these two cases only), in the solver, we call the special +function `solveCompletelyIfRequired`. This function recursively calls the +solver but in TcSVanilla mode (i.e. full-blown solving, with no restrictions). +If this recursive call manages to solve all the remaining constraints fully, +then we proceed with that outcome (i.e. we continue with that inert set, etc). +Otherwise, discard everything that happened in the recursive call, and continue +with the original constraint unchanged. + +This functionality is crucially used by the specialiser, for which such +irreversible constraint solving steps are actively harmful, as described in +Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. + +In the future, we could consider re-using this functionality for the short-cut +solver (see Note [The shortcut solver] in GHC.Tc.Solver), but we would have to +be wary of the performance implications. +-} -- | This can deal only with equality constraints. runTcSEqualities :: TcS a -> TcM a @@ -1031,7 +1149,7 @@ runTcSEqualities thing_inside runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet) runTcSInerts inerts tcs = do ev_binds_var <- TcM.newTcEvBinds - runTcSWithEvBinds' False False ev_binds_var $ do + runTcSWithEvBinds' False TcSVanilla ev_binds_var $ do setInertSet inerts a <- tcs new_inerts <- getInertSet @@ -1040,17 +1158,17 @@ runTcSInerts inerts tcs = do runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds = runTcSWithEvBinds' True False +runTcSWithEvBinds = runTcSWithEvBinds' True TcSVanilla -runTcSWithEvBinds' :: Bool -- ^ Restore type variable cycles afterwards? +runTcSWithEvBinds' :: Bool -- True <=> restore type equality cycles -- Don't if you want to reuse the InertSet. -- See also Note [Type equality cycles] -- in GHC.Tc.Solver.Equality - -> Bool + -> TcSMode -> EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs +runTcSWithEvBinds' restore_cycles mode ev_binds_var tcs = do { unified_var <- TcM.newTcRef 0 ; step_count <- TcM.newTcRef 0 ; inert_var <- TcM.newTcRef emptyInert @@ -1061,7 +1179,7 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs , tcs_unif_lvl = unif_lvl_var , tcs_count = step_count , tcs_inerts = inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = wl_var } -- Run the computation @@ -1085,29 +1203,25 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs ---------------------------- #if defined(DEBUG) checkForCyclicBinds :: EvBindMap -> TcM () -checkForCyclicBinds ev_binds_map - | null cycles - = return () - | null coercion_cycles - = TcM.traceTc "Cycle in evidence binds" $ ppr cycles - | otherwise - = pprPanic "Cycle in coercion bindings" $ ppr coercion_cycles +checkForCyclicBinds ev_binds_map = do + edges <- liftIO $ traverse get_edge (bagToList $ evBindMapBinds ev_binds_map) + let cycles = [c | CyclicSCC c <- stronglyConnCompFromEdgedVerticesUniq edges] + coercion_cycles = [c | c <- cycles, any is_co_bind c] + is_co_bind (EvBind { eb_lhs = b }) = isEqPred (varType b) + if null cycles + then return () + else if null coercion_cycles + then TcM.traceTc "Cycle in evidence binds" $ ppr cycles + else pprPanic "Cycle in coercion bindings" $ ppr coercion_cycles where - ev_binds = evBindMapBinds ev_binds_map - - cycles :: [[EvBind]] - cycles = [c | CyclicSCC c <- stronglyConnCompFromEdgedVerticesUniq edges] - - coercion_cycles = [c | c <- cycles, any is_co_bind c] - is_co_bind (EvBind { eb_lhs = b }) = isEqPred (varType b) - - edges :: [ Node EvVar EvBind ] - edges = [ DigraphNode bind bndr (nonDetEltsUniqSet (evVarsOfTerm rhs)) - | bind@(EvBind { eb_lhs = bndr, eb_rhs = rhs}) <- bagToList ev_binds ] - -- It's OK to use nonDetEltsUFM here as - -- stronglyConnCompFromEdgedVertices is still deterministic even - -- if the edges are in nondeterministic order as explained in - -- Note [Deterministic SCC] in GHC.Data.Graph.Directed. + get_edge :: EvBind -> IO (Node EvVar EvBind) + get_edge bind@(EvBind { eb_lhs = bndr, eb_rhs = rhs}) = do + vars <- evVarsOfTerm rhs + return $ DigraphNode bind bndr (nonDetEltsUniqSet vars) + -- It's OK to use nonDetEltsUFM here as + -- stronglyConnCompFromEdgedVertices is still deterministic even + -- if the edges are in nondeterministic order as explained in + -- Note [Deterministic SCC] in GHC.Data.Graph.Directed. #endif ---------------------------- @@ -1123,7 +1237,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_inerts = old_inert_var , tcs_count = count , tcs_unif_lvl = unif_lvl - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode } -> do { inerts <- TcM.readTcRef old_inert_var ; let nest_inert = inerts { inert_cycle_breakers = pushCycleBreakerVarStack @@ -1138,7 +1252,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_ev_binds = ref , tcs_unified = unified_var , tcs_inerts = new_inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = new_wl_var } ; res <- TcM.setTcLevel inner_tclvl $ thing_inside nest_env @@ -1153,7 +1267,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) #endif ; return res } -nestTcS :: TcS a -> TcS a +nestTcS :: TcS a -> TcS a -- Use the current untouchables, augmenting the current -- evidence bindings, and solved dictionaries -- But have no effect on the InertCans, or on the inert_famapp_cache ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RecursiveDo #-} module GHC.Tc.Solver.Solve ( @@ -5,6 +6,7 @@ module GHC.Tc.Solver.Solve ( solveWanteds, -- Solves WantedConstraints solveSimpleGivens, -- Solves [Ct] solveSimpleWanteds, -- Solves Cts + solveCompletelyIfRequired, setImplicationStatus ) where @@ -51,6 +53,7 @@ import GHC.Driver.Session import Data.List( deleteFirstsBy ) import Control.Monad +import Data.Foldable ( for_ ) import qualified Data.Semigroup as S import Data.Void( Void ) @@ -546,13 +549,13 @@ neededEvVars implic@(Implic { ic_given = givens = do { ev_binds <- TcS.getTcEvBindsMap ev_binds_var ; tcvs <- TcS.getTcEvTyCoVars ev_binds_var - ; let seeds1 = foldr add_implic_seeds old_needs implics - seeds2 = nonDetStrictFoldEvBindMap add_wanted seeds1 ev_binds - -- It's OK to use a non-deterministic fold here - -- because add_wanted is commutative - seeds3 = seeds2 `unionVarSet` tcvs - need_inner = findNeededEvVars ev_binds seeds3 - live_ev_binds = filterEvBindMap (needed_ev_bind need_inner) ev_binds + ; let seeds1 = foldr add_implic_seeds old_needs implics + -- It's OK to use a non-deterministic fold here + -- because add_wanted is commutative + ; seeds2 <- wrapTcS $ foldEvBindMap add_wanted (pure seeds1) ev_binds + ; let seeds3 = seeds2 `unionVarSet` tcvs + ; need_inner <- liftIO $ findNeededEvVars ev_binds seeds3 + ; let live_ev_binds = filterEvBindMap (needed_ev_bind need_inner) ev_binds need_outer = varSetMinusEvBindMap need_inner live_ev_binds `delVarSetList` givens @@ -577,10 +580,10 @@ neededEvVars implic@(Implic { ic_given = givens | EvBindGiven{} <- info = ev_var `elemVarSet` needed | otherwise = True -- Keep all wanted bindings - add_wanted :: EvBind -> VarSet -> VarSet + add_wanted :: EvBind -> TcM VarSet -> TcM VarSet add_wanted (EvBind { eb_info = info, eb_rhs = rhs }) needs | EvBindGiven{} <- info = needs -- Add the rhs vars of the Wanted bindings only - | otherwise = evVarsOfTerm rhs `unionVarSet` needs + | otherwise = unionVarSet <$> liftIO (evVarsOfTerm rhs) <*> needs ------------------------------------------------- simplifyDelayedErrors :: Bag DelayedError -> TcS (Bag DelayedError) @@ -1217,6 +1220,12 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo -- This setSrcSpan is important: the emitImplicationTcS uses that -- TcLclEnv for the implication, and that in turn sets the location -- for the Givens when solving the constraint (#21006) + + -- We are about to do something irreversible (turning a quantified constraint + -- into an implication), so wrap the inner call in solveCompletelyIfRequired + -- to ensure we can roll back if we can't solve the implication fully. + -- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. + solveCompletelyIfRequired add_inert_wanted_qc $ do { let empty_subst = mkEmptySubst $ mkInScopeSet $ tyCoVarsOfTypes (pred:theta) `delVarSetList` tvs is_qc = IsQC (ctLocOrigin loc) @@ -1251,6 +1260,10 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo ; stopWith ev "Wanted forall-constraint" } where + add_inert_wanted_qc = + do { updInertIrreds (IrredCt ev IrredShapeReason) + ; stopWith ev "Wanted QC not fully solved" + } -- Getting the size of the head is a bit horrible -- because of the special treament for class predicates get_size pred = case classifyPredType pred of @@ -1298,7 +1311,7 @@ Note [Solving a Given forall-constraint] For a Given constraint [G] df :: forall ab. (Eq a, Ord b) => C x a b we just add it to TcS's local InstEnv of known instances, -via addInertForall. Then, if we look up (C x Int Bool), say, +via addInertForAll. Then, if we look up (C x Int Bool), say, we'll find a match in the InstEnv. @@ -1539,3 +1552,123 @@ runTcPluginSolvers solvers all_cts CtWanted {} -> (givens, (ev,ct):wanteds) +-------------------------------------------------------------------------------- + +-- | If the mode is 'TcSFullySolve', attempt to fully solve the Wanted +-- constraints that arise from 'thing_inside'; returning whether this was +-- successful. +-- +-- If not in 'TcSFullySolve' mode, simply run 'thing_inside'. +-- +-- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. +solveCompletelyIfRequired :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) +solveCompletelyIfRequired not_fully_solved_action (TcS thing_inside) + = TcS $ \ env@(TcSEnv { tcs_ev_binds = outer_ev_binds_var + , tcs_unified = outer_unified_var + , tcs_inerts = outer_inert_var + , tcs_count = outer_count + , tcs_mode = mode + }) -> + case mode of + TcSFullySolve -> + do { traceTc "solveCompletelyIfRequired {" empty + -- Create a fresh environment for the inner computation + ; outer_inerts <- TcM.readTcRef outer_inert_var + ; let (outer_givens, outer_wanteds) = + partitionInerts isGivenCt outer_inerts + -- Keep the ambient Given inerts, but drop the Wanteds. + ; new_inert_var <- TcM.newTcRef outer_givens + ; new_wl_var <- TcM.newTcRef emptyWorkList + ; new_ev_binds_var <- TcM.newTcEvBinds + ; new_unified_var <- TcM.newTcRef 0 + ; new_count <- TcM.newTcRef 0 + ; new_unif_lvl <- TcM.newTcRef Nothing + + ; let + inner_env = + TcSEnv + -- KEY part: recur with TcSVanilla + { tcs_mode = TcSVanilla + + -- Use new variables for the inner computation, because + -- we may want to discard its state entirely. + , tcs_count = new_count + , tcs_unif_lvl = new_unif_lvl + , tcs_ev_binds = new_ev_binds_var + , tcs_unified = new_unified_var + , tcs_inerts = new_inert_var + , tcs_worklist = new_wl_var + } + -- Run the inner computation + ; traceTc "solveCompletelyIfRequired thing_inside {{" empty + ; r <- thing_inside inner_env + ; wl <- TcM.readTcRef new_wl_var + ; traceTc "solveCompletelyIfRequired thing_inside }}" $ + vcat [ text "work list:" <+> ppr wl ] + + -- Now attempt to solve the resulting constraints using 'solveWanteds' + ; (implics, simples) <- unTcS getUnsolvedInerts2 inner_env + ; let wc = emptyWC { wc_simple = simples, wc_impl = implics } + ; traceTc "solveCompletelyIfRequired solveWanteds" $ + vcat [ text "wc:" <+> ppr wc + ] + ; solved_wc <- unTcS (solveWanteds wc) inner_env + + ; traceTc "solveCompletelyIfRequired solveWanteds done" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc + , text "outer_givens:" <+> ppr outer_givens + , text "outer_wanteds:" <+> ppr outer_wanteds + ] + + ; if isSolvedWC solved_wc + then + do { -- The constraint was fully solved. Continue with + -- the inner solved state. + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + + -- Add new evidence bindings to the existing ones + ; inner_ev_binds <- TcM.getTcEvBindsMap new_ev_binds_var + ; outer_ev_binds <- TcM.getTcEvBindsMap outer_ev_binds_var + ; let merged_ev_binds = outer_ev_binds `unionEvBindMap` inner_ev_binds + ; TcM.setTcEvBindsMap outer_ev_binds_var merged_ev_binds + + -- Use the new inert set, adding back on the outer Wanteds + ; new_inerts <- TcM.readTcRef new_inert_var + ; let combined_cans = (new_inerts `andInertSet` outer_wanteds) + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "outer_ev_binds_var:" <+> ppr outer_ev_binds_var + , text "inner_ev_binds_var:" <+> ppr new_ev_binds_var + , text "outer_inerts" <+> ppr outer_inerts + , text "new_inerts" <+> ppr new_inerts + , text "combined_cans:" <+> ppr combined_cans + , text "inner_ev_binds:" <+> ppr inner_ev_binds + , text "outer_ev_binds:" <+> ppr outer_ev_binds + , text "merged_ev_binds:" <+> ppr merged_ev_binds + ] + ; TcM.writeTcRef outer_inert_var combined_cans + + -- Update the outer unified, count, and unif_lvl variables + ; inner_unified <- TcM.readTcRef new_unified_var + ; inner_count <- TcM.readTcRef new_count + ; inner_unif_lvl <- TcM.readTcRef new_unif_lvl + ; TcM.updTcRef outer_unified_var (+ inner_unified) + ; TcM.updTcRef outer_count (+ inner_count) + ; for_ inner_unif_lvl $ \inner_lvl -> + unTcS (setUnificationFlag inner_lvl) env + + -- No need to update the outer work list: the inner work list + -- is empty by now (after 'solveWanteds'). + ; return r } + else + do { traceTc "solveCompletelyIfRequired: unsolved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + ; -- Failed to fully solve the constraint. + -- Discard the inner solver state and continue. + ; unTcS not_fully_solved_action env + } } + _notFullySolveMode -> + thing_inside env ===================================== compiler/GHC/Tc/Solver/Solve.hs-boot ===================================== @@ -0,0 +1,6 @@ +module GHC.Tc.Solver.Solve where + +import GHC.Tc.Solver.Monad (StopOrContinue, TcS) + +solveCompletelyIfRequired + :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) ===================================== compiler/GHC/Tc/Types/Evidence.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Tc.Types.Evidence ( -- * Evidence bindings TcEvBinds(..), EvBindsVar(..), - EvBindMap(..), emptyEvBindMap, extendEvBinds, + EvBindMap(..), emptyEvBindMap, extendEvBinds, unionEvBindMap, lookupEvBind, evBindMapBinds, foldEvBindMap, nonDetStrictFoldEvBindMap, filterEvBindMap, @@ -79,14 +79,17 @@ import GHC.Utils.Outputable import GHC.Data.Bag import GHC.Data.FastString -import qualified Data.Data as Data import GHC.Types.SrcLoc -import Data.IORef( IORef ) import GHC.Types.Unique.Set import GHC.Core.Multiplicity +import qualified Data.Data as Data + +import Control.Monad (foldM) +import Data.IORef( IORef, readIORef ) import qualified Data.Semigroup as S + {- Note [TcCoercions] ~~~~~~~~~~~~~~~~~~ @@ -433,6 +436,11 @@ extendEvBinds bs ev_bind (eb_lhs ev_bind) ev_bind } +unionEvBindMap :: EvBindMap -> EvBindMap -> EvBindMap +unionEvBindMap bs1 bs2 + = EvBindMap { ev_bind_varenv = plusDVarEnv (ev_bind_varenv bs1) + (ev_bind_varenv bs2) } + isEmptyEvBindMap :: EvBindMap -> Bool isEmptyEvBindMap (EvBindMap m) = isEmptyDVarEnv m @@ -860,56 +868,68 @@ evTermCoercion tm = case evTermCoercion_maybe tm of * * ********************************************************************* -} -findNeededEvVars :: EvBindMap -> VarSet -> VarSet +findNeededEvVars :: EvBindMap -> VarSet -> IO VarSet -- Find all the Given evidence needed by seeds, -- looking transitively through binds findNeededEvVars ev_binds seeds = transCloVarSet also_needs seeds where - also_needs :: VarSet -> VarSet - also_needs needs = nonDetStrictFoldUniqSet add emptyVarSet needs + also_needs :: VarSet -> IO VarSet + also_needs needs = foldM add emptyVarSet (nonDetEltsUniqSet needs) -- It's OK to use a non-deterministic fold here because we immediately -- forget about the ordering by creating a set - add :: Var -> VarSet -> VarSet - add v needs + add :: VarSet -> Var -> IO VarSet + add needs v | Just ev_bind <- lookupEvBind ev_binds v , EvBind { eb_info = EvBindGiven, eb_rhs = rhs } <- ev_bind - = evVarsOfTerm rhs `unionVarSet` needs + = do + rhs_vars <- evVarsOfTerm rhs + return (rhs_vars `unionVarSet` needs) | otherwise - = needs + = return needs -evVarsOfTerm :: EvTerm -> VarSet -evVarsOfTerm (EvExpr e) = exprSomeFreeVars isEvVar e +evVarsOfTerm :: EvTerm -> IO VarSet +evVarsOfTerm (EvExpr e) = pure $ exprSomeFreeVars isEvVar e evVarsOfTerm (EvTypeable _ ev) = evVarsOfTypeable ev -evVarsOfTerm (EvFun {}) = emptyVarSet -- See Note [Free vars of EvFun] - -evVarsOfTerms :: [EvTerm] -> VarSet -evVarsOfTerms = mapUnionVarSet evVarsOfTerm - -evVarsOfTypeable :: EvTypeable -> VarSet +evVarsOfTerm (EvFun { et_given = givens, et_binds = binds, et_body = body_id }) + = do { rhs_binds <- + case binds of + TcEvBinds (EvBindsVar { ebv_binds = ev_binds_ref }) -> + eltsUDFM . ev_bind_varenv <$> readIORef ev_binds_ref + TcEvBinds (CoEvBindsVar {}) -> + pure [] + EvBinds ev_bag -> + return $ bagToList ev_bag + ; let lhs_evvars = mkVarSet $ map eb_lhs rhs_binds + -- Get the RHS variables + ; rhs_evvars <- foldM (\acc bind -> do + vars <- evVarsOfTerm (eb_rhs bind) + pure (vars `unionVarSet` acc)) + emptyVarSet rhs_binds + -- Variables needed by the body, excluding the given variables and LHS variables + ; let needed_vars = (unitVarSet body_id `unionVarSet` rhs_evvars) + `minusVarSet` mkVarSet givens + `minusVarSet` lhs_evvars + ; pure needed_vars } + +evVarsOfTerms :: [EvTerm] -> IO VarSet +evVarsOfTerms [] = pure emptyVarSet +evVarsOfTerms (t:ts) = do + vars1 <- evVarsOfTerm t + vars2 <- evVarsOfTerms ts + pure (vars1 `unionVarSet` vars2) + +evVarsOfTypeable :: EvTypeable -> IO VarSet evVarsOfTypeable ev = case ev of - EvTypeableTyCon _ e -> mapUnionVarSet evVarsOfTerm e + EvTypeableTyCon _ e -> evVarsOfTerms e EvTypeableTyApp e1 e2 -> evVarsOfTerms [e1,e2] EvTypeableTrFun em e1 e2 -> evVarsOfTerms [em,e1,e2] EvTypeableTyLit e -> evVarsOfTerm e -{- Note [Free vars of EvFun] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Finding the free vars of an EvFun is made tricky by the fact the -bindings et_binds may be a mutable variable. Fortunately, we -can just squeeze by. Here's how. - -* evVarsOfTerm is used only by GHC.Tc.Solver.neededEvVars. -* Each EvBindsVar in an et_binds field of an EvFun is /also/ in the - ic_binds field of an Implication -* So we can track usage via the processing for that implication, - (see Note [Tracking redundant constraints] in GHC.Tc.Solver). - We can ignore usage from the EvFun altogether. - -************************************************************************ +{- ********************************************************************* * * Pretty printing * * ===================================== compiler/GHC/Types/Var/Set.hs ===================================== @@ -168,31 +168,36 @@ fixVarSet fn vars where new_vars = fn vars -transCloVarSet :: (VarSet -> VarSet) - -- Map some variables in the set to +-- | Compute the transitive closure of a set +transCloVarSet :: forall m . Monad m + => (VarSet -> m VarSet) + -- ^ Map some variables in the set to -- extra variables that should be in it - -> VarSet -> VarSet + -> VarSet -> m VarSet -- (transCloVarSet f s) repeatedly applies f to new candidates, adding any -- new variables to s that it finds thereby, until it reaches a fixed point. -- --- The function fn could be (Var -> VarSet), but we use (VarSet -> VarSet) +-- The function fn could be (Var -> m VarSet), but we use (VarSet -> m VarSet) -- for efficiency, so that the test can be batched up. -- It's essential that fn will work fine if given new candidates -- one at a time; ie fn {v1,v2} = fn v1 `union` fn v2 -- Use fixVarSet if the function needs to see the whole set all at once -transCloVarSet fn seeds - = go seeds seeds +transCloVarSet fn seeds = go seeds seeds where go :: VarSet -- Accumulating result -> VarSet -- Work-list; un-processed subset of accumulating result - -> VarSet + -> m VarSet -- Specification: go acc vs = acc `union` transClo fn vs go acc candidates - | isEmptyVarSet new_vs = acc - | otherwise = go (acc `unionVarSet` new_vs) new_vs - where - new_vs = fn candidates `minusVarSet` acc + | isEmptyVarSet candidates = return acc + | otherwise = do + candidates' <- fn candidates + let new_vs = candidates' `minusVarSet` acc + if isEmptyVarSet new_vs + then return acc + else go (acc `unionVarSet` new_vs) new_vs +{-# INLINEABLE transCloVarSet #-} seqVarSet :: VarSet -> () seqVarSet s = s `seq` () ===================================== testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs ===================================== @@ -17,7 +17,6 @@ import Data.Proxy f1 :: ( Num a, Eq b ) => a -> b -> Int f1 _ _ = 111 - -- Make sure we don't generate a rule with an LHS of the form -- -- forall @e (d :: Eq e). f1 @[e] ($fEqList d) = ... @@ -56,12 +55,18 @@ f3 z = z == z -------------------------------------------------------------------------------- -f4 :: Monad m => a -> m a +f4 :: (Eq a, Monad m) => a -> m a f4 = return -- Check we can deal with locally quantified variables in constraints, -- in this case 'Monad (ST s)'. -{-# SPECIALISE f4 :: b -> ST s b #-} +{-# SPECIALISE f4 :: forall s b. Eq b => b -> ST s b #-} + +f4_qc :: (Eq a, forall m. Monad m => Monad (t m)) => t m a -> () +f4_qc _ = () + +-- Like 'f4' but with a quantified constraint. +{-# SPECIALISE f4_qc :: forall r n b. (forall m. Monad m => Monad (r m)) => r n Int -> () #-} -------------------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/34f8b5253dd1c7c8bdfe80dcfb52b2a3ceef0a94...e35aac40400eea45442a4315c97d1fba1f43edd0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/34f8b5253dd1c7c8bdfe80dcfb52b2a3ceef0a94...e35aac40400eea45442a4315c97d1fba1f43edd0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/fabd52d0/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 13:29:53 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 07 Mar 2025 08:29:53 -0500 Subject: [Git][ghc/ghc][wip/T24359] new plan from March 7 Message-ID: <67caf4d166ea5_54e9979ec587203e@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: dbffc28b by sheaf at 2025-03-07T14:29:39+01:00 new plan from March 7 - - - - - 8 changed files: - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Types/Evidence.hs - testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs Changes: ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -39,7 +39,7 @@ import GHC.Tc.Gen.HsType import GHC.Tc.Solver( reportUnsolvedEqualities, pushLevelAndSolveEqualitiesX , emitResidualConstraints ) import GHC.Tc.Solver.Solve( solveWanteds ) -import GHC.Tc.Solver.Monad( runTcS, runTcSWithEvBinds ) +import GHC.Tc.Solver.Monad( runTcS, runTcSFullySolve ) import GHC.Tc.Validity ( checkValidType ) import GHC.Tc.Utils.Monad @@ -761,16 +761,11 @@ This is done in three parts. (1) Typecheck the expression, capturing its constraints - (2) Clone these Wanteds, solve them, and zonk the original Wanteds. - This is the same thing that we do for RULES: see Step 1 in - Note [The SimplifyRule Plan]. + (2) Solve these constraints, but in special TcSFullySolve mode which ensures + each original Wanted is either fully solved or left untouched. + See Note [Fully solving constraints for specialisation]. - (3) Compute the constraints to quantify over. - - a. 'getRuleQuantCts' computes the initial quantification candidates - b. Filter out the fully soluble constraints; these are the constraints - we are specialising away. - See Note [Fully solving constraints for specialisation]. + (3) Compute the constraints to quantify over, using `getRuleQuantCts`. (4) Emit the residual (non-quantified) constraints, and wrap the expression in a let binding for those constraints. @@ -850,9 +845,8 @@ The conclusion is this: - fully solved (no free evidence variables), or - left untouched. -To achieve this, we quantify over all constraints that are **not fully soluble** -(see 'fullySolveCt_maybe'), although we still call 'mkMinimalBySCs' on this set -to avoid e.g. quantifying over both `Eq a` and `Ord a`. +To achieve this, we run the solver in a special "all-or-nothing" solving mode, +described in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. Note [Handling old-form SPECIALISE pragmas] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1029,40 +1023,26 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) <- tcRuleBndrs skol_info rule_bndrs $ tcInferRho spec_e - -- (2) Clone these Wanteds, solve them, and zonk the original - -- Wanteds, in order to benefit from any unifications. - - ; throwaway_ev_binds_var <- newTcEvBinds - ; spec_e_wanted_clone <- cloneWC spec_e_wanted - ; _ <- setTcLevel rhs_tclvl $ - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds spec_e_wanted_clone + -- (2) Solve the resulting wanteds in TcSFullySolve mode. + ; ev_binds_var <- newTcEvBinds + ; spec_e_wanted <- setTcLevel rhs_tclvl $ + runTcSFullySolve ev_binds_var $ + solveWanteds spec_e_wanted ; spec_e_wanted <- liftZonkM $ zonkWC spec_e_wanted -- (3) Compute which constraints to quantify over. - -- (a) Compute quantification candidates - ; ev_binds_var <- newTcEvBinds ; (quant_cands, residual_wc) <- getRuleQuantCts spec_e_wanted - -- (b) Compute fully soluble constraints - -- See Note [Fully solving constraints for specialisation] - ; traceTc "tcSpecPrag SpecSigE: computing fully soluble Wanteds {" empty - ; fully_soluble_evids <- - setTcLevel rhs_tclvl $ - mkVarSet <$> - mapMaybeM fullySolveCt_maybe (bagToList quant_cands) - ; let (fully_soluble_cts, quant_cts) = partitionBag ((`elemVarSet` fully_soluble_evids) . ctEvId) quant_cands - -- (c) Compute constraints to quantify over using 'mkMinimalBySCs' - qevs = map ctEvId (bagToList quant_cts) - ; traceTc "tcSpecPrag SpecSigE: computed fully soluble Wanteds }" (ppr fully_soluble_cts) - -- (4) Emit the residual constraints (that we are not quantifying over) ; let tv_bndrs = filter isTyVar rule_bndrs' + qevs = map ctEvId (bagToList quant_cands) ; emitResidualConstraints rhs_tclvl skol_info_anon ev_binds_var emptyVarSet tv_bndrs qevs - (residual_wc `addSimples` fully_soluble_cts) + residual_wc ; let lhs_call = mkLHsWrap (WpLet (TcEvBinds ev_binds_var)) tc_spec_e + ; ev_binds <- getTcEvBindsMap ev_binds_var + ; traceTc "tcSpecPrag SpecSigE }" $ vcat [ text "nm:" <+> ppr nm , text "rule_bndrs':" <+> ppr rule_bndrs' @@ -1070,9 +1050,11 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) , text "spec_e:" <+> ppr tc_spec_e , text "inl:" <+> ppr inl , text "spec_e_wanted:" <+> ppr spec_e_wanted - , text "quant_cts:" <+> ppr quant_cts + , text "quant_cands:" <+> ppr quant_cands , text "residual_wc:" <+> ppr residual_wc - , text "fully_soluble_wanteds:" <+> ppr fully_soluble_cts + , text (replicate 80 '-') + , text "ev_binds_var:" <+> ppr ev_binds_var + , text "ev_binds:" <+> ppr ev_binds ] -- (5) Store the results in a SpecPragE record, which will be @@ -1087,24 +1069,6 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) tcSpecPrag _ prag = pprPanic "tcSpecPrag" (ppr prag) --- | Try to fully solve a constraint. -fullySolveCt_maybe :: Ct -> TcM (Maybe EvId) -fullySolveCt_maybe ct = do - throwaway_ev_binds_var <- newTcEvBinds - res_wc <- - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds $ emptyWC { wc_simple = unitBag ct } - -- NB: don't use 'solveSimpleWanteds', as this will not - -- fully solve quantified constraints. - traceTc "fullySolveCt_maybe" $ - vcat [ text "ct:" <+> ppr ct - , text "res_wc:" <+> ppr res_wc - ] - return $ - if isSolvedWC res_wc - then Just $ ctEvId ct - else Nothing - -------------- tcSpecWrapper :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper -- A simpler variant of tcSubType, used for SPECIALISE pragmas ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -61,6 +61,7 @@ import Data.Void( Void ) import Control.Monad.Trans.Maybe( MaybeT, runMaybeT ) import Control.Monad.Trans.Class( lift ) import Control.Monad +import {-# SOURCE #-} GHC.Tc.Solver.Solve (solveCompletelyIfRequired) {- ********************************************************************* @@ -848,7 +849,13 @@ shortCutSolver dflags ev_w ev_i tryInstances :: DictCt -> SolverStage () tryInstances dict_ct = Stage $ do { inerts <- getInertSet - ; try_instances inerts dict_ct } + + -- We are about to do something irreversible (using an instance + -- declaration), so we wrap 'try_instances' in solveCompletelyIfRequired + -- to ensure we can roll back if we can't solve the constraint fully. + -- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. + ; solveCompletelyIfRequired (continueWith ()) $ + try_instances inerts dict_ct } try_instances :: InertSet -> DictCt -> TcS (StopOrContinue ()) -- Try to use type-class instance declarations to simplify the constraint ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -25,6 +25,7 @@ module GHC.Tc.Solver.InertSet ( InertEqs, foldTyEqs, delEq, findEq, partitionInertEqs, partitionFunEqs, + partitionInerts, andInertSet, foldFunEqs, addEqToCans, -- * Inert Dicts @@ -75,6 +76,7 @@ import GHC.Utils.Panic import GHC.Data.Bag import Control.Monad ( forM_ ) +import Data.List ( partition ) import Data.List.NonEmpty ( NonEmpty(..), (<|) ) import Data.Function ( on ) @@ -391,7 +393,6 @@ emptyInert , inert_famapp_cache = emptyFunEqs , inert_solved_dicts = emptyDictMap } - {- Note [Solved dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When we apply a top-level instance declaration, we add the "solved" @@ -2215,3 +2216,115 @@ Wrong! The level-check ensures that the inner implicit parameter wins. (Actually I think that the order in which the work-list is processed means that this chain of events won't happen, but that's very fragile.) -} + +-- | Partition the inert set according to a predicate. +partitionInerts :: (Ct -> Bool) -> InertSet -> (InertSet, InertSet) +partitionInerts pred is@(IS { inert_cans = cans }) + = (is { inert_cans = givens_cans }, is { inert_cans = wanteds_cans }) + where + -- Helper functions to convert between Ct and specific constraint types + eqPred :: EqCt -> Bool + eqPred eq = pred (CEqCan eq) + + dictPred :: DictCt -> Bool + dictPred dict = pred (CDictCan dict) + + irredPred :: IrredCt -> Bool + irredPred irred = pred (CIrredCan irred) + + qciPred :: QCInst -> Bool + qciPred qci = pred (CQuantCan qci) + + -- Partition the inert constraints + (eq_givens_list, eq_wanteds) = partitionInertEqs eqPred (inert_eqs cans) + (funeq_givens_list, funeq_wanteds) = partitionFunEqs eqPred (inert_funeqs cans) + (dict_givens_bag, dict_wanteds) = partitionDicts dictPred (inert_dicts cans) + (safehask_givens_bag, safehask_wanteds) = partitionDicts dictPred (inert_safehask cans) + (insts_givens, insts_wanteds) = partition qciPred (inert_insts cans) + (irreds_givens, irreds_wanteds) = partitionBag irredPred (inert_irreds cans) + + -- Convert lists to the appropriate container types + eq_givens = foldr addInertEqs emptyTyEqs eq_givens_list + funeq_givens = foldr addFunEqs emptyFunEqs funeq_givens_list + + givens_cans = emptyInertCans { + inert_eqs = eq_givens, + inert_funeqs = funeq_givens, + inert_dicts = dictsToDictMap dict_givens_bag, + inert_safehask = dictsToDictMap safehask_givens_bag, + inert_insts = insts_givens, + inert_irreds = irreds_givens, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + + wanteds_cans = emptyInertCans { + inert_eqs = eq_wanteds, + inert_funeqs = funeq_wanteds, + inert_dicts = dict_wanteds, + inert_safehask = safehask_wanteds, + inert_insts = insts_wanteds, + inert_irreds = irreds_wanteds, + inert_given_eq_lvl = inert_given_eq_lvl cans, + inert_given_eqs = inert_given_eqs cans + } + +-- | Convert a Bag of DictCts to a DictMap +dictsToDictMap :: Bag DictCt -> DictMap DictCt +dictsToDictMap = foldr addDict emptyDictMap . bagToList + +-- | Union two DictMaps +unionDictMap :: DictMap DictCt -> DictMap DictCt -> DictMap DictCt +unionDictMap dm1 dm2 = foldrTcAppMap addDict dm1 dm2 + +-- | Union two InertEqs +unionTyEqs :: InertEqs -> InertEqs -> InertEqs +unionTyEqs eqs1 eqs2 = foldrTyEqs addInertEqs eqs1 eqs2 + +-- | Union two InertFunEqs +unionFunEqs :: InertFunEqs -> InertFunEqs -> InertFunEqs +unionFunEqs feqs1 feqs2 = foldrFunEqs addFunEqs feqs1 feqs2 + +-- | Union two FunEqMap Reductions +unionFunEqMap :: FunEqMap Reduction -> FunEqMap Reduction -> FunEqMap Reduction +unionFunEqMap m1 m2 = foldTcAppMap (\r acc -> + let ty = reductionReducedType r + in case tcSplitTyConApp_maybe ty of + Just (tc, args) -> insertTcApp acc tc args r + Nothing -> acc) + m1 m2 + +-- | Fold over a TcAppMap with a function +foldrTcAppMap :: (a -> b -> b) -> TcAppMap a -> b -> b +foldrTcAppMap k m z = foldTcAppMap (\x acc -> k x acc) m z + +-- | Fold over FunEqs with a function +foldrFunEqs :: (EqCt -> b -> b) -> InertFunEqs -> b -> b +foldrFunEqs k feqs z = foldFunEqs (\eq acc -> k eq acc) feqs z + +-- | Fold over TyEqs with a function +foldrTyEqs :: (EqCt -> b -> b) -> InertEqs -> b -> b +foldrTyEqs k eqs z = foldTyEqs (\eq acc -> k eq acc) eqs z + +-- | Combine two 'InertSet's in a monoidal manner. +andInertSet :: InertSet -> InertSet -> InertSet +andInertSet is1 is2 + = IS { inert_cans = combinedCans, + inert_cycle_breakers = inert_cycle_breakers is1, -- Keep the first one's cycle breakers + inert_famapp_cache = unionFunEqMap (inert_famapp_cache is1) (inert_famapp_cache is2), + inert_solved_dicts = unionDictMap (inert_solved_dicts is1) (inert_solved_dicts is2) + } + where + cans1 = inert_cans is1 + cans2 = inert_cans is2 + + combinedCans = IC { + inert_eqs = unionTyEqs (inert_eqs cans1) (inert_eqs cans2), + inert_funeqs = unionFunEqs (inert_funeqs cans1) (inert_funeqs cans2), + inert_dicts = unionDictMap (inert_dicts cans1) (inert_dicts cans2), + inert_safehask = unionDictMap (inert_safehask cans1) (inert_safehask cans2), + inert_insts = inert_insts cans1 ++ inert_insts cans2, + inert_irreds = unionBags (inert_irreds cans1) (inert_irreds cans2), + inert_given_eq_lvl = maxTcLevel (inert_given_eq_lvl cans1) (inert_given_eq_lvl cans2), + inert_given_eqs = inert_given_eqs cans1 || inert_given_eqs cans2 + } ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -14,7 +14,9 @@ module GHC.Tc.Solver.Monad ( -- The TcS monad - TcS, runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + TcS(..), TcSEnv(..), TcSMode(..), + runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + runTcSFullySolve, failTcS, warnTcS, addErrTcS, wrapTcS, ctLocWarnTcS, runTcSEqualities, nestTcS, nestImplicTcS, setEvBindsTcS, @@ -71,7 +73,7 @@ module GHC.Tc.Solver.Monad ( getInertEqs, getInertCans, getInertGivens, getInertInsols, getInnermostGivenEqLevel, getInertSet, setInertSet, - getUnsolvedInerts, + getUnsolvedInerts, getUnsolvedInerts2, removeInertCts, getPendingGivenScs, insertFunEq, addInertForAll, updInertDicts, updInertIrreds, @@ -203,13 +205,14 @@ import GHC.Exts (oneShot) import Control.Monad import Data.Foldable hiding ( foldr1 ) import Data.IORef -import Data.List ( mapAccumL ) +import Data.List ( mapAccumL, unfoldr ) import Data.List.NonEmpty ( nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) import qualified Data.Semigroup as S import GHC.Types.SrcLoc import GHC.Rename.Env +--import GHC.Tc.Solver.Solve (solveWanteds) #if defined(DEBUG) import GHC.Types.Unique.Set (nonDetEltsUniqSet) @@ -705,6 +708,45 @@ getUnsolvedInerts where ct = mk_ct thing +getUnsolvedInerts2 :: TcS ( Bag Implication, Cts ) +getUnsolvedInerts2 + = do { IC { inert_eqs = tv_eqs + , inert_funeqs = fun_eqs + , inert_irreds = irreds + , inert_dicts = idicts + } <- getInertCans + + ; let unsolved_tv_eqs = foldTyEqs (add_if_unsolved CEqCan) tv_eqs emptyCts + unsolved_fun_eqs = foldFunEqs (add_if_unsolved CEqCan) fun_eqs emptyCts + unsolved_irreds = foldr (add_if_unsolved CIrredCan) emptyCts irreds + unsolved_dicts = foldDicts (add_if_unsolved CDictCan) idicts emptyCts + + ; wl_var <- getTcSWorkListRef + ; wl_curr <- readTcRef wl_var + ; implics <- getWorkListImplics + ; let wl_simpls = listToBag $ unfoldr selectWorkItem wl_curr + + ; traceTcS "getUnsolvedInerts" $ + vcat [ text " tv eqs =" <+> ppr unsolved_tv_eqs + , text "fun eqs =" <+> ppr unsolved_fun_eqs + , text "dicts =" <+> ppr unsolved_dicts + , text "irreds =" <+> ppr unsolved_irreds + , text "implics =" <+> ppr implics ] + + ; return ( implics, unsolved_tv_eqs `unionBags` + unsolved_fun_eqs `unionBags` + unsolved_irreds `unionBags` + unsolved_dicts `unionBags` + wl_simpls) } + where + add_if_unsolved :: (a -> Ct) -> a -> Cts -> Cts + add_if_unsolved mk_ct thing cts + | isWantedCt ct = ct `consCts` cts + | otherwise = cts + where + ct = mk_ct thing + + getHasGivenEqs :: TcLevel -- TcLevel of this implication -> TcS ( HasGivenEqs -- are there Given equalities? , InertIrreds ) -- Insoluble equalities arising from givens @@ -850,6 +892,31 @@ for it, so TcS carries a mutable location where the binding can be added. This is initialised from the innermost implication constraint. -} +-- | See Note [TcSMode] +data TcSMode + = TcSVanilla -- ^ Normal constraint solving + | TcSEarlyAbort -- ^ Abort early on insoluble constraints + | TcSFullySolve -- ^ Fully solve all constraints + deriving (Eq) + +{- Note [TcSMode] +~~~~~~~~~~~~~~~~~ +The constraint solver can operate in different modes: + +* TcSVanilla: Normal constraint solving mode. This is the default. + +* TcSEarlyAbort: Abort (fail in the monad) as soon as we come across an + insoluble constraint. This is used to fail-fast when checking for hole-fits. + See Note [Speeding up valid hole-fits]. + +* TcSFullySolve: Solve constraints fully or not at all. This is described in + Note [TcSFullySolve]. + + This mode is currently used in one place only: when solving constraints + arising from specialise pragmas. + See Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. +-} + data TcSEnv = TcSEnv { tcs_ev_binds :: EvBindsVar, @@ -869,13 +936,11 @@ data TcSEnv tcs_inerts :: IORef InertSet, -- Current inert set - -- Whether to throw an exception if we come across an insoluble constraint. - -- Used to fail-fast when checking for hole-fits. See Note [Speeding up - -- valid hole-fits]. - tcs_abort_on_insoluble :: Bool, + -- | The mode of operation for the constraint solver. + -- See Note [TcSMode] + tcs_mode :: TcSMode, - -- See Note [WorkList priorities] in GHC.Tc.Solver.InertSet - tcs_worklist :: IORef WorkList -- Current worklist + tcs_worklist :: IORef WorkList } --------------- @@ -946,9 +1011,9 @@ addErrTcS = wrapTcS . TcM.addErr panicTcS doc = pprPanic "GHC.Tc.Solver.Monad" doc tryEarlyAbortTcS :: TcS () --- Abort (fail in the monad) if the abort_on_insoluble flag is on +-- Abort (fail in the monad) if the mode is TcSEarlyAbort tryEarlyAbortTcS - = mkTcS (\env -> when (tcs_abort_on_insoluble env) TcM.failM) + = mkTcS (\env -> when (tcs_mode env == TcSEarlyAbort) TcM.failM) -- | Emit a warning within the 'TcS' monad at the location given by the 'CtLoc'. ctLocWarnTcS :: CtLoc -> TcRnMessage -> TcS () @@ -1018,7 +1083,60 @@ runTcS tcs runTcSEarlyAbort :: TcS a -> TcM a runTcSEarlyAbort tcs = do { ev_binds_var <- TcM.newTcEvBinds - ; runTcSWithEvBinds' True True ev_binds_var tcs } + ; runTcSWithEvBinds' True TcSEarlyAbort ev_binds_var tcs } + +-- | Run the 'TcS' monad in 'TcSFullySolve' mode, which either fully solves +-- each individual constraint or leaves it alone. See Note [TcSFullySolve]. +runTcSFullySolve :: EvBindsVar -> TcS a -> TcM a +runTcSFullySolve ev_binds_var tcs + = runTcSWithEvBinds' True TcSFullySolve ev_binds_var tcs + +{- Note [TcSFullySolve] +~~~~~~~~~~~~~~~~~~~~~~~ +The TcSFullySolve mode is a specialized constraint solving mode that guarantees +each constraint is either: + - Fully solved with no free evidence variables, or + - Left completely untouched (no simplification at all) + +Examples: + + * [W] Eq [a]. + + In TcSFullySolve mode, we **do not** simplify this constraint to [W] Eq a, + using the top-level Eq instance; instead we leave it alone as [W] Eq [a]. + + * [W] forall x. Eq x => Eq (f x). + + In TcSFullySolve mode, we **do not** process this quantified constraint by + creating a new implication constraint; we leave it alone instead. + + * [W] Eq (Maybe Int). + + This constraint is solved fully, using two top-level Eq instances. + + * [W] forall x. Eq x => Eq [x]. + + This constraint is solved fully as well, using the Eq instance for lists. + +The main observation is that, in TcSFullySolve mode, we should not take any +**irreversible** steps. We can't run instances in reverse, nor recover the +original quantified constraint from the generated implication, so in these +two cases (and these two cases only), in the solver, we call the special +function `solveCompletelyIfRequired`. This function recursively calls the +solver but in TcSVanilla mode (i.e. full-blown solving, with no restrictions). +If this recursive call manages to solve all the remaining constraints fully, +then we proceed with that outcome (i.e. we continue with that inert set, etc). +Otherwise, discard everything that happened in the recursive call, and continue +with the original constraint unchanged. + +This functionality is crucially used by the specialiser, for which such +irreversible constraint solving steps are actively harmful, as described in +Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. + +In the future, we could consider re-using this functionality for the short-cut +solver (see Note [Shortcut solving] in GHC.Tc.Solver.Dict), but we would have to +be wary of the performance implications. +-} -- | This can deal only with equality constraints. runTcSEqualities :: TcS a -> TcM a @@ -1031,7 +1149,7 @@ runTcSEqualities thing_inside runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet) runTcSInerts inerts tcs = do ev_binds_var <- TcM.newTcEvBinds - runTcSWithEvBinds' False False ev_binds_var $ do + runTcSWithEvBinds' False TcSVanilla ev_binds_var $ do setInertSet inerts a <- tcs new_inerts <- getInertSet @@ -1040,17 +1158,17 @@ runTcSInerts inerts tcs = do runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds = runTcSWithEvBinds' True False +runTcSWithEvBinds = runTcSWithEvBinds' True TcSVanilla -runTcSWithEvBinds' :: Bool -- ^ Restore type variable cycles afterwards? +runTcSWithEvBinds' :: Bool -- True <=> restore type equality cycles -- Don't if you want to reuse the InertSet. -- See also Note [Type equality cycles] -- in GHC.Tc.Solver.Equality - -> Bool + -> TcSMode -> EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs +runTcSWithEvBinds' restore_cycles mode ev_binds_var tcs = do { unified_var <- TcM.newTcRef 0 ; step_count <- TcM.newTcRef 0 ; inert_var <- TcM.newTcRef emptyInert @@ -1061,7 +1179,7 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs , tcs_unif_lvl = unif_lvl_var , tcs_count = step_count , tcs_inerts = inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = wl_var } -- Run the computation @@ -1119,7 +1237,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_inerts = old_inert_var , tcs_count = count , tcs_unif_lvl = unif_lvl - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode } -> do { inerts <- TcM.readTcRef old_inert_var ; let nest_inert = inerts { inert_cycle_breakers = pushCycleBreakerVarStack @@ -1134,7 +1252,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_ev_binds = ref , tcs_unified = unified_var , tcs_inerts = new_inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = new_wl_var } ; res <- TcM.setTcLevel inner_tclvl $ thing_inside nest_env @@ -1149,7 +1267,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) #endif ; return res } -nestTcS :: TcS a -> TcS a +nestTcS :: TcS a -> TcS a -- Use the current untouchables, augmenting the current -- evidence bindings, and solved dictionaries -- But have no effect on the InertCans, or on the inert_famapp_cache ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RecursiveDo #-} module GHC.Tc.Solver.Solve ( @@ -5,6 +6,7 @@ module GHC.Tc.Solver.Solve ( solveWanteds, -- Solves WantedConstraints solveSimpleGivens, -- Solves [Ct] solveSimpleWanteds, -- Solves Cts + solveCompletelyIfRequired, setImplicationStatus ) where @@ -51,6 +53,7 @@ import GHC.Driver.Session import Data.List( deleteFirstsBy ) import Control.Monad +import Data.Foldable ( for_ ) import qualified Data.Semigroup as S import Data.Void( Void ) @@ -1217,6 +1220,12 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo -- This setSrcSpan is important: the emitImplicationTcS uses that -- TcLclEnv for the implication, and that in turn sets the location -- for the Givens when solving the constraint (#21006) + + -- We are about to do something irreversible (turning a quantified constraint + -- into an implication), so wrap the inner call in solveCompletelyIfRequired + -- to ensure we can roll back if we can't solve the implication fully. + -- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. + solveCompletelyIfRequired add_inert_wanted_qc $ do { let empty_subst = mkEmptySubst $ mkInScopeSet $ tyCoVarsOfTypes (pred:theta) `delVarSetList` tvs is_qc = IsQC (ctLocOrigin loc) @@ -1251,6 +1260,10 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo ; stopWith ev "Wanted forall-constraint" } where + add_inert_wanted_qc = + do { updInertIrreds (IrredCt ev IrredShapeReason) + ; stopWith ev "Wanted QC not fully solved" + } -- Getting the size of the head is a bit horrible -- because of the special treament for class predicates get_size pred = case classifyPredType pred of @@ -1298,7 +1311,7 @@ Note [Solving a Given forall-constraint] For a Given constraint [G] df :: forall ab. (Eq a, Ord b) => C x a b we just add it to TcS's local InstEnv of known instances, -via addInertForall. Then, if we look up (C x Int Bool), say, +via addInertForAll. Then, if we look up (C x Int Bool), say, we'll find a match in the InstEnv. @@ -1539,3 +1552,123 @@ runTcPluginSolvers solvers all_cts CtWanted {} -> (givens, (ev,ct):wanteds) +-------------------------------------------------------------------------------- + +-- | If the mode is 'TcSFullySolve', attempt to fully solve the Wanted +-- constraints that arise from 'thing_inside'; returning whether this was +-- successful. +-- +-- If not in 'TcSFullySolve' mode, simply run 'thing_inside'. +-- +-- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. +solveCompletelyIfRequired :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) +solveCompletelyIfRequired not_fully_solved_action (TcS thing_inside) + = TcS $ \ env@(TcSEnv { tcs_ev_binds = outer_ev_binds_var + , tcs_unified = outer_unified_var + , tcs_inerts = outer_inert_var + , tcs_count = outer_count + , tcs_mode = mode + }) -> + case mode of + TcSFullySolve -> + do { traceTc "solveCompletelyIfRequired {" empty + -- Create a fresh environment for the inner computation + ; outer_inerts <- TcM.readTcRef outer_inert_var + ; let (outer_givens, outer_wanteds) = + partitionInerts isGivenCt outer_inerts + -- Keep the ambient Given inerts, but drop the Wanteds. + ; new_inert_var <- TcM.newTcRef outer_givens + ; new_wl_var <- TcM.newTcRef emptyWorkList + ; new_ev_binds_var <- TcM.newTcEvBinds + ; new_unified_var <- TcM.newTcRef 0 + ; new_count <- TcM.newTcRef 0 + ; new_unif_lvl <- TcM.newTcRef Nothing + + ; let + inner_env = + TcSEnv + -- KEY part: recur with TcSVanilla + { tcs_mode = TcSVanilla + + -- Use new variables for the inner computation, because + -- we may want to discard its state entirely. + , tcs_count = new_count + , tcs_unif_lvl = new_unif_lvl + , tcs_ev_binds = new_ev_binds_var + , tcs_unified = new_unified_var + , tcs_inerts = new_inert_var + , tcs_worklist = new_wl_var + } + -- Run the inner computation + ; traceTc "solveCompletelyIfRequired thing_inside {{" empty + ; r <- thing_inside inner_env + ; wl <- TcM.readTcRef new_wl_var + ; traceTc "solveCompletelyIfRequired thing_inside }}" $ + vcat [ text "work list:" <+> ppr wl ] + + -- Now attempt to solve the resulting constraints using 'solveWanteds' + ; (implics, simples) <- unTcS getUnsolvedInerts2 inner_env + ; let wc = emptyWC { wc_simple = simples, wc_impl = implics } + ; traceTc "solveCompletelyIfRequired solveWanteds" $ + vcat [ text "wc:" <+> ppr wc + ] + ; solved_wc <- unTcS (solveWanteds wc) inner_env + + ; traceTc "solveCompletelyIfRequired solveWanteds done" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc + , text "outer_givens:" <+> ppr outer_givens + , text "outer_wanteds:" <+> ppr outer_wanteds + ] + + ; if isSolvedWC solved_wc + then + do { -- The constraint was fully solved. Continue with + -- the inner solved state. + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + + -- Add new evidence bindings to the existing ones + ; inner_ev_binds <- TcM.getTcEvBindsMap new_ev_binds_var + ; outer_ev_binds <- TcM.getTcEvBindsMap outer_ev_binds_var + ; let merged_ev_binds = outer_ev_binds `unionEvBindMap` inner_ev_binds + ; TcM.setTcEvBindsMap outer_ev_binds_var merged_ev_binds + + -- Use the new inert set, adding back on the outer Wanteds + ; new_inerts <- TcM.readTcRef new_inert_var + ; let combined_cans = (new_inerts `andInertSet` outer_wanteds) + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "outer_ev_binds_var:" <+> ppr outer_ev_binds_var + , text "inner_ev_binds_var:" <+> ppr new_ev_binds_var + , text "outer_inerts" <+> ppr outer_inerts + , text "new_inerts" <+> ppr new_inerts + , text "combined_cans:" <+> ppr combined_cans + , text "inner_ev_binds:" <+> ppr inner_ev_binds + , text "outer_ev_binds:" <+> ppr outer_ev_binds + , text "merged_ev_binds:" <+> ppr merged_ev_binds + ] + ; TcM.writeTcRef outer_inert_var combined_cans + + -- Update the outer unified, count, and unif_lvl variables + ; inner_unified <- TcM.readTcRef new_unified_var + ; inner_count <- TcM.readTcRef new_count + ; inner_unif_lvl <- TcM.readTcRef new_unif_lvl + ; TcM.updTcRef outer_unified_var (+ inner_unified) + ; TcM.updTcRef outer_count (+ inner_count) + ; for_ inner_unif_lvl $ \inner_lvl -> + unTcS (setUnificationFlag inner_lvl) env + + -- No need to update the outer work list: the inner work list + -- is empty by now (after 'solveWanteds'). + ; return r } + else + do { traceTc "solveCompletelyIfRequired: unsolved }" $ + vcat [ text "wc:" <+> ppr wc + , text "solved_wc:" <+> ppr solved_wc ] + ; -- Failed to fully solve the constraint. + -- Discard the inner solver state and continue. + ; unTcS not_fully_solved_action env + } } + _notFullySolveMode -> + thing_inside env ===================================== compiler/GHC/Tc/Solver/Solve.hs-boot ===================================== @@ -0,0 +1,6 @@ +module GHC.Tc.Solver.Solve where + +import GHC.Tc.Solver.Monad (StopOrContinue, TcS) + +solveCompletelyIfRequired + :: TcS (StopOrContinue a) -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) ===================================== compiler/GHC/Tc/Types/Evidence.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Tc.Types.Evidence ( -- * Evidence bindings TcEvBinds(..), EvBindsVar(..), - EvBindMap(..), emptyEvBindMap, extendEvBinds, + EvBindMap(..), emptyEvBindMap, extendEvBinds, unionEvBindMap, lookupEvBind, evBindMapBinds, foldEvBindMap, nonDetStrictFoldEvBindMap, filterEvBindMap, ===================================== testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs ===================================== @@ -17,7 +17,6 @@ import Data.Proxy f1 :: ( Num a, Eq b ) => a -> b -> Int f1 _ _ = 111 - -- Make sure we don't generate a rule with an LHS of the form -- -- forall @e (d :: Eq e). f1 @[e] ($fEqList d) = ... @@ -56,12 +55,18 @@ f3 z = z == z -------------------------------------------------------------------------------- -f4 :: Monad m => a -> m a +f4 :: (Eq a, Monad m) => a -> m a f4 = return -- Check we can deal with locally quantified variables in constraints, -- in this case 'Monad (ST s)'. -{-# SPECIALISE f4 :: b -> ST s b #-} +{-# SPECIALISE f4 :: forall s b. Eq b => b -> ST s b #-} + +f4_qc :: (Eq a, forall m. Monad m => Monad (t m)) => t m a -> () +f4_qc _ = () + +-- Like 'f4' but with a quantified constraint. +{-# SPECIALISE f4_qc :: forall r n b. (forall m. Monad m => Monad (r m)) => r n Int -> () #-} -------------------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dbffc28b11f274baacae30224397fa09dce0bbbb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dbffc28b11f274baacae30224397fa09dce0bbbb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/9895b6e8/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 13:44:43 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 07 Mar 2025 08:44:43 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-expectJust Message-ID: <67caf84b962a6_783681a02ac859a8@gitlab.mail> Matthew Pickering pushed new branch wip/fix-expectJust at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-expectJust You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/b05c7938/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 13:48:52 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 07 Mar 2025 08:48:52 -0500 Subject: [Git][ghc/ghc][wip/t25571] 4 commits: Cmm: Add surface syntax for Word/Float bitcast ops Message-ID: <67caf94442ece_783681dd0bc9026d@gitlab.mail> Matthew Pickering pushed to branch wip/t25571 at Glasgow Haskell Compiler / GHC Commits: 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 24 changed files: - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout Changes: ===================================== compiler/GHC/Cmm/Opt.hs ===================================== @@ -19,9 +19,11 @@ import GHC.Cmm import GHC.Utils.Misc import GHC.Utils.Panic +import GHC.Utils.Outputable import GHC.Platform import Data.Maybe +import GHC.Float constantFoldNode :: Platform -> CmmNode e x -> CmmNode e x @@ -63,24 +65,51 @@ cmmMachOpFoldM _ (MO_VF_Broadcast lg _w) exprs = [CmmLit l] -> Just $! CmmLit (CmmVec $ replicate lg l) _ -> Nothing cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] - = case op of - MO_S_Neg _ -> Just $! CmmLit (CmmInt (narrowS rep (-x)) rep) - MO_Not _ -> Just $! CmmLit (CmmInt (complement x) rep) + | MO_WF_Bitcast width <- op = case width of + W32 | res <- castWord32ToFloat (fromInteger x) + -- Since we store float literals as Rationals + -- we must check for the usual tricky cases first + , not (isNegativeZero res || isNaN res || isInfinite res) + -- (round-tripping subnormals is not a problem) + , !res_rat <- toRational res + -> Just (CmmLit (CmmFloat res_rat W32)) + + W64 | res <- castWord64ToDouble (fromInteger x) + -- Since we store float literals as Rationals + -- we must check for the usual tricky cases first + , not (isNegativeZero res || isNaN res || isInfinite res) + -- (round-tripping subnormals is not a problem) + , !res_rat <- toRational res + -> Just (CmmLit (CmmFloat res_rat W64)) + + _ -> Nothing + | otherwise + = Just $! case op of + MO_S_Neg _ -> CmmLit (CmmInt (narrowS rep (-x)) rep) + MO_Not _ -> CmmLit (CmmInt (complement x) rep) -- these are interesting: we must first narrow to the -- "from" type, in order to truncate to the correct size. -- The final narrow/widen to the destination type -- is implicit in the CmmLit. - MO_SF_Round _frm to -> Just $! CmmLit (CmmFloat (fromInteger x) to) - MO_SS_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) - MO_UU_Conv from to -> Just $! CmmLit (CmmInt (narrowU from x) to) - MO_XX_Conv from to -> Just $! CmmLit (CmmInt (narrowS from x) to) - - -- Not as simply as it seems, since CmmFloat uses Rational, so skipping those - -- for now ... - MO_WF_Bitcast _w -> Nothing - MO_FW_Bitcast _w -> Nothing + MO_SF_Round _frm to -> CmmLit (CmmFloat (fromInteger x) to) + MO_SS_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + MO_UU_Conv from to -> CmmLit (CmmInt (narrowU from x) to) + MO_XX_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + + MO_F_Neg{} -> invalidArgPanic + MO_FS_Truncate{} -> invalidArgPanic + MO_FF_Conv{} -> invalidArgPanic + MO_FW_Bitcast{} -> invalidArgPanic + MO_VS_Neg{} -> invalidArgPanic + MO_VF_Neg{} -> invalidArgPanic + MO_RelaxedRead{} -> invalidArgPanic + MO_AlignmentCheck{} -> invalidArgPanic + _ -> panic $ "cmmMachOpFoldM: unknown unary op: " ++ show op + where invalidArgPanic = pprPanic "cmmMachOpFoldM" $ + text "Found" <+> pprMachOp op + <+> text "illegally applied to an int literal" -- Eliminate shifts that are wider than the shiftee cmmMachOpFoldM _ op [_shiftee, CmmLit (CmmInt shift _)] ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -1109,7 +1109,10 @@ machOps = listToUFM $ ( "f2i32", flip MO_FS_Truncate W32 ), ( "f2i64", flip MO_FS_Truncate W64 ), ( "i2f32", flip MO_SF_Round W32 ), - ( "i2f64", flip MO_SF_Round W64 ) + ( "i2f64", flip MO_SF_Round W64 ), + + ( "w2f_bitcast", MO_WF_Bitcast ), + ( "f2w_bitcast", MO_FW_Bitcast ) ] callishMachOps :: Platform -> UniqFM FastString ([CmmExpr] -> (CallishMachOp, [CmmExpr])) ===================================== compiler/GHC/Core/Opt/CallerCC/Types.hs ===================================== @@ -19,6 +19,7 @@ import GHC.Types.Name hiding (varName) import GHC.Utils.Panic import qualified GHC.Utils.Binary as B import Data.Char +import Control.DeepSeq import Language.Haskell.Syntax.Module.Name @@ -33,6 +34,11 @@ instance Outputable NamePattern where ppr (PWildcard rest) = char '*' <> ppr rest ppr PEnd = Outputable.empty +instance NFData NamePattern where + rnf (PChar c n) = rnf c `seq` rnf n + rnf (PWildcard np) = rnf np + rnf PEnd = () + instance B.Binary NamePattern where get bh = do tag <- B.get bh @@ -76,6 +82,9 @@ data CallerCcFilter , ccfFuncName :: NamePattern } +instance NFData CallerCcFilter where + rnf (CallerCcFilter mn n) = rnf mn `seq` rnf n + instance Outputable CallerCcFilter where ppr ccf = maybe (char '*') ppr (ccfModuleName ccf) ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -102,6 +102,7 @@ import GHC.Data.Maybe import GHC.Builtin.Names ( mAIN_NAME ) import GHC.Driver.Backend import GHC.Driver.Flags +import GHC.Driver.IncludeSpecs import GHC.Driver.Phases ( Phase(..), phaseInputExt ) import GHC.Driver.Plugins.External import GHC.Settings @@ -922,44 +923,6 @@ data PkgDbRef | PkgDbPath FilePath deriving Eq --- | Used to differentiate the scope an include needs to apply to. --- We have to split the include paths to avoid accidentally forcing recursive --- includes since -I overrides the system search paths. See #14312. -data IncludeSpecs - = IncludeSpecs { includePathsQuote :: [String] - , includePathsGlobal :: [String] - -- | See Note [Implicit include paths] - , includePathsQuoteImplicit :: [String] - } - deriving Show - --- | Append to the list of includes a path that shall be included using `-I` --- when the C compiler is called. These paths override system search paths. -addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs -addGlobalInclude spec paths = let f = includePathsGlobal spec - in spec { includePathsGlobal = f ++ paths } - --- | Append to the list of includes a path that shall be included using --- `-iquote` when the C compiler is called. These paths only apply when quoted --- includes are used. e.g. #include "foo.h" -addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs -addQuoteInclude spec paths = let f = includePathsQuote spec - in spec { includePathsQuote = f ++ paths } - --- | These includes are not considered while fingerprinting the flags for iface --- | See Note [Implicit include paths] -addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs -addImplicitQuoteInclude spec paths = let f = includePathsQuoteImplicit spec - in spec { includePathsQuoteImplicit = f ++ paths } - - --- | Concatenate and flatten the list of global and quoted includes returning --- just a flat list of paths. -flattenIncludes :: IncludeSpecs -> [String] -flattenIncludes specs = - includePathsQuote specs ++ - includePathsQuoteImplicit specs ++ - includePathsGlobal specs -- An argument to --reexported-module which can optionally specify a module renaming. ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -693,6 +693,7 @@ data GeneralFlag | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code | Opt_WriteSelfRecompInfo + | Opt_WriteSelfRecompFlags -- ^ Include detailed flag information for self-recompilation debugging | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/IncludeSpecs.hs ===================================== @@ -0,0 +1,48 @@ +module GHC.Driver.IncludeSpecs + ( IncludeSpecs(..) + , addGlobalInclude + , addQuoteInclude + , addImplicitQuoteInclude + , flattenIncludes + ) where + +import GHC.Prelude + +-- | Used to differentiate the scope an include needs to apply to. +-- We have to split the include paths to avoid accidentally forcing recursive +-- includes since -I overrides the system search paths. See #14312. +data IncludeSpecs + = IncludeSpecs { includePathsQuote :: [String] + , includePathsGlobal :: [String] + -- | See Note [Implicit include paths] + , includePathsQuoteImplicit :: [String] + } + deriving Show + +-- | Append to the list of includes a path that shall be included using `-I` +-- when the C compiler is called. These paths override system search paths. +addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs +addGlobalInclude spec paths = let f = includePathsGlobal spec + in spec { includePathsGlobal = f ++ paths } + +-- | Append to the list of includes a path that shall be included using +-- `-iquote` when the C compiler is called. These paths only apply when quoted +-- includes are used. e.g. #include "foo.h" +addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs +addQuoteInclude spec paths = let f = includePathsQuote spec + in spec { includePathsQuote = f ++ paths } + +-- | These includes are not considered while fingerprinting the flags for iface +-- | See Note [Implicit include paths] +addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs +addImplicitQuoteInclude spec paths = let f = includePathsQuoteImplicit spec + in spec { includePathsQuoteImplicit = f ++ paths } + + +-- | Concatenate and flatten the list of global and quoted includes returning +-- just a flat list of paths. +flattenIncludes :: IncludeSpecs -> [String] +flattenIncludes specs = + includePathsQuote specs ++ + includePathsQuoteImplicit specs ++ + includePathsGlobal specs \ No newline at end of file ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,7 +2528,8 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, - flagSpec "write-if-self-recomp" Opt_WriteSelfRecompInfo, + flagSpec "write-if-self-recomp" Opt_WriteSelfRecompInfo, + flagSpec "write-if-self-recomp-flags" Opt_WriteSelfRecompFlags, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/Iface/Env.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Iface.Env ( ifaceExportNames, - trace_if, trace_hi_diffs, + trace_if, trace_hi_diffs, trace_hi_diffs_io, -- Name-cache stuff allocateGlobalBinder, @@ -270,6 +270,12 @@ trace_if :: Logger -> SDoc -> IO () {-# INLINE trace_if #-} -- see Note [INLINE conditional tracing utilities] trace_if logger doc = when (logHasDumpFlag logger Opt_D_dump_if_trace) $ putMsg logger doc +trace_hi_diffs_io :: Logger -> IO SDoc -> IO () +{-# INLINE trace_hi_diffs_io #-} -- see Note [INLINE conditional tracing utilities] +trace_hi_diffs_io logger doc = + when (logHasDumpFlag logger Opt_D_dump_hi_diffs) $ + doc >>= putMsg logger + trace_hi_diffs :: Logger -> SDoc -> IO () {-# INLINE trace_hi_diffs #-} -- see Note [INLINE conditional tracing utilities] -trace_hi_diffs logger doc = when (logHasDumpFlag logger Opt_D_dump_hi_diffs) $ putMsg logger doc +trace_hi_diffs logger doc = trace_hi_diffs_io logger (pure doc) ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -0,0 +1,200 @@ +-- | Datatype definitions for the flag representation stored in interface files +module GHC.Iface.Flags ( + IfaceDynFlags(..) + , IfaceGeneralFlag(..) + , IfaceProfAuto(..) + , IfaceExtension(..) + , IfaceLanguage(..) + , IfaceCppOptions(..) + , pprIfaceDynFlags + , missingExtraFlagInfo + ) where + +import GHC.Prelude + +import GHC.Utils.Outputable +import Control.DeepSeq +import GHC.Utils.Fingerprint +import GHC.Utils.Binary + +import GHC.Driver.DynFlags +import GHC.Types.SafeHaskell +import GHC.Core.Opt.CallerCC.Types + +import qualified GHC.LanguageExtensions as LangExt + +-- The part of DynFlags which recompilation information needs +data IfaceDynFlags = IfaceDynFlags + { ifaceMainIs :: Maybe (Maybe String) + , ifaceSafeMode :: IfaceTrustInfo + , ifaceLang :: Maybe IfaceLanguage + , ifaceExts :: [IfaceExtension] + , ifaceCppOptions :: IfaceCppOptions + , ifaceJsOptions :: IfaceCppOptions + , ifaceCmmOptions :: IfaceCppOptions + , ifacePaths :: [String] + , ifaceProf :: Maybe IfaceProfAuto + , ifaceTicky :: [IfaceGeneralFlag] + , ifaceCodeGen :: [IfaceGeneralFlag] + , ifaceFatIface :: Bool + , ifaceDebugLevel :: Int + , ifaceCallerCCFilters :: [CallerCcFilter] + } + +pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc +pprIfaceDynFlags (f, mflags) = + vcat $ + [ text "fingerprint:" <+> (ppr f) + ] + ++ case mflags of + Nothing -> [missingExtraFlagInfo] + Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> + [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] + +missingExtraFlagInfo :: SDoc +missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" + where + -- If you modify the name of this flag, you have to modify this string. + _placeholder = Opt_WriteSelfRecompFlags + +instance Binary IfaceDynFlags where + put_ bh (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = do + put_ bh a1 + put_ bh a2 + put_ bh a3 + put_ bh a4 + put_ bh a5 + put_ bh a6 + put_ bh a7 + put_ bh a8 + put_ bh a9 + put_ bh a10 + put_ bh a11 + put_ bh a12 + put_ bh a13 + put_ bh a14 + get bh = IfaceDynFlags <$> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + +instance NFData IfaceDynFlags where + rnf (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +newtype IfaceGeneralFlag = IfaceGeneralFlag GeneralFlag + +instance NFData IfaceGeneralFlag where + rnf (IfaceGeneralFlag !_) = () + +instance Binary IfaceGeneralFlag where + put_ bh (IfaceGeneralFlag f) = put_ bh (fromEnum f) + get bh = IfaceGeneralFlag . toEnum <$> get bh + +instance Outputable IfaceGeneralFlag where + ppr (IfaceGeneralFlag f) = text (show f) + +newtype IfaceProfAuto = IfaceProfAuto ProfAuto + +instance NFData IfaceProfAuto where + rnf (IfaceProfAuto !_) = () + +instance Binary IfaceProfAuto where + put_ bh (IfaceProfAuto f) = put_ bh (fromEnum f) + get bh = IfaceProfAuto . toEnum <$> get bh + +instance Outputable IfaceProfAuto where + ppr (IfaceProfAuto f) = text (show f) + + +newtype IfaceExtension = IfaceExtension LangExt.Extension + +instance NFData IfaceExtension where + rnf (IfaceExtension !_) = () + +instance Binary IfaceExtension where + put_ bh (IfaceExtension f) = put_ bh (fromEnum f) + get bh = IfaceExtension . toEnum <$> get bh + +instance Outputable IfaceExtension where + ppr (IfaceExtension f) = text (show f) + +newtype IfaceLanguage = IfaceLanguage Language + +instance NFData IfaceLanguage where + rnf (IfaceLanguage !_) = () + +instance Binary IfaceLanguage where + put_ bh (IfaceLanguage f) = put_ bh (fromEnum f) + get bh = IfaceLanguage . toEnum <$> get bh + +instance Outputable IfaceLanguage where + ppr (IfaceLanguage f) = text (show f) + +data IfaceCppOptions = IfaceCppOptions { ifaceCppIncludes :: [FilePath] + , ifaceCppOpts :: [String] + , ifaceCppSig :: ([String], Fingerprint) + } + +instance NFData IfaceCppOptions where + rnf (IfaceCppOptions is os s) = rnf is `seq` rnf os `seq` rnf s + +instance Binary IfaceCppOptions where + put_ bh (IfaceCppOptions is os s) = do + put_ bh is + put_ bh os + put_ bh s + get bh = IfaceCppOptions <$> get bh <*> get bh <*> get bh + +instance Outputable IfaceCppOptions where + ppr (IfaceCppOptions is os (wos, fp)) = + vcat [text "includes:" + , nest 2 $ hcat (map text is) + , text "opts:" + , nest 2 $ hcat (map text os) + , text "signature:" + , nest 2 $ parens (ppr fp) <+> ppr (map (text @SDoc) wos) + + ] \ No newline at end of file ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,6 +59,7 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields +import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -1271,7 +1272,7 @@ pprModIface unit_state iface , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) , nest 2 (text "opt_hash:" <+> ppr opt_hash) , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) @@ -1310,6 +1311,7 @@ pprModIface unit_state iface pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty + {- When printing export lists, we print like this: Avail f f ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -29,8 +29,10 @@ import GHC.Driver.DynFlags import GHC.Driver.Ppr import GHC.Driver.Plugins + import GHC.Iface.Syntax import GHC.Iface.Recomp.Binary +import GHC.Iface.Recomp.Types import GHC.Iface.Load import GHC.Iface.Recomp.Flags import GHC.Iface.Env @@ -70,6 +72,8 @@ import GHC.Unit.Module.Warnings import GHC.Unit.Module.Deps import Control.Monad +import Control.Monad.Trans.State +import Control.Monad.Trans.Class import Data.List (sortBy, sort, sortOn) import qualified Data.Map as Map import qualified Data.Set as Set @@ -189,6 +193,7 @@ data RecompReason | FileChanged FilePath | CustomReason String | FlagsChanged + | LinkFlagsChanged | OptimFlagsChanged | HpcFlagsChanged | MissingBytecode @@ -201,6 +206,7 @@ data RecompReason | THWithJS deriving (Eq) + instance Outputable RecompReason where ppr = \case UnitDepRemoved uid -> ppr uid <+> text "removed" @@ -223,6 +229,7 @@ instance Outputable RecompReason where FileChanged fp -> text fp <+> text "changed" CustomReason s -> text s FlagsChanged -> text "Flags changed" + LinkFlagsChanged -> text "Flags changed" OptimFlagsChanged -> text "Optimisation flags changed" HpcFlagsChanged -> text "HPC flags changed" MissingBytecode -> text "Missing bytecode" @@ -524,13 +531,46 @@ checkHie dflags mod_summary = checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_sr_flag_hash self_recomp - new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally - case old_hash == new_hash of - True -> up_to_date logger (text "Module flags unchanged") - False -> out_of_date_hash logger FlagsChanged - (text " Module flags have changed") - old_hash new_hash + let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally + if old_fp == new_fp + then up_to_date logger (text "Module flags unchanged") + else do + -- Do not perform this computation unless -ddump-hi-diffs is on + let diffs = case old_flags of + Nothing -> pure [missingExtraFlagInfo] + Just old_flags -> checkIfaceFlags old_flags new_flags + out_of_date logger FlagsChanged (fmap vcat diffs) + + +checkIfaceFlags :: IfaceDynFlags -> IfaceDynFlags -> IO [SDoc] +checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) + (IfaceDynFlags b1 b2 b3 b4 b5 b6 b7 b8 b9 b10 b11 b12 b13 b14) = + flip execStateT [] $ do + check_one "main is" (ppr . fmap (fmap (text @SDoc))) a1 b1 + check_one_simple "safemode" a2 b2 + check_one_simple "lang" a3 b3 + check_one_simple "exts" a4 b4 + check_one_simple "cpp option" a5 b5 + check_one_simple "js option" a6 b6 + check_one_simple "cmm option" a7 b7 + check_one "paths" (ppr . map (text @SDoc)) a8 b8 + check_one_simple "prof" a9 b9 + check_one_simple "ticky" a10 b10 + check_one_simple "codegen" a11 b11 + check_one_simple "fat iface" a12 b12 + check_one_simple "debug level" a13 b13 + check_one_simple "caller cc filter" a14 b14 + where + diffSimple p a b = vcat [text "before:" <+> p a + , text "after:" <+> p b ] + + check_one_simple s a b = check_one s ppr a b + + check_one s p a b = do + a' <- lift $ computeFingerprint putNameLiterally a + b' <- lift $ computeFingerprint putNameLiterally b + if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired @@ -828,7 +868,7 @@ checkEntityUsage :: Logger checkEntityUsage logger reason new_hash (name,old_hash) = do case new_hash name of -- We used it before, but it ain't there now - Nothing -> out_of_date logger reason (sep [text "No longer exported:", ppr name]) + Nothing -> out_of_date logger reason (pure $ sep [text "No longer exported:", ppr name]) -- It's there, but is it up to date? Just (_, new_hash) | new_hash == old_hash @@ -840,12 +880,12 @@ checkEntityUsage logger reason new_hash (name,old_hash) = do up_to_date :: Logger -> SDoc -> IO RecompileRequired up_to_date logger msg = trace_hi_diffs logger msg >> return UpToDate -out_of_date :: Logger -> RecompReason -> SDoc -> IO RecompileRequired -out_of_date logger reason msg = trace_hi_diffs logger msg >> return (needsRecompileBecause reason) +out_of_date :: Logger -> RecompReason -> IO SDoc -> IO RecompileRequired +out_of_date logger reason msg = trace_hi_diffs_io logger msg >> return (needsRecompileBecause reason) out_of_date_hash :: Logger -> RecompReason -> SDoc -> Fingerprint -> Fingerprint -> IO RecompileRequired out_of_date_hash logger reason msg old_hash new_hash - = out_of_date logger reason (hsep [msg, ppr old_hash, text "->", ppr new_hash]) + = out_of_date logger reason (pure $ hsep [msg, ppr old_hash, text "->", ppr new_hash]) -- --------------------------------------------------------------------------- -- Compute fingerprints for the interface @@ -950,7 +990,7 @@ mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRec mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + dyn_flags_info <- fingerprintDynFlags hsc_env this_mod putNameLiterally opt_hash <- fingerprintOptFlags dflags putNameLiterally @@ -958,8 +998,13 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + let include_detailed_flags (flag_hash, flags) = + if gopt Opt_WriteSelfRecompFlags dflags + then (flag_hash, Just flags) + else (flag_hash, Nothing) + return (ModIfaceSelfRecomp - { mi_sr_flag_hash = flag_hash + { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash , mi_sr_plugin_hash = plugin_hash ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -19,10 +19,13 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary -import GHC.Core.Opt.CallerCC () -- for Binary instances +import GHC.Iface.Flags import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) +import Data.Maybe + +-- The subset of DynFlags which is used by the recompilation checker. -- | Produce a fingerprint of a @DynFlags@ value. We only base -- the finger print on important fields in @DynFlags@ so that @@ -32,7 +35,7 @@ import System.FilePath (normalise) -- file, not the actual 'Module' according to our 'DynFlags'. fingerprintDynFlags :: HscEnv -> Module -> (WriteBinHandle -> Name -> IO ()) - -> IO Fingerprint + -> IO (Fingerprint, IfaceDynFlags) fingerprintDynFlags hsc_env this_mod nameio = let dflags at DynFlags{..} = hsc_dflags hsc_env @@ -43,53 +46,61 @@ fingerprintDynFlags hsc_env this_mod nameio = -- oflags = sort $ filter filterOFlags $ flags dflags -- all the extension flags and the language - lang = (fmap fromEnum language, - map fromEnum $ EnumSet.toList extensionFlags) + lang = fmap IfaceLanguage language + exts = map IfaceExtension $ EnumSet.toList extensionFlags -- avoid fingerprinting the absolute path to the directory of the source file -- see Note [Implicit include paths] includePathsMinusImplicit = includePaths { includePathsQuoteImplicit = [] } -- -I, -D and -U flags affect Haskell C/CPP Preprocessor - cpp = ( map normalise $ flattenIncludes includePathsMinusImplicit - -- normalise: eliminate spurious differences due to "./foo" vs "foo" - , picPOpts dflags - , opt_P_signature dflags) + cpp = IfaceCppOptions + { ifaceCppIncludes = map normalise $ flattenIncludes includePathsMinusImplicit + -- normalise: eliminate spurious differences due to "./foo" vs "foo" + , ifaceCppOpts = picPOpts dflags + , ifaceCppSig = opt_P_signature dflags + } -- See Note [Repeated -optP hashing] + -- -I, -D and -U flags affect JavaScript C/CPP Preprocessor - js = ( map normalise $ flattenIncludes includePathsMinusImplicit + js = IfaceCppOptions + { ifaceCppIncludes = map normalise $ flattenIncludes includePathsMinusImplicit -- normalise: eliminate spurious differences due to "./foo" vs "foo" - , picPOpts dflags - , opt_JSP_signature dflags) + , ifaceCppOpts = picPOpts dflags + , ifaceCppSig = opt_JSP_signature dflags + } -- See Note [Repeated -optP hashing] -- -I, -D and -U flags affect C-- CPP Preprocessor - cmm = ( map normalise $ flattenIncludes includePathsMinusImplicit + cmm = IfaceCppOptions { + ifaceCppIncludes = map normalise $ flattenIncludes includePathsMinusImplicit -- normalise: eliminate spurious differences due to "./foo" vs "foo" - , picPOpts dflags - , opt_CmmP_signature dflags) + , ifaceCppOpts = picPOpts dflags + , ifaceCppSig = ([], opt_CmmP_signature dflags) + } -- Note [path flags and recompilation] paths = [ hcSuf ] -- -fprof-auto etc. - prof = if sccProfilingEnabled dflags then fromEnum profAuto else 0 + prof = if sccProfilingEnabled dflags then Just (IfaceProfAuto profAuto) else Nothing -- Ticky ticky = - map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk, Opt_Ticky_Tag] + mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk, Opt_Ticky_Tag] -- Other flags which affect code generation - codegen = map (`gopt` dflags) (EnumSet.toList codeGenFlags) + codegen = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) (EnumSet.toList codeGenFlags) -- Did we include core for all bindings? fat_iface = gopt Opt_WriteIfSimplifiedCore dflags - flags = ((mainis, safeHs, lang, cpp, js, cmm), (paths, prof, ticky, codegen, debugLevel, callerCcFilters, fat_iface)) + f = IfaceDynFlags mainis safeHs lang exts cpp js cmm paths prof ticky codegen fat_iface debugLevel callerCcFilters - in -- pprTrace "flags" (ppr flags) $ - computeFingerprint nameio flags + in do + fp <- computeFingerprint nameio f + return (fp, f) -- Fingerprint the optimisation info. We keep this separate from the rest of -- the flags because GHCi users (especially) may wish to ignore changes in ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,9 +1,14 @@ -module GHC.Iface.Recomp.Types ( ModIfaceSelfRecomp(..) - ) where +module GHC.Iface.Recomp.Types ( + ModIfaceSelfRecomp(..), + IfaceDynFlags(..), + pprIfaceDynFlags, + missingExtraFlagInfo, +) where import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable +import GHC.Iface.Flags import GHC.Unit.Module.Deps import GHC.Utils.Binary @@ -64,7 +69,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !Fingerprint + , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -99,7 +104,7 @@ instance Outputable ModIfaceSelfRecomp where = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash , text "usages:" <+> ppr (length mi_sr_usages) - , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash ===================================== compiler/GHC/Types/ProfAuto.hs ===================================== @@ -12,4 +12,4 @@ data ProfAuto | ProfAutoTop -- ^ top-level functions annotated only | ProfAutoExports -- ^ exported functions annotated only | ProfAutoCalls -- ^ annotate call-sites - deriving (Eq,Enum) + deriving (Eq,Enum, Show) ===================================== compiler/GHC/Types/SafeHaskell.hs ===================================== @@ -14,6 +14,7 @@ import GHC.Prelude import GHC.Utils.Binary import GHC.Utils.Outputable +import Control.DeepSeq import Data.Word @@ -31,6 +32,15 @@ data SafeHaskellMode | Sf_Ignore -- ^ @-fno-safe-haskell@ state deriving (Eq) +instance NFData SafeHaskellMode where + rnf x = case x of + Sf_None -> () + Sf_Unsafe -> () + Sf_Trustworthy -> () + Sf_Safe -> () + Sf_SafeInferred -> () + Sf_Ignore -> () + instance Show SafeHaskellMode where show Sf_None = "None" show Sf_Unsafe = "Unsafe" @@ -46,6 +56,10 @@ instance Outputable SafeHaskellMode where -- Simply a wrapper around SafeHaskellMode to separate iface and flags newtype IfaceTrustInfo = TrustInfo SafeHaskellMode +instance NFData IfaceTrustInfo where + rnf (TrustInfo shm) = rnf shm + + getSafeMode :: IfaceTrustInfo -> SafeHaskellMode getSafeMode (TrustInfo x) = x ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -103,6 +103,7 @@ import GHC.Prelude import GHC.Hs import GHC.Iface.Syntax +import GHC.Iface.Flags import GHC.Iface.Ext.Fields import GHC.Iface.Recomp.Types @@ -395,7 +396,7 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint @@ -613,7 +614,6 @@ instance Binary ModIface where }}) - emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface ===================================== compiler/ghc.cabal.in ===================================== @@ -511,6 +511,7 @@ Library GHC.Driver.Config.Tidy GHC.Driver.Config.StgToJS GHC.Driver.DynFlags + GHC.Driver.IncludeSpecs GHC.Driver.Env GHC.Driver.Env.KnotVars GHC.Driver.Env.Types @@ -609,6 +610,7 @@ Library GHC.Iface.Recomp.Types GHC.Iface.Rename GHC.Iface.Syntax + GHC.Iface.Flags GHC.Iface.Tidy GHC.Iface.Tidy.StaticPtrTable GHC.Iface.Warnings ===================================== docs/users_guide/phases.rst ===================================== @@ -705,7 +705,6 @@ Options affecting code generation .. ghc-flag:: -fwrite-if-self-recomp :shortdesc: Write information for self-recompilation checking in an interface file :type: dynamic - :category: codegen :default: on @@ -718,6 +717,14 @@ Options affecting code generation there is less chance of build paths leaking into the interface file and affecting determinism. +.. ghc-flag:: -fwrite-if-self-recomp-flags + :shortdesc: Include detailed flag information for self-recompilation checking + :type: dynamic + + Include detailed information about which flags were used during compilation + in an interface file. This makes it easier to debug issues with recompilation + by providing more context about the compilation environment. This flag is + primarily intended for debugging recompilation problems with ``-ddump-hi-diffs`` ===================================== testsuite/tests/cmm/opt/T25771.cmm ===================================== @@ -0,0 +1,8 @@ +// The point of this test is that the bitcast operations +// should be successfully constant-folded, without panicking. + +func (float64 x) { + x = %fadd(x, %w2f_bitcast(0x4028b0a3d70a3d71 :: bits64)); + x = %fadd(x, %f2f64(%w2f_bitcast(0x3f2a0000 :: bits32))); + return (x); +} ===================================== testsuite/tests/cmm/opt/T25771.stderr ===================================== @@ -0,0 +1,20 @@ + +==================== Output Cmm ==================== +[func() { // [D1] + { info_tbls: [] + stack_info: arg_space: 8 + } + {offset + c2: // global + //tick src<T25771.cmm:(4,18)-(8,1)> + //tick src<T25771.cmm:5:5-59> + //tick src<T25771.cmm:6:5-59> + _c1::F64 = D1; // CmmAssign + _c1::F64 = %MO_F_Add_W64(D1, 12.345 :: W64); // CmmAssign + D1 = %MO_F_Add_W64(_c1::F64, + %MO_FF_Conv_W32_W64(0.6640625 :: W32)); // CmmAssign + call (P64[Sp])(D1) args: 8, res: 0, upd: 8; // CmmCall + } + }] + + ===================================== testsuite/tests/cmm/opt/all.T ===================================== @@ -8,3 +8,7 @@ test('T20142', normal, compile, ['']) # We check this by telling the assembler to exit on warnings. test('T24556', [only_ways('optasm'), cmm_src], compile, ['-O -opta -Xassembler -opta --fatal-warnings']) +test('T25771', [cmm_src, only_ways(['optasm']), + grep_errmsg(r'(12\.345|0\.6640625)',[1]), + ], + compile, ['-ddump-cmm']) ===================================== testsuite/tests/codeGen/should_run/all.T ===================================== @@ -210,7 +210,9 @@ test('T16846', [only_ways(['optasm']), exit_code(1)], compile_and_run, ['']) test('T17920', [cmm_src], compile_and_run, ['']) test('T18527', req_c, compile_and_run, ['T18527FFI.c']) test('T19149', [req_c,only_ways('sanity')], compile_and_run, ['T19149_c.c']) -test('T20275', normal, compile_and_run, ['']) +test('T20275', [unless(js_arch(),extra_ways(['optasm']))], compile_and_run, ['']) + # Also tested with optimizations because + # that's the original reproducer for #25771 test('CallConv', [when(unregisterised(), skip), unless(arch('x86_64') or arch('aarch64'), skip), ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -91,6 +91,7 @@ GHC.Driver.Backend GHC.Driver.Backend.Internal GHC.Driver.DynFlags GHC.Driver.Flags +GHC.Driver.IncludeSpecs GHC.Driver.Phases GHC.Driver.Pipeline.Monad GHC.Driver.Plugins.External @@ -111,6 +112,7 @@ GHC.Hs.Type GHC.Hs.Utils GHC.Iface.Errors.Types GHC.Iface.Ext.Fields +GHC.Iface.Flags GHC.Iface.Recomp.Binary GHC.Iface.Recomp.Types GHC.Iface.Syntax ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -95,6 +95,7 @@ GHC.Driver.Backpack.Syntax GHC.Driver.DynFlags GHC.Driver.Errors.Types GHC.Driver.Flags +GHC.Driver.IncludeSpecs GHC.Driver.Phases GHC.Driver.Pipeline.Monad GHC.Driver.Plugins.External @@ -117,6 +118,7 @@ GHC.HsToCore.Errors.Types GHC.HsToCore.Pmc.Solver.Types GHC.Iface.Errors.Types GHC.Iface.Ext.Fields +GHC.Iface.Flags GHC.Iface.Recomp.Binary GHC.Iface.Recomp.Types GHC.Iface.Syntax View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/21c971e03ab175dd416b74931d245ed92d4f9634...44bf5fa13ddccacd9d91650fca6eb1dcf3f4cfb6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/21c971e03ab175dd416b74931d245ed92d4f9634...44bf5fa13ddccacd9d91650fca6eb1dcf3f4cfb6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/ea6db685/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 15:01:40 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 07 Mar 2025 10:01:40 -0500 Subject: [Git][ghc/ghc][wip/andreask/arm_mem_model] NCG: AArch64 - Add -fhuge-code-sections. Message-ID: <67cb0a54b8304_9b9ebc5c6081251@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/arm_mem_model at Glasgow Haskell Compiler / GHC Commits: a9fcf0ed by Andreas Klebinger at 2025-03-07T15:38:54+01:00 NCG: AArch64 - Add -fhuge-code-sections. When enabled the arm backend will assume jumps to targets outside of the current module are further than 128MB away. This will allow for code to work if: * The current module results in less than 128MB of code. * The whole program is loaded within a 4GB memory region. We enable this by default on mac where the lack of split sections can sometimes cause us to go over this limit - see #24648. This works around #24648 for now. ------------------------- Metric Increase: T783 ------------------------- - - - - - 7 changed files: - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-optimisation.rst Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -24,7 +24,7 @@ import GHC.Cmm.DebugBlock import GHC.CmmToAsm.Monad ( NatM, getNewRegNat , getPicBaseMaybeNat, getPlatform, getConfig - , getDebugBlock, getFileId, getNewLabelNat + , getDebugBlock, getFileId, getNewLabelNat, getThisModuleNat ) -- import GHC.CmmToAsm.Instr import GHC.CmmToAsm.PIC @@ -1505,8 +1505,16 @@ assignReg_FltCode = assignReg_IntCode -- Jumps genJump :: CmmExpr{-the branch target-} -> NatM InstrBlock -genJump expr@(CmmLit (CmmLabel lbl)) - = return $ unitOL (annExpr expr (J (TLabel lbl))) +genJump expr@(CmmLit (CmmLabel lbl)) = do + cur_mod <- getThisModuleNat + !huge_sections <- ncgEnableHugeTextSections <$> getConfig + let is_local = isLocalCLabel cur_mod lbl + + if not huge_sections || is_local + then return $ unitOL (annExpr expr (J (TLabel lbl))) + else do + (target, _format, code) <- getSomeReg expr + return (code `appOL` unitOL (annExpr expr (J (TReg target)))) genJump expr = do (target, _format, code) <- getSomeReg expr ===================================== compiler/GHC/CmmToAsm/Config.hs ===================================== @@ -47,6 +47,7 @@ data NCGConfig = NCGConfig , ncgDwarfSourceNotes :: !Bool -- ^ Enable GHC-specific source note DIEs , ncgCmmStaticPred :: !Bool -- ^ Enable static control-flow prediction , ncgEnableShortcutting :: !Bool -- ^ Enable shortcutting (don't jump to blocks only containing a jump) + , ncgEnableHugeTextSections:: !Bool -- ^ Enable use of far-jumps by default. , ncgComputeUnwinding :: !Bool -- ^ Compute block unwinding tables , ncgEnableDeadCodeElimination :: !Bool -- ^ Whether to enable the dead-code elimination } ===================================== compiler/GHC/Driver/Config/CmmToAsm.hs ===================================== @@ -70,6 +70,7 @@ initNCGConfig dflags this_mod = NCGConfig , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags , ncgCmmStaticPred = gopt Opt_CmmStaticPred dflags , ncgEnableShortcutting = gopt Opt_AsmShortcutting dflags + , ncgEnableHugeTextSections = gopt Opt_HugeCodeSections dflags , ncgComputeUnwinding = debugLevel dflags > 0 , ncgEnableDeadCodeElimination = not (gopt Opt_InfoTableMap dflags) -- Disable when -finfo-table-map is on (#20428) ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1191,6 +1191,16 @@ defaultFlags settings ++ validHoleFitDefaults + -- Platform/OS specific stuff + ++ case platformOS platform of + -- On mac in edge cases we end up with very large text sections + -- so enable HugeTextSections by default to generate jumps compatible + -- with those. + OSDarwin + | platformArch platform == ArchAArch64 + -> [Opt_HugeCodeSections] + _ -> [] + where platform = sTargetPlatform settings ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -657,6 +657,7 @@ data GeneralFlag | Opt_CmmElimCommonBlocks | Opt_CmmControlFlow | Opt_AsmShortcutting + | Opt_HugeCodeSections | Opt_OmitYields | Opt_FunToThunk -- deprecated | Opt_DictsStrict -- be strict in argument dictionaries @@ -906,6 +907,7 @@ optimisationFlags = EnumSet.fromList , Opt_CmmSink , Opt_CmmElimCommonBlocks , Opt_AsmShortcutting + , Opt_HugeCodeSections , Opt_FunToThunk , Opt_DmdTxDictSel , Opt_Loopification ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2462,6 +2462,7 @@ fFlagsDeps = [ flagSpec "gen-manifest" Opt_GenManifest, flagSpec "ghci-history" Opt_GhciHistory, flagSpec "ghci-leak-check" Opt_GhciLeakCheck, + flagSpec "huge-code-sections" Opt_HugeCodeSections, flagSpec "validate-ide-info" Opt_ValidateHie, flagGhciSpec "local-ghci-history" Opt_LocalGhciHistory, flagGhciSpec "no-it" Opt_NoIt, ===================================== docs/users_guide/using-optimisation.rst ===================================== @@ -687,6 +687,27 @@ as such you shouldn't need to set any of them explicitly. A flag ``-fno-full-laziness``. If that is inconvenient for you, please leave a comment `on the issue tracker (#21204) <https://gitlab.haskell.org/ghc/ghc/-/issues/21204>`__. +.. ghc-flag:: -fhuge-code-sections + :shortdesc: Assume code sections can be unreasonably large. + :type: dynamic + :reverse: -fno-huge-code-sections + :category: + + :default: On for AArch64 MacOS + + In particular on macOS we have sometimes seen the linker fail to properly handle insertions of jump + islands to linking of projects which large amounts of code. + + The result being code sections large enough to prevent the linker + from properly relocating jumps. (:ghc-ticket:`24648`) + + In such cases this flag forces all jumps to targets outside of the currently + compiled module to use jump variants which can deal with very large code offsets at the cost + of a little runtime performance. + + Note that this flag currently only affects the NCG AArch64 backend. + + .. ghc-flag:: -fignore-asserts :shortdesc: Ignore assertions in the source. Implied by :ghc-flag:`-O`. :type: dynamic View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a9fcf0ed8a49f03e5e89446d5f1f107273075114 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a9fcf0ed8a49f03e5e89446d5f1f107273075114 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/57a67c50/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 15:10:46 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 07 Mar 2025 10:10:46 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/remove-unused-fields Message-ID: <67cb0c75f3905_9b9eb5381a891490@gitlab.mail> Matthew Pickering pushed new branch wip/remove-unused-fields at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/remove-unused-fields You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/de95ad01/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 15:34:34 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Fri, 07 Mar 2025 10:34:34 -0500 Subject: [Git][ghc/ghc][wip/backports-9.10] mk-ghcup-metadata: Fix incorrect use of alpine() Message-ID: <67cb120a2bd98_9b9eb58901c9512b@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: b88f239e by Ben Gamari at 2025-03-07T10:31:13-05:00 mk-ghcup-metadata: Fix incorrect use of alpine() - - - - - 1 changed file: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py Changes: ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -198,7 +198,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): windows = mk(windowsArtifact) alpine3_12 = mk(alpine("3_12")) alpine3_18 = mk(alpine("3_18")) - alpine3_18_arm64 = mk(alpine("3_18"), arch='aarch64') + alpine3_18_arm64 = mk(alpine("3_18", arch='aarch64')) deb9 = mk(debian(9, "x86_64")) deb10 = mk(debian(10, "x86_64")) deb11 = mk(debian(11, "x86_64")) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b88f239e8dbb2f0a05c7745945981da2f95d4d0c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b88f239e8dbb2f0a05c7745945981da2f95d4d0c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/5cc042db/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 15:37:17 2025 From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher)) Date: Fri, 07 Mar 2025 10:37:17 -0500 Subject: [Git][ghc/ghc][wip/T18462] Multiplicity annotation on records Message-ID: <67cb12ada167d_9b9eb91486c953a4@gitlab.mail> Sjoerd Visscher pushed to branch wip/T18462 at Glasgow Haskell Compiler / GHC Commits: 1836073a by Sjoerd Visscher at 2025-03-07T16:37:09+01:00 Multiplicity annotation on records New HsConDeclField Merge HsMultAnn and HsMultAnnOn - - - - - 79 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Id/Make.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/linear_types.rst - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - + testsuite/tests/linear/should_compile/NonLinearRecord.hs - testsuite/tests/linear/should_compile/all.T - + testsuite/tests/linear/should_fail/LinearRecFieldMany.hs - + testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr - testsuite/tests/linear/should_fail/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T15279.stderr - testsuite/tests/parser/should_fail/T3811c.stderr - testsuite/tests/parser/should_fail/unpack_inside_type.stderr - testsuite/tests/printer/T18791.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/LinearTypes.html - utils/haddock/html-test/src/LinearTypes.hs - utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex - utils/haddock/latex-test/src/LinearTypes/LinearTypes.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1836073ae4ef59c4d4c75ccc0d616948c9ad4f52 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1836073ae4ef59c4d4c75ccc0d616948c9ad4f52 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/8925e643/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 15:40:16 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 07 Mar 2025 10:40:16 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/better-main Message-ID: <67cb13607c7dc_9b9eb9177d895969@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/better-main at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/better-main You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/946eb2b7/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 15:43:27 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 07 Mar 2025 10:43:27 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/testsuite_expected_window Message-ID: <67cb141f4351e_9b9ebabfce899896@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/testsuite_expected_window at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/testsuite_expected_window You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/6435b800/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 15:45:37 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 07 Mar 2025 10:45:37 -0500 Subject: [Git][ghc/ghc][wip/andreask/testsuite_expected_window] Properly describe acceptance window for stat tests. Message-ID: <67cb14a1ae366_9b9ebb97af81000be@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/testsuite_expected_window at Glasgow Haskell Compiler / GHC Commits: 33b3cb36 by Andreas Klebinger at 2025-03-07T16:21:48+01:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - 1 changed file: - testsuite/driver/perf_notes.py Changes: ===================================== testsuite/driver/perf_notes.py ===================================== @@ -162,7 +162,7 @@ class RelativeMetricAcceptanceWindow(MetricAcceptanceWindow): return (lowerBound, upperBound) def describe(self) -> str: - return '+/- %1.1f%%' % (100*self.__tol) + return '+/- %1.1f%%' % (self.__tol) def parse_perf_stat(stat_str: str) -> PerfStat: field_vals = stat_str.strip('\t').split('\t') View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/33b3cb36de411c3cd25562e50751a9e587bf7ce8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/33b3cb36de411c3cd25562e50751a9e587bf7ce8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/2cdbb234/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 15:49:18 2025 From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher)) Date: Fri, 07 Mar 2025 10:49:18 -0500 Subject: [Git][ghc/ghc][wip/T18462] Multiplicity annotation on records Message-ID: <67cb157eb931c_9b9eba7b5481040a6@gitlab.mail> Sjoerd Visscher pushed to branch wip/T18462 at Glasgow Haskell Compiler / GHC Commits: 1c5bc154 by Sjoerd Visscher at 2025-03-07T16:49:11+01:00 Multiplicity annotation on records New HsConDeclField Merge HsMultAnn and HsMultAnnOn - - - - - 79 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Id/Make.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/linear_types.rst - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - + testsuite/tests/linear/should_compile/NonLinearRecord.hs - testsuite/tests/linear/should_compile/all.T - + testsuite/tests/linear/should_fail/LinearRecFieldMany.hs - + testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr - testsuite/tests/linear/should_fail/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T15279.stderr - testsuite/tests/parser/should_fail/T3811c.stderr - testsuite/tests/parser/should_fail/unpack_inside_type.stderr - testsuite/tests/printer/T18791.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/LinearTypes.html - utils/haddock/html-test/src/LinearTypes.hs - utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex - utils/haddock/latex-test/src/LinearTypes/LinearTypes.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c5bc1544065282cedb4cf901a2d13042d4d4d45 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c5bc1544065282cedb4cf901a2d13042d4d4d45 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/fb5e926f/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 16:14:52 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 07 Mar 2025 11:14:52 -0500 Subject: [Git][ghc/ghc][wip/andreask/arm_mem_model] NCG: AArch64 - Add -finter-module-far-jumps. Message-ID: <67cb1b7c80cd8_9b9eb121414c106015@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/arm_mem_model at Glasgow Haskell Compiler / GHC Commits: 5757fbcf by Andreas Klebinger at 2025-03-07T16:52:07+01:00 NCG: AArch64 - Add -finter-module-far-jumps. When enabled the arm backend will assume jumps to targets outside of the current module are further than 128MB away. This will allow for code to work if: * The current module results in less than 128MB of code. * The whole program is loaded within a 4GB memory region. We enable this by default on mac where the lack of split sections can sometimes cause us to go over this limit - see #24648. This works around #24648 for now. ------------------------- Metric Increase: T783 ------------------------- - - - - - 7 changed files: - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-optimisation.rst Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -24,7 +24,7 @@ import GHC.Cmm.DebugBlock import GHC.CmmToAsm.Monad ( NatM, getNewRegNat , getPicBaseMaybeNat, getPlatform, getConfig - , getDebugBlock, getFileId, getNewLabelNat + , getDebugBlock, getFileId, getNewLabelNat, getThisModuleNat ) -- import GHC.CmmToAsm.Instr import GHC.CmmToAsm.PIC @@ -1505,8 +1505,19 @@ assignReg_FltCode = assignReg_IntCode -- Jumps genJump :: CmmExpr{-the branch target-} -> NatM InstrBlock -genJump expr@(CmmLit (CmmLabel lbl)) - = return $ unitOL (annExpr expr (J (TLabel lbl))) +genJump expr@(CmmLit (CmmLabel lbl)) = do + cur_mod <- getThisModuleNat + !useFarJumps <- ncgEnableInterModuleFarJumps <$> getConfig + let is_local = isLocalCLabel cur_mod lbl + + -- We prefer to generate a near jump using a simble `B` instruction + -- with a range (+/-128MB). But if the target is outside the current module + -- we might have to account for large code offsets. (#24648) + if not useFarJumps || is_local + then return $ unitOL (annExpr expr (J (TLabel lbl))) + else do + (target, _format, code) <- getSomeReg expr + return (code `appOL` unitOL (annExpr expr (J (TReg target)))) genJump expr = do (target, _format, code) <- getSomeReg expr ===================================== compiler/GHC/CmmToAsm/Config.hs ===================================== @@ -47,6 +47,7 @@ data NCGConfig = NCGConfig , ncgDwarfSourceNotes :: !Bool -- ^ Enable GHC-specific source note DIEs , ncgCmmStaticPred :: !Bool -- ^ Enable static control-flow prediction , ncgEnableShortcutting :: !Bool -- ^ Enable shortcutting (don't jump to blocks only containing a jump) + , ncgEnableInterModuleFarJumps:: !Bool -- ^ Use far-jumps for cross-module jumps. , ncgComputeUnwinding :: !Bool -- ^ Compute block unwinding tables , ncgEnableDeadCodeElimination :: !Bool -- ^ Whether to enable the dead-code elimination } ===================================== compiler/GHC/Driver/Config/CmmToAsm.hs ===================================== @@ -70,6 +70,7 @@ initNCGConfig dflags this_mod = NCGConfig , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags , ncgCmmStaticPred = gopt Opt_CmmStaticPred dflags , ncgEnableShortcutting = gopt Opt_AsmShortcutting dflags + , ncgEnableInterModuleFarJumps = gopt Opt_InterModuleFarJumps dflags , ncgComputeUnwinding = debugLevel dflags > 0 , ncgEnableDeadCodeElimination = not (gopt Opt_InfoTableMap dflags) -- Disable when -finfo-table-map is on (#20428) ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1191,6 +1191,17 @@ defaultFlags settings ++ validHoleFitDefaults + -- Platform/OS specific stuff + ++ case platformOS platform of + -- On mac naturally the linker is broken for jumps with very large + -- offsets. (#24648) So we enable HugeTextSections by default to generate + -- far jumps when crossing module boundries instead. As these don't rely + -- on linker fixups. + OSDarwin + | platformArch platform == ArchAArch64 + -> [Opt_InterModuleFarJumps] + _ -> [] + where platform = sTargetPlatform settings ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -657,6 +657,7 @@ data GeneralFlag | Opt_CmmElimCommonBlocks | Opt_CmmControlFlow | Opt_AsmShortcutting + | Opt_InterModuleFarJumps | Opt_OmitYields | Opt_FunToThunk -- deprecated | Opt_DictsStrict -- be strict in argument dictionaries @@ -906,6 +907,7 @@ optimisationFlags = EnumSet.fromList , Opt_CmmSink , Opt_CmmElimCommonBlocks , Opt_AsmShortcutting + , Opt_InterModuleFarJumps , Opt_FunToThunk , Opt_DmdTxDictSel , Opt_Loopification ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2462,6 +2462,7 @@ fFlagsDeps = [ flagSpec "gen-manifest" Opt_GenManifest, flagSpec "ghci-history" Opt_GhciHistory, flagSpec "ghci-leak-check" Opt_GhciLeakCheck, + flagSpec "inter-module-far-jumps" Opt_InterModuleFarJumps, flagSpec "validate-ide-info" Opt_ValidateHie, flagGhciSpec "local-ghci-history" Opt_LocalGhciHistory, flagGhciSpec "no-it" Opt_NoIt, ===================================== docs/users_guide/using-optimisation.rst ===================================== @@ -687,6 +687,22 @@ as such you shouldn't need to set any of them explicitly. A flag ``-fno-full-laziness``. If that is inconvenient for you, please leave a comment `on the issue tracker (#21204) <https://gitlab.haskell.org/ghc/ghc/-/issues/21204>`__. +.. ghc-flag:: -finter-module-far-jumps + :shortdesc: Assume code sections can be very large. + :type: dynamic + :reverse: -fno-inter-module-far-jumps + :category: + + :default: On for AArch64 MacOS + + This flag forces GHC to use far jumps instead of near jumps for all jumps + which cross module boundries. This removes the need for jump islands/linker + jump fixups which some linkers struggle to deal with. (:ghc-ticket:`24648`) + + This comes at a very modest code size/runtime overhead. Note that this flag + currently only affects the NCG AArch64 backend. + + .. ghc-flag:: -fignore-asserts :shortdesc: Ignore assertions in the source. Implied by :ghc-flag:`-O`. :type: dynamic View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5757fbcf88911bf4249eef0633528c3258a36d49 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5757fbcf88911bf4249eef0633528c3258a36d49 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/9f82e373/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 16:16:14 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 07 Mar 2025 11:16:14 -0500 Subject: [Git][ghc/ghc][wip/andreask/arm_mem_model] NCG: AArch64 - Add -finter-module-far-jumps. Message-ID: <67cb1bce43990_9b9eb1219d7c107992@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/arm_mem_model at Glasgow Haskell Compiler / GHC Commits: 7b13d63b by Andreas Klebinger at 2025-03-07T16:54:06+01:00 NCG: AArch64 - Add -finter-module-far-jumps. When enabled the arm backend will assume jumps to targets outside of the current module are further than 128MB away. This will allow for code to work if: * The current module results in less than 128MB of code. * The whole program is loaded within a 4GB memory region. We enable this by default on mac where the lack of split sections can sometimes cause us to go over this limit - see #24648. This works around #24648 for now. ------------------------- Metric Increase: T783 ------------------------- - - - - - 7 changed files: - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-optimisation.rst Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -24,7 +24,7 @@ import GHC.Cmm.DebugBlock import GHC.CmmToAsm.Monad ( NatM, getNewRegNat , getPicBaseMaybeNat, getPlatform, getConfig - , getDebugBlock, getFileId, getNewLabelNat + , getDebugBlock, getFileId, getNewLabelNat, getThisModuleNat ) -- import GHC.CmmToAsm.Instr import GHC.CmmToAsm.PIC @@ -1505,8 +1505,19 @@ assignReg_FltCode = assignReg_IntCode -- Jumps genJump :: CmmExpr{-the branch target-} -> NatM InstrBlock -genJump expr@(CmmLit (CmmLabel lbl)) - = return $ unitOL (annExpr expr (J (TLabel lbl))) +genJump expr@(CmmLit (CmmLabel lbl)) = do + cur_mod <- getThisModuleNat + !useFarJumps <- ncgEnableInterModuleFarJumps <$> getConfig + let is_local = isLocalCLabel cur_mod lbl + + -- We prefer to generate a near jump using a simble `B` instruction + -- with a range (+/-128MB). But if the target is outside the current module + -- we might have to account for large code offsets. (#24648) + if not useFarJumps || is_local + then return $ unitOL (annExpr expr (J (TLabel lbl))) + else do + (target, _format, code) <- getSomeReg expr + return (code `appOL` unitOL (annExpr expr (J (TReg target)))) genJump expr = do (target, _format, code) <- getSomeReg expr ===================================== compiler/GHC/CmmToAsm/Config.hs ===================================== @@ -47,6 +47,7 @@ data NCGConfig = NCGConfig , ncgDwarfSourceNotes :: !Bool -- ^ Enable GHC-specific source note DIEs , ncgCmmStaticPred :: !Bool -- ^ Enable static control-flow prediction , ncgEnableShortcutting :: !Bool -- ^ Enable shortcutting (don't jump to blocks only containing a jump) + , ncgEnableInterModuleFarJumps:: !Bool -- ^ Use far-jumps for cross-module jumps. , ncgComputeUnwinding :: !Bool -- ^ Compute block unwinding tables , ncgEnableDeadCodeElimination :: !Bool -- ^ Whether to enable the dead-code elimination } ===================================== compiler/GHC/Driver/Config/CmmToAsm.hs ===================================== @@ -70,6 +70,7 @@ initNCGConfig dflags this_mod = NCGConfig , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags , ncgCmmStaticPred = gopt Opt_CmmStaticPred dflags , ncgEnableShortcutting = gopt Opt_AsmShortcutting dflags + , ncgEnableInterModuleFarJumps = gopt Opt_InterModuleFarJumps dflags , ncgComputeUnwinding = debugLevel dflags > 0 , ncgEnableDeadCodeElimination = not (gopt Opt_InfoTableMap dflags) -- Disable when -finfo-table-map is on (#20428) ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1191,6 +1191,17 @@ defaultFlags settings ++ validHoleFitDefaults + -- Platform/OS specific stuff + ++ case platformOS platform of + -- On mac naturally the linker is broken for jumps with very large + -- offsets. (#24648) So we enable HugeTextSections by default to generate + -- far jumps when crossing module boundries instead. As these don't rely + -- on linker fixups. + OSDarwin + | platformArch platform == ArchAArch64 + -> [Opt_InterModuleFarJumps] + _ -> [] + where platform = sTargetPlatform settings ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -657,6 +657,7 @@ data GeneralFlag | Opt_CmmElimCommonBlocks | Opt_CmmControlFlow | Opt_AsmShortcutting + | Opt_InterModuleFarJumps | Opt_OmitYields | Opt_FunToThunk -- deprecated | Opt_DictsStrict -- be strict in argument dictionaries @@ -906,6 +907,7 @@ optimisationFlags = EnumSet.fromList , Opt_CmmSink , Opt_CmmElimCommonBlocks , Opt_AsmShortcutting + , Opt_InterModuleFarJumps , Opt_FunToThunk , Opt_DmdTxDictSel , Opt_Loopification ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2462,6 +2462,7 @@ fFlagsDeps = [ flagSpec "gen-manifest" Opt_GenManifest, flagSpec "ghci-history" Opt_GhciHistory, flagSpec "ghci-leak-check" Opt_GhciLeakCheck, + flagSpec "inter-module-far-jumps" Opt_InterModuleFarJumps, flagSpec "validate-ide-info" Opt_ValidateHie, flagGhciSpec "local-ghci-history" Opt_LocalGhciHistory, flagGhciSpec "no-it" Opt_NoIt, ===================================== docs/users_guide/using-optimisation.rst ===================================== @@ -687,6 +687,23 @@ as such you shouldn't need to set any of them explicitly. A flag ``-fno-full-laziness``. If that is inconvenient for you, please leave a comment `on the issue tracker (#21204) <https://gitlab.haskell.org/ghc/ghc/-/issues/21204>`__. +.. ghc-flag:: -finter-module-far-jumps + :shortdesc: Assume code sections can be very large. + :type: dynamic + :reverse: -fno-inter-module-far-jumps + :category: + + :default: On for AArch64 MacOS + + This flag forces GHC to use far jumps instead of near jumps for all jumps + which cross module boundries. This removes the need for jump islands/linker + jump fixups which some linkers struggle to deal with. (:ghc-ticket:`24648`) + + This comes at a very modest code size (~2%) and runtime (~0.6%) overhead. + + Note that this flag currently only affects the NCG AArch64 backend. + + .. ghc-flag:: -fignore-asserts :shortdesc: Ignore assertions in the source. Implied by :ghc-flag:`-O`. :type: dynamic View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b13d63bd4e421f3daadcf8f20e634f5628543cd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b13d63bd4e421f3daadcf8f20e634f5628543cd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/ab62baa6/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 17:09:25 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 07 Mar 2025 12:09:25 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/nfdata-forcing Message-ID: <67cb2845e1d8a_d3da134b8e022735@gitlab.mail> Matthew Pickering pushed new branch wip/nfdata-forcing at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/nfdata-forcing You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/e967f0eb/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 17:17:15 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 07 Mar 2025 12:17:15 -0500 Subject: [Git][ghc/ghc][wip/remove-unused-fields] Remove mi_hpc field from interface files Message-ID: <67cb2a1b49a57_d3da13ff14c2453d@gitlab.mail> Matthew Pickering pushed to branch wip/remove-unused-fields at Glasgow Haskell Compiler / GHC Commits: 6ad1f029 by Matthew Pickering at 2025-03-07T17:15:35+00:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 13 changed files: - compiler/GHC.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Unit/Module/ModIface.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout Changes: ===================================== compiler/GHC.hs ===================================== @@ -116,7 +116,6 @@ module GHC ( mi_decls, mi_extra_decls, mi_top_env, - mi_hpc, mi_trust, mi_trust_pkg, mi_complete_matches, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -138,7 +138,6 @@ deSugar hsc_env tcg_default_exports = defaults, tcg_insts = insts, tcg_fam_insts = fam_insts, - tcg_hpc = other_hpc_info, tcg_complete_matches = complete_matches, tcg_self_boot = self_boot }) @@ -179,7 +178,7 @@ deSugar hsc_env then writeMixEntries (hpcDir dflags) mod ticks orig_file2 else return 0 -- dummy hash when none are written pure $ HpcInfo (fromIntegral $ sizeSS ticks) hashNo - _ -> pure $ emptyHpcInfo other_hpc_info + _ -> pure $ emptyHpcInfo ; (msgs, mb_res) <- initDs hsc_env tcg_env $ do { dsEvBinds ev_binds $ \ ds_ev_binds -> do ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1264,7 +1264,6 @@ pprModIface unit_state iface <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) - <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -66,7 +66,6 @@ import GHC.Types.Unique.DSet import GHC.Types.TypeEnv import GHC.Types.SourceFile import GHC.Types.TyThing -import GHC.Types.HpcInfo import GHC.Types.CompleteMatch import GHC.Types.Name.Cache @@ -120,14 +119,13 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_rdr_env = rdr_env , mg_fix_env = fix_env , mg_warns = warns - , mg_hpc_info = hpc_info , mg_safe_haskell = safe_mode , mg_trust_pkg = self_trust , mg_docs = docs } = do self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages - return $ mkIface_ hsc_env this_mod core_prog hsc_src deps rdr_env import_decls fix_env warns hpc_info self_trust + return $ mkIface_ hsc_env this_mod core_prog hsc_src deps rdr_env import_decls fix_env warns self_trust safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code @@ -237,8 +235,7 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_warns = warns, - tcg_hpc = other_hpc_info + tcg_warns = warns } = do let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) @@ -247,7 +244,6 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (tcg_mod tc_result) (tcg_imports tc_result) (map mi_module pluginModules) - let hpc_info = emptyHpcInfo other_hpc_info usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result @@ -256,7 +252,7 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src deps rdr_env import_decls - fix_env warns hpc_info + fix_env warns (imp_trust_own_pkg imports) safe_mode self_recomp docs mod_details @@ -290,7 +286,7 @@ mkRecompUsageInfo hsc_env tc_result = do mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] - -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo + -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode -> Maybe ModIfaceSelfRecomp @@ -299,7 +295,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode self_recomp + pkg_trust_req safe_mode self_recomp docs ModDetails{ md_defaults = defaults, md_insts = insts, @@ -375,7 +371,6 @@ mkIface_ hsc_env & set_mi_top_env rdrs & set_mi_decls decls & set_mi_extra_decls extra_decls - & set_mi_hpc (isHpcUsed hpc_info) & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1256,18 +1256,14 @@ addFingerprints hsc_env iface0 -- The interface hash depends on: -- - the ABI hash, plus - -- - the source file hash, + -- - the things which can affect whether a module is recompiled -- - the module level annotations, - -- - usages -- - deps (home and external packages, dependent files) - -- - hpc iface_hash <- computeFingerprint putNameLiterally (mod_hash, - mi_src_hash iface0, ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_usages iface0, - sorted_deps, - mi_hpc iface0) + mi_self_recomp_info iface0, + sorted_deps ) let final_iface_exts = ModIfaceBackend ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -77,7 +77,6 @@ import GHC.Types.SrcLoc as SrcLoc import GHC.Types.Basic ( TopLevelFlag(..) ) import GHC.Types.SourceText import GHC.Types.Id -import GHC.Types.HpcInfo import GHC.Types.PkgQual import GHC.Types.GREInfo (ConInfo(..), ConFieldInfo (..), ConLikeInfo (ConIsData)) @@ -201,7 +200,7 @@ with yes we have gone with no for now. -- Note: Do the non SOURCE ones first, so that we get a helpful warning -- for SOURCE ones that are unnecessary rnImports :: [(LImportDecl GhcPs, SDoc)] - -> RnM ([LImportDecl GhcRn], [ImportUserSpec], GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)], AnyHpcUsage) + -> RnM ([LImportDecl GhcRn], [ImportUserSpec], GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)]) rnImports imports = do tcg_env <- getGblEnv -- NB: want an identity module here, because it's OK for a signature @@ -212,10 +211,10 @@ rnImports imports = do stuff1 <- mapAndReportM (rnImportDecl this_mod) ordinary stuff2 <- mapAndReportM (rnImportDecl this_mod) source -- Safe Haskell: See Note [Tracking Trust Transitively] - let (decls, imp_user_spec, rdr_env, imp_avails, defaults, hpc_usage) = combine (stuff1 ++ stuff2) + let (decls, imp_user_spec, rdr_env, imp_avails, defaults) = combine (stuff1 ++ stuff2) -- Update imp_boot_mods if imp_direct_mods mentions any of them let merged_import_avail = clobberSourceImports imp_avails - return (decls, imp_user_spec, rdr_env, merged_import_avail, defaults, hpc_usage) + return (decls, imp_user_spec, rdr_env, merged_import_avail, defaults) where clobberSourceImports imp_avails = @@ -228,24 +227,23 @@ rnImports imports = do combJ (GWIB _ IsBoot) x = Just x combJ r _ = Just r -- See Note [Combining ImportAvails] - combine :: [(LImportDecl GhcRn, ImportUserSpec, GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)], AnyHpcUsage)] - -> ([LImportDecl GhcRn], [ImportUserSpec], GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)], AnyHpcUsage) + combine :: [(LImportDecl GhcRn, ImportUserSpec, GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)])] + -> ([LImportDecl GhcRn], [ImportUserSpec], GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)]) combine ss = - let (decls, imp_user_spec, rdr_env, imp_avails, defaults, hpc_usage, finsts) = foldr + let (decls, imp_user_spec, rdr_env, imp_avails, defaults, finsts) = foldr plus - ([], [], emptyGlobalRdrEnv, emptyImportAvails, [], False, emptyModuleSet) + ([], [], emptyGlobalRdrEnv, emptyImportAvails, [], emptyModuleSet) ss in (decls, imp_user_spec, rdr_env, imp_avails { imp_finsts = moduleSetElts finsts }, - defaults, hpc_usage) + defaults) - plus (decl, us, gbl_env1, imp_avails1, defaults1, hpc_usage1) - (decls, uss, gbl_env2, imp_avails2, defaults2, hpc_usage2, finsts_set) + plus (decl, us, gbl_env1, imp_avails1, defaults1) + (decls, uss, gbl_env2, imp_avails2, defaults2, finsts_set) = ( decl:decls, us:uss, gbl_env1 `plusGlobalRdrEnv` gbl_env2, imp_avails1' `plusImportAvails` imp_avails2, defaults1 ++ defaults2, - hpc_usage1 || hpc_usage2, extendModuleSetList finsts_set new_finsts ) where imp_avails1' = imp_avails1 { imp_finsts = [] } @@ -309,7 +307,7 @@ Running generateModules from #14693 with DEPTH=16, WIDTH=30 finishes in -- 4. A boolean 'AnyHpcUsage' which is true if the imported module -- used HPC. rnImportDecl :: Module -> (LImportDecl GhcPs, SDoc) - -> RnM (LImportDecl GhcRn, ImportUserSpec , GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)], AnyHpcUsage) + -> RnM (LImportDecl GhcRn, ImportUserSpec , GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)]) rnImportDecl this_mod (L loc decl@(ImportDecl { ideclName = loc_imp_mod_name , ideclPkgQual = raw_pkg_qual @@ -438,7 +436,7 @@ rnImportDecl this_mod } return (L loc new_imp_decl, ImpUserSpec imp_spec imp_user_list, gbl_env, - imports, (,) (mi_module iface) <$> mi_defaults iface, mi_hpc iface) + imports, (,) (mi_module iface) <$> mi_defaults iface) -- | Rename raw package imports ===================================== compiler/GHC/Tc/Module.hs ===================================== @@ -459,7 +459,7 @@ isTypeSubsequenceOf (t1:t1s) (t2:t2s) tcRnImports :: HscEnv -> [(LImportDecl GhcPs, SDoc)] -> TcM ([NonEmpty ClassDefaults], TcGblEnv) tcRnImports hsc_env import_decls - = do { (rn_imports, imp_user_spec, rdr_env, imports, defaults, hpc_info) <- rnImports import_decls ; + = do { (rn_imports, imp_user_spec, rdr_env, imports, defaults) <- rnImports import_decls ; ; this_mod <- getModule ; gbl_env <- getGblEnv @@ -494,8 +494,7 @@ tcRnImports hsc_env import_decls tcg_default = foldMap subsume tc_defaults, tcg_inst_env = tcg_inst_env gbl `unionInstEnv` home_insts, tcg_fam_inst_env = extendFamInstEnvList (tcg_fam_inst_env gbl) - home_fam_insts, - tcg_hpc = hpc_info + home_fam_insts }) $ do { ; traceRn "rn1" (ppr (imp_direct_dep_mods imports)) ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -154,7 +154,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique.FM import GHC.Types.Basic import GHC.Types.CostCentre.State -import GHC.Types.HpcInfo import GHC.Data.IOEnv import GHC.Data.Bag @@ -641,10 +640,6 @@ data TcGblEnv tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName)), -- ^ Maybe Haddock header docs and Maybe located module name - tcg_hpc :: !AnyHpcUsage, -- ^ @True@ if any part of the - -- prog uses hpc instrumentation. - -- NB. BangPattern is to fix a leak, see #15111 - tcg_self_boot :: SelfBootInfo, -- ^ Whether this module has a -- corresponding hi-boot file ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -358,7 +358,6 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this tcg_zany_n = zany_n_var, tcg_keep = keep_var, tcg_hdr_info = (Nothing,Nothing), - tcg_hpc = False, tcg_main = Nothing, tcg_self_boot = NoSelfBoot, tcg_safe_infer = infer_var, ===================================== compiler/GHC/Types/HpcInfo.hs ===================================== @@ -1,9 +1,7 @@ -- | Haskell Program Coverage (HPC) support module GHC.Types.HpcInfo ( HpcInfo (..) - , AnyHpcUsage , emptyHpcInfo - , isHpcUsed ) where @@ -16,19 +14,8 @@ data HpcInfo , hpcInfoHash :: Int } | NoHpcInfo - { hpcUsed :: AnyHpcUsage -- ^ Is hpc used anywhere on the module \*tree\*? - } --- | This is used to signal if one of my imports used HPC instrumentation --- even if there is no module-local HPC usage -type AnyHpcUsage = Bool -emptyHpcInfo :: AnyHpcUsage -> HpcInfo +emptyHpcInfo :: HpcInfo emptyHpcInfo = NoHpcInfo --- | Find out if HPC is used by this module or any of the modules --- it depends upon -isHpcUsed :: HpcInfo -> AnyHpcUsage -isHpcUsed (HpcInfo {}) = True -isHpcUsed (NoHpcInfo { hpcUsed = used }) = used - ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -27,7 +27,6 @@ module GHC.Unit.Module.ModIface , mi_insts , mi_fam_insts , mi_rules - , mi_hpc , mi_trust , mi_trust_pkg , mi_complete_matches @@ -56,7 +55,6 @@ module GHC.Unit.Module.ModIface , set_mi_extra_decls , set_mi_foreign , set_mi_top_env - , set_mi_hpc , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches @@ -113,7 +111,6 @@ import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env -import GHC.Types.HpcInfo import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Types.SourceFile @@ -300,8 +297,6 @@ data ModIface_ (phase :: ModIfacePhase) mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc_ :: !AnyHpcUsage, - -- ^ True if this program uses Hpc at any point in the program. mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. @@ -481,7 +476,6 @@ instance Binary ModIface where mi_insts_ = insts, mi_fam_insts_ = fam_insts, mi_rules_ = rules, - mi_hpc_ = hpc_info, mi_trust_ = trust, mi_trust_pkg_ = trust_pkg, mi_complete_matches_ = complete_matches, @@ -521,7 +515,6 @@ instance Binary ModIface where put_ bh fam_insts lazyPut bh rules put_ bh orphan_hash - put_ bh hpc_info put_ bh trust put_ bh trust_pkg put_ bh complete_matches @@ -551,7 +544,6 @@ instance Binary ModIface where fam_insts <- {-# SCC "bin_fam_insts" #-} get bh rules <- {-# SCC "bin_rules" #-} lazyGet bh orphan_hash <- get bh - hpc_info <- get bh trust <- get bh trust_pkg <- get bh complete_matches <- get bh @@ -578,7 +570,6 @@ instance Binary ModIface where mi_insts_ = insts, mi_fam_insts_ = fam_insts, mi_rules_ = rules, - mi_hpc_ = hpc_info, mi_trust_ = trust, mi_trust_pkg_ = trust_pkg, -- And build the cached values @@ -623,7 +614,6 @@ emptyPartialModIface mod mi_extra_decls_ = Nothing, mi_foreign_ = emptyIfaceForeign, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_hpc_ = False, mi_trust_ = noIfaceTrustInfo, mi_trust_pkg_ = False, mi_complete_matches_ = [], @@ -674,7 +664,7 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ - , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_fam_insts_, mi_rules_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ , mi_ext_fields_ }) = rnf mi_module_ @@ -694,7 +684,6 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_insts_ `seq` rnf mi_fam_insts_ `seq` rnf mi_rules_ - `seq` rnf mi_hpc_ `seq` mi_trust_ `seq` rnf mi_trust_pkg_ `seq` rnf mi_complete_matches_ @@ -828,9 +817,6 @@ set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreig set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } -set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase -set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } - set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } @@ -924,7 +910,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} {-# INLINE mi_rules #-} -{-# INLINE mi_hpc #-} {-# INLINE mi_trust #-} {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} @@ -940,7 +925,7 @@ pattern ModIface :: [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface @@ -960,7 +945,6 @@ pattern ModIface , mi_insts , mi_fam_insts , mi_rules - , mi_hpc , mi_trust , mi_trust_pkg , mi_complete_matches @@ -986,7 +970,6 @@ pattern ModIface , mi_insts_ = mi_insts , mi_fam_insts_ = mi_fam_insts , mi_rules_ = mi_rules - , mi_hpc_ = mi_hpc , mi_trust_ = mi_trust , mi_trust_pkg_ = mi_trust_pkg , mi_complete_matches_ = mi_complete_matches ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -162,7 +162,6 @@ GHC.Types.ForeignStubs GHC.Types.GREInfo GHC.Types.Hint GHC.Types.Hint.Ppr -GHC.Types.HpcInfo GHC.Types.Id GHC.Types.Id.Info GHC.Types.Id.Make ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -185,7 +185,6 @@ GHC.Types.ForeignStubs GHC.Types.GREInfo GHC.Types.Hint GHC.Types.Hint.Ppr -GHC.Types.HpcInfo GHC.Types.Id GHC.Types.Id.Info GHC.Types.Id.Make View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ad1f029e3fcc7c5a493cbb5273d86d3b1d1c362 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ad1f029e3fcc7c5a493cbb5273d86d3b1d1c362 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/229e52a8/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 18:32:18 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 07 Mar 2025 13:32:18 -0500 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Add mapMaybeTM to TrieMap Message-ID: <67cb3bb25a114_e8a1f435440100786@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: ca89d176 by sheaf at 2025-03-07T19:31:58+01:00 Add mapMaybeTM to TrieMap - - - - - 30049b74 by sheaf at 2025-03-07T19:31:58+01:00 new plan from March 7 - - - - - 17 changed files: - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Types/Var/Env.hs - testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr Changes: ===================================== compiler/GHC/Cmm/Dataflow/Label.hs ===================================== @@ -63,6 +63,7 @@ module GHC.Cmm.Dataflow.Label , mapToList , mapFromList , mapFromListWith + , mapMapMaybe ) where import GHC.Prelude @@ -280,6 +281,9 @@ mapFromList assocs = LM (M.fromList [(lblToUnique k, v) | (k, v) <- assocs]) mapFromListWith :: (v -> v -> v) -> [(Label, v)] -> LabelMap v mapFromListWith f assocs = LM (M.fromListWith f [(lblToUnique k, v) | (k, v) <- assocs]) +mapMapMaybe :: (a -> Maybe b) -> LabelMap a -> LabelMap b +mapMapMaybe f (LM m) = LM (M.mapMaybe f m) + ----------------------------------------------------------------------------- -- Instances @@ -298,7 +302,8 @@ instance TrieMap LabelMap where lookupTM k m = mapLookup k m alterTM k f m = mapAlter f k m foldTM k m z = mapFoldr k z m - filterTM f m = mapFilter f m + filterTM f = mapFilter f + mapMaybeTM f = mapMapMaybe f ----------------------------------------------------------------------------- -- FactBase ===================================== compiler/GHC/Core/Map/Expr.hs ===================================== @@ -122,6 +122,7 @@ instance TrieMap CoreMap where alterTM k f (CoreMap m) = CoreMap (alterTM (deBruijnize k) f m) foldTM k (CoreMap m) = foldTM k m filterTM f (CoreMap m) = CoreMap (filterTM f m) + mapMaybeTM f (CoreMap m) = CoreMap (mapMaybeTM f m) -- | @CoreMapG a@ is a map from @DeBruijn CoreExpr@ to @a at . The extended -- key makes it suitable for recursive traversal, since it can track binders, @@ -271,6 +272,7 @@ instance TrieMap CoreMapX where alterTM = xtE foldTM = fdE filterTM = ftE + mapMaybeTM = mpE -------------------------- ftE :: (a->Bool) -> CoreMapX a -> CoreMapX a @@ -287,6 +289,20 @@ ftE f (CM { cm_var = cvar, cm_lit = clit , cm_letr = fmap (fmap (filterTM f)) cletr, cm_case = fmap (filterTM f) ccase , cm_ecase = fmap (filterTM f) cecase, cm_tick = fmap (filterTM f) ctick } +mpE :: (a -> Maybe b) -> CoreMapX a -> CoreMapX b +mpE f (CM { cm_var = cvar, cm_lit = clit + , cm_co = cco, cm_type = ctype + , cm_cast = ccast , cm_app = capp + , cm_lam = clam, cm_letn = cletn + , cm_letr = cletr, cm_case = ccase + , cm_ecase = cecase, cm_tick = ctick }) + = CM { cm_var = mapMaybeTM f cvar, cm_lit = mapMaybeTM f clit + , cm_co = mapMaybeTM f cco, cm_type = mapMaybeTM f ctype + , cm_cast = fmap (mapMaybeTM f) ccast, cm_app = fmap (mapMaybeTM f) capp + , cm_lam = fmap (mapMaybeTM f) clam, cm_letn = fmap (fmap (mapMaybeTM f)) cletn + , cm_letr = fmap (fmap (mapMaybeTM f)) cletr, cm_case = fmap (mapMaybeTM f) ccase + , cm_ecase = fmap (mapMaybeTM f) cecase, cm_tick = fmap (mapMaybeTM f) ctick } + -------------------------- lookupCoreMap :: CoreMap a -> CoreExpr -> Maybe a lookupCoreMap cm e = lookupTM e cm @@ -409,6 +425,7 @@ instance TrieMap AltMap where alterTM = xtA emptyCME foldTM = fdA filterTM = ftA + mapMaybeTM = mpA instance Eq (DeBruijn CoreAlt) where D env1 a1 == D env2 a2 = go a1 a2 where @@ -446,3 +463,9 @@ fdA :: (a -> b -> b) -> AltMap a -> b -> b fdA k m = foldTM k (am_deflt m) . foldTM (foldTM k) (am_data m) . foldTM (foldTM k) (am_lit m) + +mpA :: (a -> Maybe b) -> AltMap a -> AltMap b +mpA f (AM { am_deflt = adeflt, am_data = adata, am_lit = alit }) + = AM { am_deflt = mapMaybeTM f adeflt + , am_data = fmap (mapMaybeTM f) adata + , am_lit = fmap (mapMaybeTM f) alit } ===================================== compiler/GHC/Core/Map/Type.hs ===================================== @@ -96,6 +96,7 @@ instance TrieMap CoercionMap where alterTM k f (CoercionMap m) = CoercionMap (alterTM (deBruijnize k) f m) foldTM k (CoercionMap m) = foldTM k m filterTM f (CoercionMap m) = CoercionMap (filterTM f m) + mapMaybeTM f (CoercionMap m) = CoercionMap (mapMaybeTM f m) type CoercionMapG = GenMap CoercionMapX newtype CoercionMapX a = CoercionMapX (TypeMapX a) @@ -112,6 +113,7 @@ instance TrieMap CoercionMapX where alterTM = xtC foldTM f (CoercionMapX core_tm) = foldTM f core_tm filterTM f (CoercionMapX core_tm) = CoercionMapX (filterTM f core_tm) + mapMaybeTM f (CoercionMapX core_tm) = CoercionMapX (mapMaybeTM f core_tm) instance Eq (DeBruijn Coercion) where D env1 co1 == D env2 co2 @@ -189,6 +191,7 @@ instance TrieMap TypeMapX where alterTM = xtT foldTM = fdT filterTM = filterT + mapMaybeTM = mpT instance Eq (DeBruijn Type) where (==) = eqDeBruijnType @@ -380,6 +383,7 @@ instance TrieMap TyLitMap where alterTM = xtTyLit foldTM = foldTyLit filterTM = filterTyLit + mapMaybeTM = mpTyLit emptyTyLitMap :: TyLitMap a emptyTyLitMap = TLM { tlm_number = Map.empty, tlm_string = emptyUFM, tlm_char = Map.empty } @@ -407,6 +411,10 @@ filterTyLit :: (a -> Bool) -> TyLitMap a -> TyLitMap a filterTyLit f (TLM { tlm_number = tn, tlm_string = ts, tlm_char = tc }) = TLM { tlm_number = Map.filter f tn, tlm_string = filterUFM f ts, tlm_char = Map.filter f tc } +mpTyLit :: (a -> Maybe b) -> TyLitMap a -> TyLitMap b +mpTyLit f (TLM { tlm_number = tn, tlm_string = ts, tlm_char = tc }) + = TLM { tlm_number = Map.mapMaybe f tn, tlm_string = mapMaybeUFM f ts, tlm_char = Map.mapMaybe f tc } + ------------------------------------------------- -- | @TypeMap a@ is a map from 'Type' to @a at . If you are a client, this -- is the type you want. The keys in this map may have different kinds. @@ -435,6 +443,7 @@ instance TrieMap TypeMap where alterTM k f m = xtTT (deBruijnize k) f m foldTM k (TypeMap m) = foldTM (foldTM k) m filterTM f (TypeMap m) = TypeMap (fmap (filterTM f) m) + mapMaybeTM f (TypeMap m) = TypeMap (fmap (mapMaybeTM f) m) foldTypeMap :: (a -> b -> b) -> b -> TypeMap a -> b foldTypeMap k z m = foldTM k m z @@ -479,6 +488,7 @@ instance TrieMap LooseTypeMap where alterTM k f (LooseTypeMap m) = LooseTypeMap (alterTM (deBruijnize k) f m) foldTM f (LooseTypeMap m) = foldTM f m filterTM f (LooseTypeMap m) = LooseTypeMap (filterTM f m) + mapMaybeTM f (LooseTypeMap m) = LooseTypeMap (mapMaybeTM f m) {- ************************************************************************ @@ -558,10 +568,13 @@ instance TrieMap BndrMap where alterTM = xtBndr emptyCME foldTM = fdBndrMap filterTM = ftBndrMap + mapMaybeTM = mpBndrMap fdBndrMap :: (a -> b -> b) -> BndrMap a -> b -> b fdBndrMap f (BndrMap tm) = foldTM (foldTM f) tm +mpBndrMap :: (a -> Maybe b) -> BndrMap a -> BndrMap b +mpBndrMap f (BndrMap tm) = BndrMap (fmap (mapMaybeTM f) tm) -- We need to use 'BndrMap' for 'Coercion', 'CoreExpr' AND 'Type', since all -- of these data types have binding forms. @@ -594,6 +607,7 @@ instance TrieMap VarMap where alterTM = xtVar emptyCME foldTM = fdVar filterTM = ftVar + mapMaybeTM = mpVar lkVar :: CmEnv -> Var -> VarMap a -> Maybe a lkVar env v @@ -619,9 +633,24 @@ ftVar :: (a -> Bool) -> VarMap a -> VarMap a ftVar f (VM { vm_bvar = bv, vm_fvar = fv }) = VM { vm_bvar = filterTM f bv, vm_fvar = filterTM f fv } +mpVar :: (a -> Maybe b) -> VarMap a -> VarMap b +mpVar f (VM { vm_bvar = bv, vm_fvar = fv }) + = VM { vm_bvar = mapMaybeTM f bv, vm_fvar = mapMaybeTM f fv } + ------------------------------------------------- lkDNamed :: NamedThing n => n -> DNameEnv a -> Maybe a lkDNamed n env = lookupDNameEnv env (getName n) xtDNamed :: NamedThing n => n -> XT a -> DNameEnv a -> DNameEnv a xtDNamed tc f m = alterDNameEnv f m (getName tc) + +mpT :: (a -> Maybe b) -> TypeMapX a -> TypeMapX b +mpT f (TM { tm_var = tvar, tm_app = tapp, tm_tycon = ttycon + , tm_forall = tforall, tm_tylit = tlit + , tm_coerce = tcoerce }) + = TM { tm_var = mapMaybeTM f tvar + , tm_app = fmap (mapMaybeTM f) tapp + , tm_tycon = mapMaybeTM f ttycon + , tm_forall = fmap (mapMaybeTM f) tforall + , tm_tylit = mapMaybeTM f tlit + , tm_coerce = tcoerce >>= f } ===================================== compiler/GHC/Data/TrieMap.hs ===================================== @@ -69,7 +69,7 @@ class Functor m => TrieMap m where lookupTM :: forall b. Key m -> m b -> Maybe b alterTM :: forall b. Key m -> XT b -> m b -> m b filterTM :: (a -> Bool) -> m a -> m a - + mapMaybeTM :: (a -> Maybe b) -> m a -> m b foldTM :: (a -> b -> b) -> m a -> b -> b -- The unusual argument order here makes -- it easy to compose calls to foldTM; @@ -146,6 +146,7 @@ instance TrieMap IntMap.IntMap where alterTM = xtInt foldTM k m z = IntMap.foldr k z m filterTM f m = IntMap.filter f m + mapMaybeTM f m = IntMap.mapMaybe f m xtInt :: Int -> XT a -> IntMap.IntMap a -> IntMap.IntMap a xtInt k f m = IntMap.alter f k m @@ -157,6 +158,7 @@ instance Ord k => TrieMap (Map.Map k) where alterTM k f m = Map.alter f k m foldTM k m z = Map.foldr k z m filterTM f m = Map.filter f m + mapMaybeTM f m = Map.mapMaybe f m {- @@ -233,6 +235,7 @@ instance forall key. Uniquable key => TrieMap (UniqDFM key) where alterTM k f m = alterUDFM f m k foldTM k m z = foldUDFM k z m filterTM f m = filterUDFM f m + mapMaybeTM f m = mapMaybeUDFM f m {- ************************************************************************ @@ -259,6 +262,7 @@ instance TrieMap m => TrieMap (MaybeMap m) where alterTM = xtMaybe alterTM foldTM = fdMaybe filterTM = ftMaybe + mapMaybeTM = mpMaybe instance TrieMap m => Foldable (MaybeMap m) where foldMap = foldMapTM @@ -281,6 +285,10 @@ ftMaybe :: TrieMap m => (a -> Bool) -> MaybeMap m a -> MaybeMap m a ftMaybe f (MM { mm_nothing = mn, mm_just = mj }) = MM { mm_nothing = filterMaybe f mn, mm_just = filterTM f mj } +mpMaybe :: TrieMap m => (a -> Maybe b) -> MaybeMap m a -> MaybeMap m b +mpMaybe f (MM { mm_nothing = mn, mm_just = mj }) + = MM { mm_nothing = mn >>= f, mm_just = mapMaybeTM f mj } + foldMaybe :: (a -> b -> b) -> Maybe a -> b -> b foldMaybe _ Nothing b = b foldMaybe k (Just a) b = k a b @@ -314,6 +322,7 @@ instance TrieMap m => TrieMap (ListMap m) where alterTM = xtList alterTM foldTM = fdList filterTM = ftList + mapMaybeTM = mpList instance TrieMap m => Foldable (ListMap m) where foldMap = foldMapTM @@ -340,6 +349,10 @@ ftList :: TrieMap m => (a -> Bool) -> ListMap m a -> ListMap m a ftList f (LM { lm_nil = mnil, lm_cons = mcons }) = LM { lm_nil = filterMaybe f mnil, lm_cons = fmap (filterTM f) mcons } +mpList :: TrieMap m => (a -> Maybe b) -> ListMap m a -> ListMap m b +mpList f (LM { lm_nil = mnil, lm_cons = mcons }) + = LM { lm_nil = mnil >>= f, lm_cons = fmap (mapMaybeTM f) mcons } + {- ************************************************************************ * * @@ -395,6 +408,7 @@ instance (Eq (Key m), TrieMap m) => TrieMap (GenMap m) where alterTM = xtG foldTM = fdG filterTM = ftG + mapMaybeTM = mpG instance (Eq (Key m), TrieMap m) => Foldable (GenMap m) where foldMap = foldMapTM @@ -457,3 +471,11 @@ ftG f input@(SingletonMap _ v) ftG f (MultiMap m) = MultiMap (filterTM f m) -- we don't have enough information to reconstruct the key to make -- a SingletonMap + +{-# INLINEABLE mpG #-} +mpG :: TrieMap m => (a -> Maybe b) -> GenMap m a -> GenMap m b +mpG _ EmptyMap = EmptyMap +mpG f (SingletonMap k v) = case f v of + Just v' -> SingletonMap k v' + Nothing -> EmptyMap +mpG f (MultiMap m) = MultiMap (mapMaybeTM f m) ===================================== compiler/GHC/Stg/CSE.hs ===================================== @@ -142,6 +142,8 @@ instance TrieMap StgArgMap where foldTM k m = foldTM k (sam_var m) . foldTM k (sam_lit m) filterTM f (SAM {sam_var = varm, sam_lit = litm}) = SAM { sam_var = filterTM f varm, sam_lit = filterTM f litm } + mapMaybeTM f (SAM {sam_var = varm, sam_lit = litm}) = + SAM { sam_var = mapMaybeTM f varm, sam_lit = mapMaybeTM f litm } newtype ConAppMap a = CAM { un_cam :: DNameEnv (ListMap StgArgMap a) } @@ -158,6 +160,7 @@ instance TrieMap ConAppMap where m { un_cam = un_cam m |> xtDNamed dataCon |>> alterTM args f } foldTM k = un_cam >.> foldTM (foldTM k) filterTM f = un_cam >.> fmap (filterTM f) >.> CAM + mapMaybeTM f = un_cam >.> fmap (mapMaybeTM f) >.> CAM ----------------- -- The CSE Env -- ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -39,7 +39,7 @@ import GHC.Tc.Gen.HsType import GHC.Tc.Solver( reportUnsolvedEqualities, pushLevelAndSolveEqualitiesX , emitResidualConstraints ) import GHC.Tc.Solver.Solve( solveWanteds ) -import GHC.Tc.Solver.Monad( runTcS, runTcSWithEvBinds ) +import GHC.Tc.Solver.Monad( runTcS, runTcSFullySolve ) import GHC.Tc.Validity ( checkValidType ) import GHC.Tc.Utils.Monad @@ -761,16 +761,11 @@ This is done in three parts. (1) Typecheck the expression, capturing its constraints - (2) Clone these Wanteds, solve them, and zonk the original Wanteds. - This is the same thing that we do for RULES: see Step 1 in - Note [The SimplifyRule Plan]. + (2) Solve these constraints, but in special TcSFullySolve mode which ensures + each original Wanted is either fully solved or left untouched. + See Note [Fully solving constraints for specialisation]. - (3) Compute the constraints to quantify over. - - a. 'getRuleQuantCts' computes the initial quantification candidates - b. Filter out the fully soluble constraints; these are the constraints - we are specialising away. - See Note [Fully solving constraints for specialisation]. + (3) Compute the constraints to quantify over, using `getRuleQuantCts`. (4) Emit the residual (non-quantified) constraints, and wrap the expression in a let binding for those constraints. @@ -850,9 +845,8 @@ The conclusion is this: - fully solved (no free evidence variables), or - left untouched. -To achieve this, we quantify over all constraints that are **not fully soluble** -(see 'fullySolveCt_maybe'), although we still call 'mkMinimalBySCs' on this set -to avoid e.g. quantifying over both `Eq a` and `Ord a`. +To achieve this, we run the solver in a special "all-or-nothing" solving mode, +described in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. Note [Handling old-form SPECIALISE pragmas] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1029,40 +1023,26 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) <- tcRuleBndrs skol_info rule_bndrs $ tcInferRho spec_e - -- (2) Clone these Wanteds, solve them, and zonk the original - -- Wanteds, in order to benefit from any unifications. - - ; throwaway_ev_binds_var <- newTcEvBinds - ; spec_e_wanted_clone <- cloneWC spec_e_wanted - ; _ <- setTcLevel rhs_tclvl $ - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds spec_e_wanted_clone + -- (2) Solve the resulting wanteds in TcSFullySolve mode. + ; ev_binds_var <- newTcEvBinds + ; spec_e_wanted <- setTcLevel rhs_tclvl $ + runTcSFullySolve ev_binds_var $ + solveWanteds spec_e_wanted ; spec_e_wanted <- liftZonkM $ zonkWC spec_e_wanted -- (3) Compute which constraints to quantify over. - -- (a) Compute quantification candidates - ; ev_binds_var <- newTcEvBinds ; (quant_cands, residual_wc) <- getRuleQuantCts spec_e_wanted - -- (b) Compute fully soluble constraints - -- See Note [Fully solving constraints for specialisation] - ; traceTc "tcSpecPrag SpecSigE: computing fully soluble Wanteds {" empty - ; fully_soluble_evids <- - setTcLevel rhs_tclvl $ - mkVarSet <$> - mapMaybeM fullySolveCt_maybe (bagToList quant_cands) - ; let (fully_soluble_cts, quant_cts) = partitionBag ((`elemVarSet` fully_soluble_evids) . ctEvId) quant_cands - -- (c) Compute constraints to quantify over using 'mkMinimalBySCs' - qevs = map ctEvId (bagToList quant_cts) - ; traceTc "tcSpecPrag SpecSigE: computed fully soluble Wanteds }" (ppr fully_soluble_cts) - -- (4) Emit the residual constraints (that we are not quantifying over) ; let tv_bndrs = filter isTyVar rule_bndrs' + qevs = map ctEvId (bagToList quant_cands) ; emitResidualConstraints rhs_tclvl skol_info_anon ev_binds_var emptyVarSet tv_bndrs qevs - (residual_wc `addSimples` fully_soluble_cts) + residual_wc ; let lhs_call = mkLHsWrap (WpLet (TcEvBinds ev_binds_var)) tc_spec_e + ; ev_binds <- getTcEvBindsMap ev_binds_var + ; traceTc "tcSpecPrag SpecSigE }" $ vcat [ text "nm:" <+> ppr nm , text "rule_bndrs':" <+> ppr rule_bndrs' @@ -1070,9 +1050,11 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) , text "spec_e:" <+> ppr tc_spec_e , text "inl:" <+> ppr inl , text "spec_e_wanted:" <+> ppr spec_e_wanted - , text "quant_cts:" <+> ppr quant_cts + , text "quant_cands:" <+> ppr quant_cands , text "residual_wc:" <+> ppr residual_wc - , text "fully_soluble_wanteds:" <+> ppr fully_soluble_cts + , text (replicate 80 '-') + , text "ev_binds_var:" <+> ppr ev_binds_var + , text "ev_binds:" <+> ppr ev_binds ] -- (5) Store the results in a SpecPragE record, which will be @@ -1087,24 +1069,6 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) tcSpecPrag _ prag = pprPanic "tcSpecPrag" (ppr prag) --- | Try to fully solve a constraint. -fullySolveCt_maybe :: Ct -> TcM (Maybe EvId) -fullySolveCt_maybe ct = do - throwaway_ev_binds_var <- newTcEvBinds - res_wc <- - runTcSWithEvBinds throwaway_ev_binds_var $ - solveWanteds $ emptyWC { wc_simple = unitBag ct } - -- NB: don't use 'solveSimpleWanteds', as this will not - -- fully solve quantified constraints. - traceTc "fullySolveCt_maybe" $ - vcat [ text "ct:" <+> ppr ct - , text "res_wc:" <+> ppr res_wc - ] - return $ - if isSolvedWC res_wc - then Just $ ctEvId ct - else Nothing - -------------- tcSpecWrapper :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper -- A simpler variant of tcSubType, used for SPECIALISE pragmas ===================================== compiler/GHC/Tc/Solver.hs ===================================== @@ -231,7 +231,7 @@ simplifyAndEmitFlatConstraints wanted -- it's OK to use unkSkol | we must increase the TcLevel, -- because we don't bind | as explained in -- any skolem variables here | Note [Wrapping failing kind equalities] - ; emitImplication implic + ; TcM.emitImplication implic ; failM } Just (simples, errs) -> do { _ <- promoteTyVarSet (tyCoVarsOfCts simples) ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -61,6 +61,7 @@ import Data.Void( Void ) import Control.Monad.Trans.Maybe( MaybeT, runMaybeT ) import Control.Monad.Trans.Class( lift ) import Control.Monad +import {-# SOURCE #-} GHC.Tc.Solver.Solve (solveCompletelyIfRequired) {- ********************************************************************* @@ -848,7 +849,13 @@ shortCutSolver dflags ev_w ev_i tryInstances :: DictCt -> SolverStage () tryInstances dict_ct = Stage $ do { inerts <- getInertSet - ; try_instances inerts dict_ct } + + -- We are about to do something irreversible (using an instance + -- declaration), so we wrap 'try_instances' in solveCompletelyIfRequired + -- to ensure we can roll back if we can't solve the constraint fully. + -- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. + ; solveCompletelyIfRequired (Right dict_ct) $ + try_instances inerts dict_ct } try_instances :: InertSet -> DictCt -> TcS (StopOrContinue ()) -- Try to use type-class instance declarations to simplify the constraint ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -25,6 +25,8 @@ module GHC.Tc.Solver.InertSet ( InertEqs, foldTyEqs, delEq, findEq, partitionInertEqs, partitionFunEqs, + filterInertEqs, filterFunEqs, + inertGivens, foldFunEqs, addEqToCans, -- * Inert Dicts @@ -78,7 +80,6 @@ import Control.Monad ( forM_ ) import Data.List.NonEmpty ( NonEmpty(..), (<|) ) import Data.Function ( on ) - {- ************************************************************************ * * @@ -391,7 +392,6 @@ emptyInert , inert_famapp_cache = emptyFunEqs , inert_solved_dicts = emptyDictMap } - {- Note [Solved dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When we apply a top-level instance declaration, we add the "solved" @@ -1378,6 +1378,17 @@ addInertEqs :: EqCt -> InertEqs -> InertEqs addInertEqs eq_ct@(EqCt { eq_lhs = TyVarLHS tv }) eqs = addTyEq eqs tv eq_ct addInertEqs other _ = pprPanic "extendInertEqs" (ppr other) +-- | Filter InertEqs according to a predicate +filterInertEqs :: (EqCt -> Bool) -> InertEqs -> InertEqs +filterInertEqs f = mapMaybeDVarEnv g + where + g xs = + let filtered = filter f xs + in + if null filtered + then Nothing + else Just filtered + ------------------------ addCanFunEq :: InertFunEqs -> TyCon -> [TcType] -> EqCt -> InertFunEqs @@ -1401,7 +1412,16 @@ addFunEqs eq_ct@(EqCt { eq_lhs = TyFamLHS tc args }) fun_eqs = addCanFunEq fun_eqs tc args eq_ct addFunEqs other _ = pprPanic "extendFunEqs" (ppr other) - +-- | Filter entries in InertFunEqs that satisfy the predicate +filterFunEqs :: (EqCt -> Bool) -> InertFunEqs -> InertFunEqs +filterFunEqs f = mapMaybeTcAppMap g + where + g xs = + let filtered = filter f xs + in + if null filtered + then Nothing + else Just filtered {- ********************************************************************* * * @@ -2215,3 +2235,44 @@ Wrong! The level-check ensures that the inner implicit parameter wins. (Actually I think that the order in which the work-list is processed means that this chain of events won't happen, but that's very fragile.) -} + +{- ********************************************************************* +* * + Extracting Givens from the inert set +* * +********************************************************************* -} + + +-- | Extract only Given constraints from the inert set. +inertGivens :: InertSet -> InertSet +inertGivens is@(IS { inert_cans = cans }) = + is { inert_cans = givens_cans + , inert_solved_dicts = emptyDictMap + } + where + + isGivenEq :: EqCt -> Bool + isGivenEq eq = isGiven (ctEvidence (CEqCan eq)) + isGivenDict :: DictCt -> Bool + isGivenDict dict = isGiven (ctEvidence (CDictCan dict)) + isGivenIrred :: IrredCt -> Bool + isGivenIrred irred = isGiven (ctEvidence (CIrredCan irred)) + + -- Filter the inert constraints for Givens + (eq_givens_list, _) = partitionInertEqs isGivenEq (inert_eqs cans) + (funeq_givens_list, _) = partitionFunEqs isGivenEq (inert_funeqs cans) + dict_givens = filterDicts isGivenDict (inert_dicts cans) + safehask_givens = filterDicts isGivenDict (inert_safehask cans) + irreds_givens = filterBag isGivenIrred (inert_irreds cans) + + eq_givens = foldr addInertEqs emptyTyEqs eq_givens_list + funeq_givens = foldr addFunEqs emptyFunEqs funeq_givens_list + + givens_cans = + cans + { inert_eqs = eq_givens + , inert_funeqs = funeq_givens + , inert_dicts = dict_givens + , inert_safehask = safehask_givens + , inert_irreds = irreds_givens + } ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -14,11 +14,14 @@ module GHC.Tc.Solver.Monad ( -- The TcS monad - TcS, runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + TcS(..), TcSEnv(..), TcSMode(..), + runTcS, runTcSEarlyAbort, runTcSWithEvBinds, runTcSInerts, + runTcSFullySolve, failTcS, warnTcS, addErrTcS, wrapTcS, ctLocWarnTcS, runTcSEqualities, nestTcS, nestImplicTcS, setEvBindsTcS, emitImplicationTcS, emitTvImplicationTcS, + emitImplication, emitFunDepWanteds, selectNextWorkItem, @@ -210,6 +213,7 @@ import Data.Maybe ( isJust ) import qualified Data.Semigroup as S import GHC.Types.SrcLoc import GHC.Rename.Env +--import GHC.Tc.Solver.Solve (solveWanteds) #if defined(DEBUG) import GHC.Types.Unique.Set (nonDetEltsUniqSet) @@ -705,6 +709,7 @@ getUnsolvedInerts where ct = mk_ct thing + getHasGivenEqs :: TcLevel -- TcLevel of this implication -> TcS ( HasGivenEqs -- are there Given equalities? , InertIrreds ) -- Insoluble equalities arising from givens @@ -850,6 +855,31 @@ for it, so TcS carries a mutable location where the binding can be added. This is initialised from the innermost implication constraint. -} +-- | See Note [TcSMode] +data TcSMode + = TcSVanilla -- ^ Normal constraint solving + | TcSEarlyAbort -- ^ Abort early on insoluble constraints + | TcSFullySolve -- ^ Fully solve all constraints + deriving (Eq) + +{- Note [TcSMode] +~~~~~~~~~~~~~~~~~ +The constraint solver can operate in different modes: + +* TcSVanilla: Normal constraint solving mode. This is the default. + +* TcSEarlyAbort: Abort (fail in the monad) as soon as we come across an + insoluble constraint. This is used to fail-fast when checking for hole-fits. + See Note [Speeding up valid hole-fits]. + +* TcSFullySolve: Solve constraints fully or not at all. This is described in + Note [TcSFullySolve]. + + This mode is currently used in one place only: when solving constraints + arising from specialise pragmas. + See Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. +-} + data TcSEnv = TcSEnv { tcs_ev_binds :: EvBindsVar, @@ -869,13 +899,11 @@ data TcSEnv tcs_inerts :: IORef InertSet, -- Current inert set - -- Whether to throw an exception if we come across an insoluble constraint. - -- Used to fail-fast when checking for hole-fits. See Note [Speeding up - -- valid hole-fits]. - tcs_abort_on_insoluble :: Bool, + -- | The mode of operation for the constraint solver. + -- See Note [TcSMode] + tcs_mode :: TcSMode, - -- See Note [WorkList priorities] in GHC.Tc.Solver.InertSet - tcs_worklist :: IORef WorkList -- Current worklist + tcs_worklist :: IORef WorkList } --------------- @@ -946,9 +974,9 @@ addErrTcS = wrapTcS . TcM.addErr panicTcS doc = pprPanic "GHC.Tc.Solver.Monad" doc tryEarlyAbortTcS :: TcS () --- Abort (fail in the monad) if the abort_on_insoluble flag is on +-- Abort (fail in the monad) if the mode is TcSEarlyAbort tryEarlyAbortTcS - = mkTcS (\env -> when (tcs_abort_on_insoluble env) TcM.failM) + = mkTcS (\env -> when (tcs_mode env == TcSEarlyAbort) TcM.failM) -- | Emit a warning within the 'TcS' monad at the location given by the 'CtLoc'. ctLocWarnTcS :: CtLoc -> TcRnMessage -> TcS () @@ -1018,7 +1046,60 @@ runTcS tcs runTcSEarlyAbort :: TcS a -> TcM a runTcSEarlyAbort tcs = do { ev_binds_var <- TcM.newTcEvBinds - ; runTcSWithEvBinds' True True ev_binds_var tcs } + ; runTcSWithEvBinds' True TcSEarlyAbort ev_binds_var tcs } + +-- | Run the 'TcS' monad in 'TcSFullySolve' mode, which either fully solves +-- each individual constraint or leaves it alone. See Note [TcSFullySolve]. +runTcSFullySolve :: EvBindsVar -> TcS a -> TcM a +runTcSFullySolve ev_binds_var tcs + = runTcSWithEvBinds' True TcSFullySolve ev_binds_var tcs + +{- Note [TcSFullySolve] +~~~~~~~~~~~~~~~~~~~~~~~ +The TcSFullySolve mode is a specialized constraint solving mode that guarantees +each constraint is either: + - Fully solved with no free evidence variables, or + - Left completely untouched (no simplification at all) + +Examples: + + * [W] Eq [a]. + + In TcSFullySolve mode, we **do not** simplify this constraint to [W] Eq a, + using the top-level Eq instance; instead we leave it alone as [W] Eq [a]. + + * [W] forall x. Eq x => Eq (f x). + + In TcSFullySolve mode, we **do not** process this quantified constraint by + creating a new implication constraint; we leave it alone instead. + + * [W] Eq (Maybe Int). + + This constraint is solved fully, using two top-level Eq instances. + + * [W] forall x. Eq x => Eq [x]. + + This constraint is solved fully as well, using the Eq instance for lists. + +The main observation is that, in TcSFullySolve mode, we should not take any +**irreversible** steps. We can't run instances in reverse, nor recover the +original quantified constraint from the generated implication, so in these +two cases (and these two cases only), in the solver, we call the special +function `solveCompletelyIfRequired`. This function recursively calls the +solver but in TcSVanilla mode (i.e. full-blown solving, with no restrictions). +If this recursive call manages to solve all the remaining constraints fully, +then we proceed with that outcome (i.e. we continue with that inert set, etc). +Otherwise, discard everything that happened in the recursive call, and continue +with the original constraint unchanged. + +This functionality is crucially used by the specialiser, for which such +irreversible constraint solving steps are actively harmful, as described in +Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. + +In the future, we could consider re-using this functionality for the short-cut +solver (see Note [Shortcut solving] in GHC.Tc.Solver.Dict), but we would have to +be wary of the performance implications. +-} -- | This can deal only with equality constraints. runTcSEqualities :: TcS a -> TcM a @@ -1031,7 +1112,7 @@ runTcSEqualities thing_inside runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet) runTcSInerts inerts tcs = do ev_binds_var <- TcM.newTcEvBinds - runTcSWithEvBinds' False False ev_binds_var $ do + runTcSWithEvBinds' False TcSVanilla ev_binds_var $ do setInertSet inerts a <- tcs new_inerts <- getInertSet @@ -1040,17 +1121,17 @@ runTcSInerts inerts tcs = do runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds = runTcSWithEvBinds' True False +runTcSWithEvBinds = runTcSWithEvBinds' True TcSVanilla -runTcSWithEvBinds' :: Bool -- ^ Restore type variable cycles afterwards? +runTcSWithEvBinds' :: Bool -- True <=> restore type equality cycles -- Don't if you want to reuse the InertSet. -- See also Note [Type equality cycles] -- in GHC.Tc.Solver.Equality - -> Bool + -> TcSMode -> EvBindsVar -> TcS a -> TcM a -runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs +runTcSWithEvBinds' restore_cycles mode ev_binds_var tcs = do { unified_var <- TcM.newTcRef 0 ; step_count <- TcM.newTcRef 0 ; inert_var <- TcM.newTcRef emptyInert @@ -1061,7 +1142,7 @@ runTcSWithEvBinds' restore_cycles abort_on_insoluble ev_binds_var tcs , tcs_unif_lvl = unif_lvl_var , tcs_count = step_count , tcs_inerts = inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = wl_var } -- Run the computation @@ -1123,7 +1204,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_inerts = old_inert_var , tcs_count = count , tcs_unif_lvl = unif_lvl - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode } -> do { inerts <- TcM.readTcRef old_inert_var ; let nest_inert = inerts { inert_cycle_breakers = pushCycleBreakerVarStack @@ -1138,7 +1219,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_ev_binds = ref , tcs_unified = unified_var , tcs_inerts = new_inert_var - , tcs_abort_on_insoluble = abort_on_insoluble + , tcs_mode = mode , tcs_worklist = new_wl_var } ; res <- TcM.setTcLevel inner_tclvl $ thing_inside nest_env @@ -1153,7 +1234,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) #endif ; return res } -nestTcS :: TcS a -> TcS a +nestTcS :: TcS a -> TcS a -- Use the current untouchables, augmenting the current -- evidence bindings, and solved dictionaries -- But have no effect on the InertCans, or on the inert_famapp_cache ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RecursiveDo #-} module GHC.Tc.Solver.Solve ( @@ -5,6 +6,7 @@ module GHC.Tc.Solver.Solve ( solveWanteds, -- Solves WantedConstraints solveSimpleGivens, -- Solves [Ct] solveSimpleWanteds, -- Solves Cts + solveCompletelyIfRequired, setImplicationStatus ) where @@ -51,6 +53,7 @@ import GHC.Driver.Session import Data.List( deleteFirstsBy ) import Control.Monad +import Data.Foldable ( for_, traverse_ ) import qualified Data.Semigroup as S import Data.Void( Void ) @@ -1217,6 +1220,12 @@ solveForAll ev@(CtWanted { ctev_dest = dest, ctev_rewriters = rewriters, ctev_lo -- This setSrcSpan is important: the emitImplicationTcS uses that -- TcLclEnv for the implication, and that in turn sets the location -- for the Givens when solving the constraint (#21006) + + -- We are about to do something irreversible (turning a quantified constraint + -- into an implication), so wrap the inner call in solveCompletelyIfRequired + -- to ensure we can roll back if we can't solve the implication fully. + -- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. + solveCompletelyIfRequired (Left ev) $ do { let empty_subst = mkEmptySubst $ mkInScopeSet $ tyCoVarsOfTypes (pred:theta) `delVarSetList` tvs is_qc = IsQC (ctLocOrigin loc) @@ -1298,7 +1307,7 @@ Note [Solving a Given forall-constraint] For a Given constraint [G] df :: forall ab. (Eq a, Ord b) => C x a b we just add it to TcS's local InstEnv of known instances, -via addInertForall. Then, if we look up (C x Int Bool), say, +via addInertForAll. Then, if we look up (C x Int Bool), say, we'll find a match in the InstEnv. @@ -1539,3 +1548,109 @@ runTcPluginSolvers solvers all_cts CtWanted {} -> (givens, (ev,ct):wanteds) +-------------------------------------------------------------------------------- + +-- | If the mode is 'TcSFullySolve', attempt to fully solve the Wanted +-- constraints that arise from 'thing_inside'; returning whether this was +-- successful. +-- +-- If not in 'TcSFullySolve' mode, simply run 'thing_inside'. +-- +-- See Note [TcSFullySolve] in GHC.Tc.Solver.Monad. +solveCompletelyIfRequired :: Either CtEvidence DictCt -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) +solveCompletelyIfRequired dict_or_qc (TcS thing_inside) + = TcS $ \ env@(TcSEnv { tcs_ev_binds = outer_ev_binds_var + , tcs_unified = outer_unified_var + , tcs_inerts = outer_inert_var + , tcs_count = outer_count + , tcs_mode = mode + }) -> + case mode of + TcSFullySolve -> + do { traceTc "solveCompletelyIfRequired {" empty + -- Create a fresh environment for the inner computation + ; outer_inerts <- TcM.readTcRef outer_inert_var + ; let outer_givens = inertGivens outer_inerts + -- Keep the ambient Given inerts, but drop the Wanteds. + ; new_inert_var <- TcM.newTcRef outer_givens + ; new_wl_var <- TcM.newTcRef emptyWorkList + ; new_ev_binds_var <- TcM.newTcEvBinds + ; new_unified_var <- TcM.newTcRef 0 + ; new_count <- TcM.newTcRef 0 + ; new_unif_lvl <- TcM.newTcRef Nothing + + ; let + inner_env = + TcSEnv + -- KEY part: recur with TcSVanilla + { tcs_mode = TcSVanilla + + -- Use new variables for the inner computation, because + -- we may want to discard its state entirely. + , tcs_count = new_count + , tcs_unif_lvl = new_unif_lvl + , tcs_ev_binds = new_ev_binds_var + , tcs_unified = new_unified_var + , tcs_inerts = new_inert_var + , tcs_worklist = new_wl_var + } + + -- Solve the constraint + ; let + ct = case dict_or_qc of + Left qci_ev -> mkNonCanonical qci_ev + Right dict_ct -> CDictCan dict_ct + wc = emptyWC { wc_simple = unitBag ct } + ; traceTc "solveCompletelyIfRequired solveWanteds" $ + vcat [ text "ct:" <+> ppr ct + ] + ; solved_wc <- unTcS (solveWanteds wc) inner_env + + ; if isSolvedWC solved_wc + then + do { -- The constraint was fully solved. Continue with + -- the inner solver state. + ; traceTc "solveCompletelyIfRequired: fully solved }" $ + vcat [ text "ct:" <+> ppr ct + , text "solved_wc:" <+> ppr solved_wc ] + + -- Add new evidence bindings to the existing ones + ; inner_ev_binds <- TcM.getTcEvBindsMap new_ev_binds_var + ; outer_ev_binds <- TcM.getTcEvBindsMap outer_ev_binds_var + ; let merged_ev_binds = outer_ev_binds `unionEvBindMap` inner_ev_binds + ; TcM.setTcEvBindsMap outer_ev_binds_var merged_ev_binds + + -- Update the outer unified, count, and unif_lvl variables + ; inner_unified <- TcM.readTcRef new_unified_var + ; inner_count <- TcM.readTcRef new_count + ; inner_unif_lvl <- TcM.readTcRef new_unif_lvl + ; TcM.updTcRef outer_unified_var (+ inner_unified) + ; TcM.updTcRef outer_count (+ inner_count) + ; for_ inner_unif_lvl $ \inner_lvl -> + unTcS (setUnificationFlag inner_lvl) env + + -- Keep the outer inert set and work list: the inner work + -- list is empty, and there are no leftover unsolved + -- Wanteds. + -- However, we **must not** drop solved implications, due + -- to Note [Free vars of EvFun] in GHC.Tc.Types.Evidence. + ; traverse_ ( ( `unTcS` env ) . TcS.emitImplication ) $ wc_impl solved_wc + ; return $ Stop (ctEvidence ct) (text "Fully solved:" <+> ppr ct) + } + else + do { traceTc "solveCompletelyIfRequired: unsolved }" $ + vcat [ text "ct:" <+> ppr ct + , text "solved_wc:" <+> ppr solved_wc ] + -- Failed to fully solve the constraint: + -- + -- - discard the inner solver state, + -- - add the original constraint as an inert. + ; ( `unTcS` env ) $ case dict_or_qc of + Left qci_ev -> + updInertIrreds (IrredCt qci_ev IrredShapeReason) + Right dict_ct -> + updInertDicts dict_ct + ; return $ Stop (ctEvidence ct) (text "Not fully solved; kept as inert:" <+> ppr ct) + } } + _notFullySolveMode -> + thing_inside env ===================================== compiler/GHC/Tc/Solver/Solve.hs-boot ===================================== @@ -0,0 +1,11 @@ +module GHC.Tc.Solver.Solve where + +import GHC.Prelude + ( Either ) +import GHC.Tc.Solver.Monad + ( StopOrContinue, TcS ) +import GHC.Tc.Types.Constraint + ( CtEvidence, DictCt ) + +solveCompletelyIfRequired + :: Either CtEvidence DictCt -> TcS (StopOrContinue a) -> TcS (StopOrContinue a) ===================================== compiler/GHC/Tc/Solver/Types.hs ===================================== @@ -14,6 +14,7 @@ module GHC.Tc.Solver.Types ( TcAppMap, emptyTcAppMap, isEmptyTcAppMap, insertTcApp, alterTcApp, filterTcAppMap, + mapMaybeTcAppMap, tcAppMapToBag, foldTcAppMap, delTcApp, EqualCtList, filterEqualCtList, addToEqualCtList @@ -114,6 +115,16 @@ filterTcAppMap f m = mapMaybeDTyConEnv one_tycon m where filtered_tm = filterTM f tm +mapMaybeTcAppMap :: forall a b. (a -> Maybe b) -> TcAppMap a -> TcAppMap b +mapMaybeTcAppMap f m = mapMaybeDTyConEnv one_tycon m + where + one_tycon :: ListMap LooseTypeMap a -> Maybe (ListMap LooseTypeMap b) + one_tycon tm + | isEmptyTM mapped_tm = Nothing + | otherwise = Just mapped_tm + where + mapped_tm = mapMaybeTM f tm + tcAppMapToBag :: TcAppMap a -> Bag a tcAppMapToBag m = foldTcAppMap consBag m emptyBag ===================================== compiler/GHC/Tc/Types/Evidence.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Tc.Types.Evidence ( -- * Evidence bindings TcEvBinds(..), EvBindsVar(..), - EvBindMap(..), emptyEvBindMap, extendEvBinds, + EvBindMap(..), emptyEvBindMap, extendEvBinds, unionEvBindMap, lookupEvBind, evBindMapBinds, foldEvBindMap, nonDetStrictFoldEvBindMap, filterEvBindMap, @@ -433,6 +433,11 @@ extendEvBinds bs ev_bind (eb_lhs ev_bind) ev_bind } +-- | Union two evidence binding maps +unionEvBindMap :: EvBindMap -> EvBindMap -> EvBindMap +unionEvBindMap (EvBindMap env1) (EvBindMap env2) = + EvBindMap { ev_bind_varenv = plusDVarEnv env1 env2 } + isEmptyEvBindMap :: EvBindMap -> Bool isEmptyEvBindMap (EvBindMap m) = isEmptyDVarEnv m ===================================== compiler/GHC/Types/Var/Env.hs ===================================== @@ -74,7 +74,8 @@ module GHC.Types.Var.Env ( -- * TidyEnv and its operation TidyEnv, - emptyTidyEnv, mkEmptyTidyEnv, delTidyEnvList + emptyTidyEnv, mkEmptyTidyEnv, delTidyEnvList, + mapMaybeDVarEnv ) where import GHC.Prelude @@ -656,6 +657,9 @@ mapDVarEnv = mapUDFM filterDVarEnv :: (a -> Bool) -> DVarEnv a -> DVarEnv a filterDVarEnv = filterUDFM +mapMaybeDVarEnv :: (a -> Maybe b) -> DVarEnv a -> DVarEnv b +mapMaybeDVarEnv f = mapMaybeUDFM f + alterDVarEnv :: (Maybe a -> Maybe a) -> DVarEnv a -> Var -> DVarEnv a alterDVarEnv = alterUDFM ===================================== testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs ===================================== @@ -17,7 +17,6 @@ import Data.Proxy f1 :: ( Num a, Eq b ) => a -> b -> Int f1 _ _ = 111 - -- Make sure we don't generate a rule with an LHS of the form -- -- forall @e (d :: Eq e). f1 @[e] ($fEqList d) = ... @@ -56,12 +55,18 @@ f3 z = z == z -------------------------------------------------------------------------------- -f4 :: Monad m => a -> m a +f4 :: (Eq a, Monad m) => a -> m a f4 = return -- Check we can deal with locally quantified variables in constraints, -- in this case 'Monad (ST s)'. -{-# SPECIALISE f4 :: b -> ST s b #-} +{-# SPECIALISE f4 :: forall s b. Eq b => b -> ST s b #-} + +f4_qc :: (Eq a, forall m. Monad m => Monad (t m)) => t m a -> () +f4_qc _ = () + +-- Like 'f4' but with a quantified constraint. +{-# SPECIALISE f4_qc :: forall r n b. (forall m. Monad m => Monad (r m)) => r n Int -> () #-} -------------------------------------------------------------------------------- ===================================== testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr ===================================== @@ -26,10 +26,17 @@ forall (@c) (df :: forall x. Eq x => Eq [x]) ($dEq :: Eq c). f3 @c @[] $dEq df = f3_$sf1 @c $dEq -"USPEC f4 @(ST s) @_" - forall (@b) (@s) ($dMonad :: Monad (ST s)). - f4 @(ST s) @b $dMonad +"USPEC f4 @_ @(ST s)" + forall (@s) (@b) ($dMonad :: Monad (ST s)) ($dEq :: Eq b). + f4 @b @(ST s) $dEq $dMonad = $fApplicativeST_$cpure @s @b +"USPEC f4_qc @Int @_ @_" + forall (@(n :: * -> *)) + (@(r :: (* -> *) -> * -> *)) + (df :: forall (m :: * -> *). Monad m => Monad (r m)) + ($dEq :: Eq Int). + f4_qc @Int @r @n $dEq df + = \ _ [Occ=Dead] -> () "USPEC f5 @(D Int)" forall ($dEq :: Eq (D Int)). f5 @(D Int) $dEq = f5_$sf5 "USPEC f5_qc @Int @D" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dbffc28b11f274baacae30224397fa09dce0bbbb...30049b74c302270ca4e0dfd18ef7eeaee815bd65 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dbffc28b11f274baacae30224397fa09dce0bbbb...30049b74c302270ca4e0dfd18ef7eeaee815bd65 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/10c32ced/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 19:18:25 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 07 Mar 2025 14:18:25 -0500 Subject: [Git][ghc/ghc][wip/nfdata-forcing] interfaces: Ensure that forceModIface deeply forces a ModIface Message-ID: <67cb4681abaf0_10a0e711dcd0-34@gitlab.mail> Matthew Pickering pushed to branch wip/nfdata-forcing at Glasgow Haskell Compiler / GHC Commits: 2fbdfc58 by Matthew Pickering at 2025-03-07T19:18:01+00:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time on disk. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory usages too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface. This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 23 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - libraries/ghc-boot/GHC/Serialized.hs Changes: ===================================== compiler/GHC/Core.hs ===================================== @@ -120,6 +120,8 @@ import Data.List.NonEmpty (nonEmpty) import qualified Data.List.NonEmpty as NE import Data.Word +import Control.DeepSeq + infixl 4 `mkApps`, `mkTyApps`, `mkVarApps`, `App`, `mkCoApps` -- Left associative, so that we can say (f `mkTyApps` xs `mkVarApps` ys) @@ -1185,6 +1187,10 @@ instance Binary IsOrphan where n <- get bh return $ NotOrphan n +instance NFData IsOrphan where + rnf IsOrphan = () + rnf (NotOrphan n) = rnf n + {- Note [Orphans] ~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Coercion/Axiom.hs ===================================== @@ -58,6 +58,7 @@ import GHC.Types.SrcLoc import qualified Data.Data as Data import Data.Array import Data.List ( mapAccumL ) +import Control.DeepSeq {- Note [Coercion axiom branches] @@ -559,6 +560,11 @@ instance Binary Role where 3 -> return Phantom _ -> panic ("get Role " ++ show tag) +instance NFData Role where + rnf Nominal = () + rnf Representational = () + rnf Phantom = () + {- ************************************************************************ * * ===================================== compiler/GHC/Core/DataCon.hs ===================================== @@ -112,6 +112,7 @@ import qualified Data.ByteString.Lazy as LBS import qualified Data.Data as Data import Data.Char import Data.List( find ) +import Control.DeepSeq {- Note [Data constructor representation] @@ -1075,6 +1076,16 @@ instance Binary SrcUnpackedness where 1 -> return SrcUnpack _ -> return NoSrcUnpack +instance NFData SrcStrictness where + rnf SrcLazy = () + rnf SrcStrict = () + rnf NoSrcStrict = () + +instance NFData SrcUnpackedness where + rnf SrcNoUnpack = () + rnf SrcUnpack = () + rnf NoSrcUnpack = () + -- | Compare strictness annotations eqHsBang :: HsImplBang -> HsImplBang -> Bool eqHsBang HsLazy HsLazy = True ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -181,6 +181,7 @@ import GHC.Settings.Constants import GHC.Utils.Misc import GHC.Types.Unique.Set import GHC.Unit.Module +import Control.DeepSeq import Language.Haskell.Syntax.Basic (FieldLabelString(..)) @@ -2916,6 +2917,10 @@ instance Binary Injectivity where _ -> do { xs <- get bh ; return (Injective xs) } } +instance NFData Injectivity where + rnf NotInjective = () + rnf (Injective xs) = rnf xs + -- | Returns whether or not this 'TyCon' is definite, or a hole -- that may be filled in at some later point. See Note [Skolem abstract data] tyConSkolem :: TyCon -> Bool ===================================== compiler/GHC/Data/Strict.hs ===================================== @@ -22,10 +22,15 @@ import GHC.Prelude hiding (Maybe(..), Either(..)) import Control.Applicative import Data.Semigroup import Data.Data +import Control.DeepSeq data Maybe a = Nothing | Just !a deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data) +instance NFData a => NFData (Maybe a) where + rnf Nothing = () + rnf (Just x) = rnf x + fromMaybe :: a -> Maybe a -> a fromMaybe d Nothing = d fromMaybe _ (Just x) = x ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -106,7 +106,5 @@ instance Outputable ModIfaceSelfRecomp where ])] instance NFData ModIfaceSelfRecomp where - -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so - -- I left it as a shallow force. rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -539,6 +539,14 @@ instance Binary IfaceLFInfo where 4 -> pure IfLFUnlifted _ -> panic "Invalid byte" +instance NFData IfaceLFInfo where + rnf = \case + IfLFReEntrant arity -> rnf arity + IfLFThunk updatable mb_fun -> rnf updatable `seq` rnf mb_fun + IfLFCon con -> rnf con + IfLFUnknown fun_flag -> rnf fun_flag + IfLFUnlifted -> () + {- Note [Versioning of instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2767,6 +2775,10 @@ getUnfoldingCache bh = do return (UnfoldingCache { uf_is_value = hnf, uf_is_conlike = conlike , uf_is_work_free = wf, uf_expandable = exp }) +seqUnfoldingCache :: IfUnfoldingCache -> () +seqUnfoldingCache (UnfoldingCache hnf conlike wf exp) = + rnf hnf `seq` rnf conlike `seq` rnf wf `seq` rnf exp `seq` () + infixl 9 .<<|. (.<<|.) :: (Num a, Bits a) => a -> Bool -> a x .<<|. b = (if b then (`setBit` 0) else id) (x `shiftL` 1) @@ -2837,12 +2849,10 @@ instance Binary IfaceExpr where putByte bh 13 put_ bh a put_ bh b - put_ bh (IfaceLitRubbish TypeLike r) = do + put_ bh (IfaceLitRubbish torc r) = do putByte bh 14 put_ bh r - put_ bh (IfaceLitRubbish ConstraintLike r) = do - putByte bh 15 - put_ bh r + put_ bh torc get bh = do h <- getByte bh case h of @@ -2886,9 +2896,8 @@ instance Binary IfaceExpr where b <- get bh return (IfaceECase a b) 14 -> do r <- get bh - return (IfaceLitRubbish TypeLike r) - 15 -> do r <- get bh - return (IfaceLitRubbish ConstraintLike r) + torc <- get bh + return (IfaceLitRubbish torc r) _ -> panic ("get IfaceExpr " ++ show h) instance Binary IfaceTickish where @@ -3047,31 +3056,31 @@ instance NFData IfaceDecl where rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 IfaceData f1 f2 f3 f4 f5 f6 f7 f8 f9 -> - f1 `seq` seqList f2 `seq` f3 `seq` f4 `seq` f5 `seq` + rnf f1 `seq` seqList f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` rnf f9 IfaceSynonym f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 IfaceFamily f1 f2 f3 f4 f5 f6 -> - rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 `seq` f6 `seq` () + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` () IfaceClass f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 IfaceAxiom nm tycon role ax -> rnf nm `seq` rnf tycon `seq` - role `seq` + rnf role `seq` rnf ax IfacePatSyn f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 -> - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` f6 `seq` - rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` f11 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 `seq` () instance NFData IfaceAxBranch where rnf (IfaceAxBranch f1 f2 f3 f4 f5 f6 f7) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` rnf f7 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 instance NFData IfaceClassBody where rnf = \case @@ -3089,7 +3098,7 @@ instance NFData IfaceAT where rnf (IfaceAT f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceClassOp where - rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` f3 `seq` () + rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` () instance NFData IfaceTyConParent where rnf = \case @@ -3104,14 +3113,17 @@ instance NFData IfaceConDecls where instance NFData IfaceConDecl where rnf (IfCon f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` - rnf f7 `seq` rnf f8 `seq` f9 `seq` rnf f10 `seq` rnf f11 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 instance NFData IfaceSrcBang where - rnf (IfSrcBang f1 f2) = f1 `seq` f2 `seq` () + rnf (IfSrcBang f1 f2) = rnf f1 `seq` rnf f2 `seq` () instance NFData IfaceBang where - rnf x = x `seq` () + rnf IfNoBang = () + rnf IfStrict = () + rnf IfUnpack = () + rnf (IfUnpackCo co) = rnf co instance NFData IfaceIdDetails where rnf = \case @@ -3125,23 +3137,22 @@ instance NFData IfaceInfoItem where rnf = \case HsArity a -> rnf a HsDmdSig str -> seqDmdSig str - HsInline p -> p `seq` () -- TODO: seq further? + HsInline p -> rnf p `seq` () HsUnfold b unf -> rnf b `seq` rnf unf HsNoCafRefs -> () - HsCprSig cpr -> cpr `seq` () - HsLFInfo lf_info -> lf_info `seq` () -- TODO: seq further? - HsTagSig sig -> sig `seq` () + HsCprSig cpr -> seqCprSig cpr `seq` () + HsLFInfo lf_info -> rnf lf_info `seq` () + HsTagSig sig -> seqTagSig sig `seq` () instance NFData IfGuidance where rnf = \case IfNoGuidance -> () - IfWhen a b c -> a `seq` b `seq` c `seq` () + IfWhen a b c -> rnf a `seq` rnf b `seq` rnf c `seq` () instance NFData IfaceUnfolding where rnf = \case - IfCoreUnfold src cache guidance expr -> src `seq` cache `seq` rnf guidance `seq` rnf expr + IfCoreUnfold src cache guidance expr -> rnf src `seq` seqUnfoldingCache cache `seq` rnf guidance `seq` rnf expr IfDFunUnfold bndrs exprs -> rnf bndrs `seq` rnf exprs - -- See Note [UnfoldingCache] in GHC.Core for why it suffices to merely `seq` on cache instance NFData IfaceExpr where rnf = \case @@ -3152,13 +3163,13 @@ instance NFData IfaceExpr where IfaceTuple sort exprs -> sort `seq` rnf exprs IfaceLam bndr expr -> rnf bndr `seq` rnf expr IfaceApp e1 e2 -> rnf e1 `seq` rnf e2 - IfaceCase e nm alts -> rnf e `seq` nm `seq` rnf alts + IfaceCase e nm alts -> rnf e `seq` rnf nm `seq` rnf alts IfaceECase e ty -> rnf e `seq` rnf ty IfaceLet bind e -> rnf bind `seq` rnf e IfaceCast e co -> rnf e `seq` rnf co - IfaceLit l -> l `seq` () -- FIXME - IfaceLitRubbish tc r -> tc `seq` rnf r `seq` () - IfaceFCall fc ty -> fc `seq` rnf ty + IfaceLit l -> rnf l `seq` () + IfaceLitRubbish tc r -> rnf tc `seq` rnf r `seq` () + IfaceFCall fc ty -> rnf fc `seq` rnf ty IfaceTick tick e -> rnf tick `seq` rnf e instance NFData IfaceAlt where @@ -3192,22 +3203,22 @@ instance NFData IfaceFamTyConFlav where instance NFData IfaceTickish where rnf = \case IfaceHpcTick m i -> rnf m `seq` rnf i - IfaceSCC cc b1 b2 -> cc `seq` rnf b1 `seq` rnf b2 - IfaceSource src str -> src `seq` rnf str + IfaceSCC cc b1 b2 -> rnf cc `seq` rnf b1 `seq` rnf b2 + IfaceSource src str -> rnf src `seq` rnf str IfaceBreakpoint m i fvs -> rnf m `seq` rnf i `seq` rnf fvs instance NFData IfaceConAlt where rnf = \case IfaceDefaultAlt -> () IfaceDataAlt nm -> rnf nm - IfaceLitAlt lit -> lit `seq` () + IfaceLitAlt lit -> rnf lit `seq` () instance NFData IfaceCompleteMatch where rnf (IfaceCompleteMatch f1 mtc) = rnf f1 `seq` rnf mtc instance NFData IfaceRule where rnf (IfaceRule f1 f2 f3 f4 f5 f6 f7 f8) = - rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` f8 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` () instance NFData IfaceDefault where rnf (IfaceDefault f1 f2 f3) = @@ -3215,11 +3226,11 @@ instance NFData IfaceDefault where instance NFData IfaceFamInst where rnf (IfaceFamInst f1 f2 f3 f4) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` () instance NFData IfaceClsInst where rnf (IfaceClsInst f1 f2 f3 f4 f5 f6) = - f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` f5 `seq` rnf f6 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 instance NFData IfaceWarnings where rnf = \case @@ -3227,12 +3238,12 @@ instance NFData IfaceWarnings where IfWarnSome vs ds -> rnf vs `seq` rnf ds instance NFData IfaceWarningTxt where - rnf = \case - IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 - IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 + rnf = \case + IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 + IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 instance NFData IfaceStringLiteral where - rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 + rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceAnnotation where - rnf (IfaceAnnotation f1 f2) = f1 `seq` f2 `seq` () + rnf (IfaceAnnotation f1 f2) = rnf f1 `seq` rnf f2 `seq` () ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -2577,6 +2577,11 @@ instance Binary (DefMethSpec IfaceType) where 0 -> return VanillaDM _ -> do { t <- get bh; return (GenericDM t) } +instance NFData (DefMethSpec IfaceType) where + rnf = \case + VanillaDM -> () + GenericDM t -> rnf t + instance NFData IfaceType where rnf = \case IfaceFreeTyVar f1 -> f1 `seq` () ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -148,6 +148,7 @@ import qualified GHC.Boot.TH.Ppr as TH #if defined(HAVE_INTERNAL_INTERPRETER) import Unsafe.Coerce ( unsafeCoerce ) import GHC.Desugar ( AnnotationWrapper(..) ) +import Control.DeepSeq #endif import Control.Monad @@ -1039,11 +1040,7 @@ convertAnnotationWrapper fhv = do -- annotation are exposed at this point. This is also why we are -- doing all this stuff inside the context of runMeta: it has the -- facilities to deal with user error in a meta-level expression - seqSerialized serialized `seq` serialized - --- | Force the contents of the Serialized value so weknow it doesn't contain any bottoms -seqSerialized :: Serialized -> () -seqSerialized (Serialized the_type bytes) = the_type `seq` bytes `seqList` () + rnf serialized `seq` serialized #endif ===================================== compiler/GHC/Types/Annotations.hs ===================================== @@ -31,7 +31,7 @@ import Control.Monad import Data.Maybe import Data.Typeable import Data.Word ( Word8 ) - +import Control.DeepSeq -- | Represents an annotation after it has been sufficiently desugared from -- it's initial form of 'GHC.Hs.Decls.AnnDecl' @@ -71,6 +71,10 @@ instance Binary name => Binary (AnnTarget name) where 0 -> liftM NamedTarget $ get bh _ -> liftM ModuleTarget $ get bh +instance NFData name => NFData (AnnTarget name) where + rnf (NamedTarget n) = rnf n + rnf (ModuleTarget m) = rnf m + instance Outputable Annotation where ppr ann = ppr (ann_target ann) ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -529,6 +529,10 @@ instance Binary FunctionOrData where 1 -> return IsData _ -> panic "Binary FunctionOrData" +instance NFData FunctionOrData where + rnf IsFunction = () + rnf IsData = () + {- ************************************************************************ * * @@ -871,6 +875,9 @@ data OverlapMode -- See Note [Rules for instance lookup] in GHC.Core.InstEnv instance Outputable OverlapFlag where ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag) +instance NFData OverlapFlag where + rnf (OverlapFlag mode safe) = rnf mode `seq` rnf safe + instance Outputable OverlapMode where ppr (NoOverlap _) = empty ppr (Overlappable _) = text "[overlappable]" @@ -879,6 +886,14 @@ instance Outputable OverlapMode where ppr (Incoherent _) = text "[incoherent]" ppr (NonCanonical _) = text "[noncanonical]" +instance NFData OverlapMode where + rnf (NoOverlap s) = rnf s + rnf (Overlappable s) = rnf s + rnf (Overlapping s) = rnf s + rnf (Overlaps s) = rnf s + rnf (Incoherent s) = rnf s + rnf (NonCanonical s) = rnf s + instance Binary OverlapMode where put_ bh (NoOverlap s) = putByte bh 0 >> put_ bh s put_ bh (Overlaps s) = putByte bh 1 >> put_ bh s @@ -1860,6 +1875,14 @@ instance Binary Activation where ab <- get bh return (ActiveAfter src ab) +instance NFData Activation where + rnf = \case + AlwaysActive -> () + NeverActive -> () + ActiveBefore src aa -> rnf src `seq` rnf aa + ActiveAfter src ab -> rnf src `seq` rnf ab + FinalActive -> () + instance Outputable RuleMatchInfo where ppr ConLike = text "CONLIKE" ppr FunLike = text "FUNLIKE" @@ -1872,6 +1895,11 @@ instance Binary RuleMatchInfo where if h == 1 then return ConLike else return FunLike +instance NFData RuleMatchInfo where + rnf = \case + ConLike -> () + FunLike -> () + instance Outputable InlineSpec where ppr (Inline src) = text "INLINE" <+> pprWithSourceText src empty ppr (NoInline src) = text "NOINLINE" <+> pprWithSourceText src empty @@ -1906,6 +1934,14 @@ instance Binary InlineSpec where s <- get bh return (Opaque s) +instance NFData InlineSpec where + rnf = \case + Inline s -> rnf s + NoInline s -> rnf s + Inlinable s -> rnf s + Opaque s -> rnf s + NoUserInlinePrag -> () + instance Outputable InlinePragma where ppr = pprInline @@ -1925,6 +1961,9 @@ instance Binary InlinePragma where d <- get bh return (InlinePragma s a b c d) +instance NFData InlinePragma where + rnf (InlinePragma s a b c d) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c `seq` rnf d + -- | Outputs string for pragma name for any of INLINE/INLINABLE/NOINLINE. This -- differs from the Outputable instance for the InlineSpec type where the pragma -- name string as well as the accompanying SourceText (if any) is printed. @@ -2017,6 +2056,13 @@ instance Binary UnfoldingSource where 2 -> return StableSystemSrc _ -> return VanillaSrc +instance NFData UnfoldingSource where + rnf = \case + CompulsorySrc -> () + StableUserSrc -> () + StableSystemSrc -> () + VanillaSrc -> () + instance Outputable UnfoldingSource where ppr CompulsorySrc = text "Compulsory" ppr StableUserSrc = text "StableUser" @@ -2161,6 +2207,19 @@ data TypeOrConstraint = TypeLike | ConstraintLike deriving( Eq, Ord, Data ) +instance Binary TypeOrConstraint where + put_ bh = \case + TypeLike -> putByte bh 0 + ConstraintLike -> putByte bh 1 + get bh = getByte bh >>= \case + 0 -> pure TypeLike + 1 -> pure ConstraintLike + _ -> panic "TypeOrConstraint.get: invalid value" + +instance NFData TypeOrConstraint where + rnf = \case + TypeLike -> () + ConstraintLike -> () {- ********************************************************************* * * ===================================== compiler/GHC/Types/CostCentre.hs ===================================== @@ -36,6 +36,7 @@ import GHC.Utils.Outputable import GHC.Types.SrcLoc import GHC.Data.FastString import GHC.Types.CostCentre.State +import Control.DeepSeq import Data.Data @@ -395,6 +396,21 @@ instance Binary CostCentre where -- CostCentre in the original module, it is not used by importing -- modules. +instance NFData CostCentre where + rnf (NormalCC aa ab ac ad) = rnf aa `seq` rnf ab `seq` rnf ac `seq` rnf ad + rnf (AllCafsCC ae ad) = rnf ae `seq` rnf ad + +instance NFData CCFlavour where + rnf CafCC = () + rnf (IndexedCC flav i) = rnf flav `seq` rnf i + +instance NFData IndexedCCFlavour where + rnf ExprCC = () + rnf DeclCC = () + rnf HpcCC = () + rnf LateCC = () + rnf CallerCC = () + getAllCAFsCC :: Module -> (CostCentre, CostCentreStack) getAllCAFsCC this_mod = let ===================================== compiler/GHC/Types/CostCentre/State.hs ===================================== @@ -15,6 +15,7 @@ import GHC.Data.FastString.Env import Data.Data import GHC.Utils.Binary +import Control.DeepSeq -- | Per-module state for tracking cost centre indices. -- @@ -29,6 +30,9 @@ newCostCentreState = CostCentreState emptyFsEnv newtype CostCentreIndex = CostCentreIndex { unCostCentreIndex :: Int } deriving (Eq, Ord, Data, Binary) +instance NFData CostCentreIndex where + rnf (CostCentreIndex i) = rnf i + -- | Get a new index for a given cost centre name. getCCIndex :: FastString -> CostCentreState ===================================== compiler/GHC/Types/ForeignCall.hs ===================================== @@ -30,6 +30,8 @@ import GHC.Types.SourceText ( SourceText, pprWithSourceText ) import Data.Char import Data.Data +import Control.DeepSeq (NFData(..)) + {- ************************************************************************ * * @@ -344,3 +346,31 @@ instance Binary Header where get bh = do s <- get bh h <- get bh return (Header s h) + +instance NFData ForeignCall where + rnf (CCall c) = rnf c + +instance NFData Safety where + rnf PlaySafe = () + rnf PlayInterruptible = () + rnf PlayRisky = () + +instance NFData CCallSpec where + rnf (CCallSpec t c s) = rnf t `seq` rnf c `seq` rnf s + +instance NFData CCallTarget where + rnf (StaticTarget s a b c) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c + rnf DynamicTarget = () + +instance NFData CCallConv where + rnf CCallConv = () + rnf StdCallConv = () + rnf PrimCallConv = () + rnf CApiConv = () + rnf JavaScriptCallConv = () + +instance NFData CType where + rnf (CType s mh fs) = rnf s `seq` rnf mh `seq` rnf fs + +instance NFData Header where + rnf (Header s h) = rnf s `seq` rnf h ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -84,6 +84,7 @@ import Data.Char import Data.Data ( Data ) import GHC.Exts( isTrue#, dataToTag#, (<#) ) import Numeric ( fromRat ) +import Control.DeepSeq {- ************************************************************************ @@ -204,6 +205,20 @@ instance Binary LitNumType where h <- getByte bh return (toEnum (fromIntegral h)) +instance NFData LitNumType where + rnf (LitNumBigNat) = () + rnf (LitNumInt) = () + rnf (LitNumInt8) = () + rnf (LitNumInt16) = () + rnf (LitNumInt32) = () + rnf (LitNumInt64) = () + rnf (LitNumWord) = () + rnf (LitNumWord8) = () + rnf (LitNumWord16) = () + rnf (LitNumWord32) = () + rnf (LitNumWord64) = () + + {- Note [BigNum literals] ~~~~~~~~~~~~~~~~~~~~~~ @@ -288,6 +303,16 @@ instance Binary Literal where return (LitNumber nt i) _ -> pprPanic "Binary:Literal" (int (fromIntegral h)) +instance NFData Literal where + rnf (LitChar c) = rnf c + rnf (LitNumber nt i) = rnf nt `seq` rnf i + rnf (LitString s) = rnf s + rnf LitNullAddr = () + rnf (LitFloat r) = rnf r + rnf (LitDouble r) = rnf r + rnf (LitLabel l1 k2) = rnf l1 `seq` rnf k2 + rnf (LitRubbish {}) = () -- LitRubbish is not contained within interface files. + -- See Note [Rubbish literals]. instance Outputable Literal where ppr = pprLiteral id ===================================== compiler/GHC/Types/SourceFile.hs ===================================== @@ -13,6 +13,7 @@ where import GHC.Prelude import GHC.Utils.Binary import GHC.Unit.Types +import Control.DeepSeq {- Note [HscSource types] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -53,6 +54,10 @@ data HsBootOrSig | Hsig -- ^ .hsig file deriving (Eq, Ord, Show) +instance NFData HsBootOrSig where + rnf HsBoot = () + rnf Hsig = () + data HscSource -- | .hs file = HsSrcFile @@ -73,6 +78,10 @@ hscSourceToIsBoot :: HscSource -> IsBootInterface hscSourceToIsBoot HsBootFile = IsBoot hscSourceToIsBoot _ = NotBoot +instance NFData HscSource where + rnf HsSrcFile = () + rnf (HsBootOrSig h) = rnf h + instance Binary HscSource where put_ bh HsSrcFile = putByte bh 0 put_ bh HsBootFile = putByte bh 1 ===================================== compiler/GHC/Types/SrcLoc.hs ===================================== @@ -223,7 +223,8 @@ data RealSrcLoc -- We use 'BufPos' in in GHC.Parser.PostProcess.Haddock to associate Haddock -- comments with parts of the AST using location information (#17544). newtype BufPos = BufPos { bufPos :: Int } - deriving (Eq, Ord, Show, Data) + deriving (Eq, Ord, Show, Data, NFData) + -- | Source Location data SrcLoc @@ -373,11 +374,13 @@ data RealSrcSpan } deriving Eq --- | StringBuffer Source Span data BufSpan = BufSpan { bufSpanStart, bufSpanEnd :: {-# UNPACK #-} !BufPos } deriving (Eq, Ord, Show, Data) +instance NFData BufSpan where + rnf (BufSpan a1 a2) = rnf a1 `seq` rnf a2 + instance Semigroup BufSpan where BufSpan start1 end1 <> BufSpan start2 end2 = BufSpan (min start1 start2) (max end1 end2) @@ -439,8 +442,18 @@ instance ToJson RealSrcSpan where end = JSObject [ ("line", JSInt srcSpanELine), ("column", JSInt srcSpanECol) ] +instance NFData RealSrcSpan where + rnf (RealSrcSpan' file line col endLine endCol) = rnf file `seq` rnf line `seq` rnf col `seq` rnf endLine `seq` rnf endCol instance NFData SrcSpan where - rnf x = x `seq` () + rnf (RealSrcSpan a1 a2) = rnf a1 `seq` rnf a2 + rnf (UnhelpfulSpan a1) = rnf a1 + +instance NFData UnhelpfulSpanReason where + rnf (UnhelpfulNoLocationInfo) = () + rnf (UnhelpfulWiredIn) = () + rnf (UnhelpfulInteractive) = () + rnf (UnhelpfulGenerated) = () + rnf (UnhelpfulOther a1) = rnf a1 getBufSpan :: SrcSpan -> Strict.Maybe BufSpan getBufSpan (RealSrcSpan _ mbspan) = mbspan ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -132,6 +132,7 @@ import GHC.Utils.Panic import GHC.Hs.Specificity () import Language.Haskell.Syntax.Specificity +import Control.DeepSeq import Data.Data @@ -734,6 +735,9 @@ instance (Binary tv, Binary vis) => Binary (VarBndr tv vis) where get bh = do { tv <- get bh; vis <- get bh; return (Bndr tv vis) } +instance (NFData tv, NFData vis) => NFData (VarBndr tv vis) where + rnf (Bndr tv vis) = rnf tv `seq` rnf vis + instance NamedThing tv => NamedThing (VarBndr tv flag) where getName (Bndr tv _) = getName tv ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -39,6 +39,7 @@ import Data.List (sortBy, sort, partition) import Data.Set (Set) import qualified Data.Set as Set import Data.Bifunctor +import Control.DeepSeq -- | Dependency information about ALL modules and packages below this one -- in the import hierarchy. This is the serialisable version of `ImportAvails`. @@ -104,6 +105,18 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +instance NFData Dependencies where + rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) + = rnf dmods + `seq` rnf dpkgs + `seq` rnf ppkgs + `seq` rnf hsigms + `seq` rnf tps + `seq` rnf bmods + `seq` rnf orphs + `seq` rnf finsts + `seq` () + -- | Extract information from the rename and typecheck phases to produce -- a dependencies information for the module being compiled. @@ -326,6 +339,13 @@ data Usage -- And of course, for modules that aren't imported directly we don't -- depend on their export lists +instance NFData Usage where + rnf (UsagePackageModule mod hash safe) = rnf mod `seq` rnf hash `seq` rnf safe `seq` () + rnf (UsageHomeModule mod uid hash entities exports safe) = rnf mod `seq` rnf uid `seq` rnf hash `seq` rnf entities `seq` rnf exports `seq` rnf safe `seq` () + rnf (UsageFile file hash label) = rnf file `seq` rnf hash `seq` rnf label `seq` () + rnf (UsageMergedRequirement mod hash) = rnf mod `seq` rnf hash `seq` () + rnf (UsageHomeModuleInterface mod uid hash) = rnf mod `seq` rnf uid `seq` rnf hash `seq` () + instance Binary Usage where put_ bh usg at UsagePackageModule{} = do putByte bh 0 ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -660,52 +660,46 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ - , mi_exports_, mi_fixities_, mi_warns_, mi_anns_ - , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ - , mi_fam_insts_, mi_rules_, mi_trust_, mi_trust_pkg_ - , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_ }) - = rnf mi_module_ - `seq` rnf mi_sig_of_ - `seq` mi_hsc_src_ - `seq` mi_hi_bytes_ - `seq` mi_deps_ - `seq` mi_exports_ - `seq` mi_fixities_ - `seq` rnf mi_warns_ - `seq` rnf mi_anns_ - `seq` rnf mi_decls_ - `seq` rnf mi_defaults_ - `seq` rnf mi_extra_decls_ - `seq` rnf mi_foreign_ - `seq` rnf mi_top_env_ - `seq` rnf mi_insts_ - `seq` rnf mi_fam_insts_ - `seq` rnf mi_rules_ - `seq` mi_trust_ - `seq` rnf mi_trust_pkg_ - `seq` rnf mi_complete_matches_ - `seq` rnf mi_docs_ - `seq` mi_final_exts_ - `seq` mi_ext_fields_ - `seq` () - -instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_mod_hash - , mi_orphan, mi_finsts, mi_exp_hash - , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn - , mi_hash_fn}) - = rnf mi_mod_hash - `seq` rnf mi_orphan - `seq` rnf mi_finsts - `seq` rnf mi_exp_hash - `seq` rnf mi_orphan_hash - `seq` rnf mi_decl_warn_fn - `seq` rnf mi_export_warn_fn - `seq` rnf mi_fix_fn - `seq` rnf mi_hash_fn + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + `seq` rnf a15 + `seq` rnf a16 + `seq` rnf a17 + `seq` rnf a18 + `seq` rnf a19 + `seq` rnf a20 + `seq` rnf a21 + `seq` rnf a22 + -- IfaceBinHandle + `seq` a23 + `seq` rnf a24 + + +instance NFData ModIfaceBackend where + rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 forceModIface :: ModIface -> IO () ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -517,6 +517,9 @@ newtype UnitId = UnitId } deriving (Data) +instance NFData UnitId where + rnf (UnitId fs) = rnf fs `seq` () + instance Binary UnitId where put_ bh (UnitId fs) = put_ bh fs get bh = do fs <- get bh; return (UnitId fs) @@ -704,6 +707,9 @@ data GenWithIsBoot mod = GWIB -- IsBootInterface: this is assumed to perform filtering of non-boot modules, -- e.g. in GHC.Driver.Env.hptModulesBelow +instance NFData mod => NFData (GenWithIsBoot mod) where + rnf (GWIB mod isBoot) = rnf mod `seq` rnf isBoot `seq` () + type ModuleNameWithIsBoot = GenWithIsBoot ModuleName type ModuleWithIsBoot = GenWithIsBoot Module ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,11 +2,11 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where -import Data.Data +import Data.Data (Data) import Data.Eq import Data.Ord import Data.Bool -import Data.Int (Int) +import Prelude import GHC.Data.FastString (FastString) import Control.DeepSeq @@ -134,5 +134,13 @@ data FixityDirection | InfixN deriving (Eq, Data) +instance NFData FixityDirection where + rnf InfixL = () + rnf InfixR = () + rnf InfixN = () + data Fixity = Fixity Int FixityDirection deriving (Eq, Data) + +instance NFData Fixity where + rnf (Fixity i d) = rnf i `seq` rnf d `seq` () ===================================== libraries/ghc-boot/GHC/Serialized.hs ===================================== @@ -22,11 +22,15 @@ import Prelude -- See note [Why do we import Prelude here?] import Data.Bits import Data.Word ( Word8 ) import Data.Data +import Control.DeepSeq -- | Represents a serialized value of a particular type. Attempts can be made to deserialize it at certain types data Serialized = Serialized TypeRep [Word8] +instance NFData Serialized where + rnf (Serialized tr ws) = rnf tr `seq` rnf ws + -- | Put a Typeable value that we are able to actually turn into bytes into a 'Serialized' value ready for deserialization later toSerialized :: forall a. Typeable a => (a -> [Word8]) -> a -> Serialized toSerialized serialize what = Serialized (typeOf what) (serialize what) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2fbdfc58a13f190582f1f23b0c0b374d91b04b00 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2fbdfc58a13f190582f1f23b0c0b374d91b04b00 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/6d999ccd/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 20:02:14 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Fri, 07 Mar 2025 15:02:14 -0500 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] cpuinfo.py: Provide RISC-V features Message-ID: <67cb50c6ead1d_10a0e74d5f3043e@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: 9554182b by Sven Tennie at 2025-03-07T21:02:07+01:00 cpuinfo.py: Provide RISC-V features - - - - - 1 changed file: - testsuite/driver/cpuinfo.py Changes: ===================================== testsuite/driver/cpuinfo.py ===================================== @@ -275,6 +275,12 @@ class DataSource: if ibm_features: return _run_and_get_stdout(['lsprop', ibm_features[0]]) + @staticmethod + def riscv_isa(): + # Expect all cores to support an equal ISA. + riscv_isa = '/proc/device-tree/cpus/cpu at 0/riscv,isa' + return _run_and_get_stdout(['cat', riscv_isa]) + @staticmethod def wmic_cpu(): return _run_and_get_stdout(['wmic', 'cpu', 'get', 'Name,CurrentClockSpeed,L2CacheSize,L3CacheSize,Description,Caption,Manufacturer', '/format:list']) @@ -2118,6 +2124,28 @@ def _get_cpu_info_from_ibm_pa_features(): g_trace.fail(err) return {} +def _get_cpu_info_from_riscv_isa(): + ''' + Returns the CPU info gathered from 'cat /proc/device-tree/cpus/cpu at 0/riscv,isa' + Returns {} if this file does not exist (i.e. we're not on RISC-V Linux) + ''' + g_trace.header('Tying to get info from lsprop ...') + + try: + returncode, output = DataSource.riscv_isa() + if output is None or returncode != 0: + g_trace.fail('Failed to cat /proc/device-tree/cpus/cpu at 0/riscv,isa. Skipping ...') + return {} + + info = { + 'flags' : output.split('_') + } + info = _filter_dict_keys_with_empty_values(info) + g_trace.success() + return info + except Exception as err: + g_trace.fail(err) + return {} def _get_cpu_info_from_cat_var_run_dmesg_boot(): ''' @@ -2717,6 +2745,9 @@ def _get_cpu_info_internal(): # Try lsprop ibm,pa-features _copy_new_fields(info, _get_cpu_info_from_ibm_pa_features()) + # Try device-tree riscv,isa + _copy_new_fields(info, _get_cpu_info_from_riscv_isa()) + # Try sysinfo _copy_new_fields(info, _get_cpu_info_from_sysinfo()) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9554182bb43848207eaa26cf618c4eccb3a7dff3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9554182bb43848207eaa26cf618c4eccb3a7dff3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/b38584bf/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 20:37:20 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 07 Mar 2025 15:37:20 -0500 Subject: [Git][ghc/ghc][wip/nfdata-forcing] interfaces: Ensure that forceModIface deeply forces a ModIface Message-ID: <67cb59007fb43_10a0e7889dfc1036@gitlab.mail> Matthew Pickering pushed to branch wip/nfdata-forcing at Glasgow Haskell Compiler / GHC Commits: c84e65f4 by Matthew Pickering at 2025-03-07T20:37:03+00:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time on disk. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory usages too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface. This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - libraries/ghc-boot/GHC/Serialized.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Core.hs ===================================== @@ -120,6 +120,8 @@ import Data.List.NonEmpty (nonEmpty) import qualified Data.List.NonEmpty as NE import Data.Word +import Control.DeepSeq + infixl 4 `mkApps`, `mkTyApps`, `mkVarApps`, `App`, `mkCoApps` -- Left associative, so that we can say (f `mkTyApps` xs `mkVarApps` ys) @@ -1185,6 +1187,10 @@ instance Binary IsOrphan where n <- get bh return $ NotOrphan n +instance NFData IsOrphan where + rnf IsOrphan = () + rnf (NotOrphan n) = rnf n + {- Note [Orphans] ~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Coercion/Axiom.hs ===================================== @@ -58,6 +58,7 @@ import GHC.Types.SrcLoc import qualified Data.Data as Data import Data.Array import Data.List ( mapAccumL ) +import Control.DeepSeq {- Note [Coercion axiom branches] @@ -559,6 +560,11 @@ instance Binary Role where 3 -> return Phantom _ -> panic ("get Role " ++ show tag) +instance NFData Role where + rnf Nominal = () + rnf Representational = () + rnf Phantom = () + {- ************************************************************************ * * ===================================== compiler/GHC/Core/DataCon.hs ===================================== @@ -112,6 +112,7 @@ import qualified Data.ByteString.Lazy as LBS import qualified Data.Data as Data import Data.Char import Data.List( find ) +import Control.DeepSeq {- Note [Data constructor representation] @@ -1075,6 +1076,16 @@ instance Binary SrcUnpackedness where 1 -> return SrcUnpack _ -> return NoSrcUnpack +instance NFData SrcStrictness where + rnf SrcLazy = () + rnf SrcStrict = () + rnf NoSrcStrict = () + +instance NFData SrcUnpackedness where + rnf SrcNoUnpack = () + rnf SrcUnpack = () + rnf NoSrcUnpack = () + -- | Compare strictness annotations eqHsBang :: HsImplBang -> HsImplBang -> Bool eqHsBang HsLazy HsLazy = True ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -181,6 +181,7 @@ import GHC.Settings.Constants import GHC.Utils.Misc import GHC.Types.Unique.Set import GHC.Unit.Module +import Control.DeepSeq import Language.Haskell.Syntax.Basic (FieldLabelString(..)) @@ -2916,6 +2917,10 @@ instance Binary Injectivity where _ -> do { xs <- get bh ; return (Injective xs) } } +instance NFData Injectivity where + rnf NotInjective = () + rnf (Injective xs) = rnf xs + -- | Returns whether or not this 'TyCon' is definite, or a hole -- that may be filled in at some later point. See Note [Skolem abstract data] tyConSkolem :: TyCon -> Bool ===================================== compiler/GHC/Data/Strict.hs ===================================== @@ -22,10 +22,15 @@ import GHC.Prelude hiding (Maybe(..), Either(..)) import Control.Applicative import Data.Semigroup import Data.Data +import Control.DeepSeq data Maybe a = Nothing | Just !a deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data) +instance NFData a => NFData (Maybe a) where + rnf Nothing = () + rnf (Just x) = rnf x + fromMaybe :: a -> Maybe a -> a fromMaybe d Nothing = d fromMaybe _ (Just x) = x ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -106,7 +106,5 @@ instance Outputable ModIfaceSelfRecomp where ])] instance NFData ModIfaceSelfRecomp where - -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so - -- I left it as a shallow force. rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -539,6 +539,14 @@ instance Binary IfaceLFInfo where 4 -> pure IfLFUnlifted _ -> panic "Invalid byte" +instance NFData IfaceLFInfo where + rnf = \case + IfLFReEntrant arity -> rnf arity + IfLFThunk updatable mb_fun -> rnf updatable `seq` rnf mb_fun + IfLFCon con -> rnf con + IfLFUnknown fun_flag -> rnf fun_flag + IfLFUnlifted -> () + {- Note [Versioning of instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2767,6 +2775,10 @@ getUnfoldingCache bh = do return (UnfoldingCache { uf_is_value = hnf, uf_is_conlike = conlike , uf_is_work_free = wf, uf_expandable = exp }) +seqUnfoldingCache :: IfUnfoldingCache -> () +seqUnfoldingCache (UnfoldingCache hnf conlike wf exp) = + rnf hnf `seq` rnf conlike `seq` rnf wf `seq` rnf exp `seq` () + infixl 9 .<<|. (.<<|.) :: (Num a, Bits a) => a -> Bool -> a x .<<|. b = (if b then (`setBit` 0) else id) (x `shiftL` 1) @@ -2837,12 +2849,10 @@ instance Binary IfaceExpr where putByte bh 13 put_ bh a put_ bh b - put_ bh (IfaceLitRubbish TypeLike r) = do + put_ bh (IfaceLitRubbish torc r) = do putByte bh 14 put_ bh r - put_ bh (IfaceLitRubbish ConstraintLike r) = do - putByte bh 15 - put_ bh r + put_ bh torc get bh = do h <- getByte bh case h of @@ -2886,9 +2896,8 @@ instance Binary IfaceExpr where b <- get bh return (IfaceECase a b) 14 -> do r <- get bh - return (IfaceLitRubbish TypeLike r) - 15 -> do r <- get bh - return (IfaceLitRubbish ConstraintLike r) + torc <- get bh + return (IfaceLitRubbish torc r) _ -> panic ("get IfaceExpr " ++ show h) instance Binary IfaceTickish where @@ -3047,31 +3056,31 @@ instance NFData IfaceDecl where rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 IfaceData f1 f2 f3 f4 f5 f6 f7 f8 f9 -> - f1 `seq` seqList f2 `seq` f3 `seq` f4 `seq` f5 `seq` + rnf f1 `seq` seqList f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` rnf f9 IfaceSynonym f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 IfaceFamily f1 f2 f3 f4 f5 f6 -> - rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 `seq` f6 `seq` () + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` () IfaceClass f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 IfaceAxiom nm tycon role ax -> rnf nm `seq` rnf tycon `seq` - role `seq` + rnf role `seq` rnf ax IfacePatSyn f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 -> - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` f6 `seq` - rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` f11 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 `seq` () instance NFData IfaceAxBranch where rnf (IfaceAxBranch f1 f2 f3 f4 f5 f6 f7) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` rnf f7 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 instance NFData IfaceClassBody where rnf = \case @@ -3089,7 +3098,7 @@ instance NFData IfaceAT where rnf (IfaceAT f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceClassOp where - rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` f3 `seq` () + rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` () instance NFData IfaceTyConParent where rnf = \case @@ -3104,14 +3113,17 @@ instance NFData IfaceConDecls where instance NFData IfaceConDecl where rnf (IfCon f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` - rnf f7 `seq` rnf f8 `seq` f9 `seq` rnf f10 `seq` rnf f11 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 instance NFData IfaceSrcBang where - rnf (IfSrcBang f1 f2) = f1 `seq` f2 `seq` () + rnf (IfSrcBang f1 f2) = rnf f1 `seq` rnf f2 `seq` () instance NFData IfaceBang where - rnf x = x `seq` () + rnf IfNoBang = () + rnf IfStrict = () + rnf IfUnpack = () + rnf (IfUnpackCo co) = rnf co instance NFData IfaceIdDetails where rnf = \case @@ -3125,23 +3137,22 @@ instance NFData IfaceInfoItem where rnf = \case HsArity a -> rnf a HsDmdSig str -> seqDmdSig str - HsInline p -> p `seq` () -- TODO: seq further? + HsInline p -> rnf p `seq` () HsUnfold b unf -> rnf b `seq` rnf unf HsNoCafRefs -> () - HsCprSig cpr -> cpr `seq` () - HsLFInfo lf_info -> lf_info `seq` () -- TODO: seq further? - HsTagSig sig -> sig `seq` () + HsCprSig cpr -> seqCprSig cpr `seq` () + HsLFInfo lf_info -> rnf lf_info `seq` () + HsTagSig sig -> seqTagSig sig `seq` () instance NFData IfGuidance where rnf = \case IfNoGuidance -> () - IfWhen a b c -> a `seq` b `seq` c `seq` () + IfWhen a b c -> rnf a `seq` rnf b `seq` rnf c `seq` () instance NFData IfaceUnfolding where rnf = \case - IfCoreUnfold src cache guidance expr -> src `seq` cache `seq` rnf guidance `seq` rnf expr + IfCoreUnfold src cache guidance expr -> rnf src `seq` seqUnfoldingCache cache `seq` rnf guidance `seq` rnf expr IfDFunUnfold bndrs exprs -> rnf bndrs `seq` rnf exprs - -- See Note [UnfoldingCache] in GHC.Core for why it suffices to merely `seq` on cache instance NFData IfaceExpr where rnf = \case @@ -3152,13 +3163,13 @@ instance NFData IfaceExpr where IfaceTuple sort exprs -> sort `seq` rnf exprs IfaceLam bndr expr -> rnf bndr `seq` rnf expr IfaceApp e1 e2 -> rnf e1 `seq` rnf e2 - IfaceCase e nm alts -> rnf e `seq` nm `seq` rnf alts + IfaceCase e nm alts -> rnf e `seq` rnf nm `seq` rnf alts IfaceECase e ty -> rnf e `seq` rnf ty IfaceLet bind e -> rnf bind `seq` rnf e IfaceCast e co -> rnf e `seq` rnf co - IfaceLit l -> l `seq` () -- FIXME - IfaceLitRubbish tc r -> tc `seq` rnf r `seq` () - IfaceFCall fc ty -> fc `seq` rnf ty + IfaceLit l -> rnf l `seq` () + IfaceLitRubbish tc r -> rnf tc `seq` rnf r `seq` () + IfaceFCall fc ty -> rnf fc `seq` rnf ty IfaceTick tick e -> rnf tick `seq` rnf e instance NFData IfaceAlt where @@ -3192,22 +3203,22 @@ instance NFData IfaceFamTyConFlav where instance NFData IfaceTickish where rnf = \case IfaceHpcTick m i -> rnf m `seq` rnf i - IfaceSCC cc b1 b2 -> cc `seq` rnf b1 `seq` rnf b2 - IfaceSource src str -> src `seq` rnf str + IfaceSCC cc b1 b2 -> rnf cc `seq` rnf b1 `seq` rnf b2 + IfaceSource src str -> rnf src `seq` rnf str IfaceBreakpoint m i fvs -> rnf m `seq` rnf i `seq` rnf fvs instance NFData IfaceConAlt where rnf = \case IfaceDefaultAlt -> () IfaceDataAlt nm -> rnf nm - IfaceLitAlt lit -> lit `seq` () + IfaceLitAlt lit -> rnf lit `seq` () instance NFData IfaceCompleteMatch where rnf (IfaceCompleteMatch f1 mtc) = rnf f1 `seq` rnf mtc instance NFData IfaceRule where rnf (IfaceRule f1 f2 f3 f4 f5 f6 f7 f8) = - rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` f8 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` () instance NFData IfaceDefault where rnf (IfaceDefault f1 f2 f3) = @@ -3215,11 +3226,11 @@ instance NFData IfaceDefault where instance NFData IfaceFamInst where rnf (IfaceFamInst f1 f2 f3 f4) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` () instance NFData IfaceClsInst where rnf (IfaceClsInst f1 f2 f3 f4 f5 f6) = - f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` f5 `seq` rnf f6 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 instance NFData IfaceWarnings where rnf = \case @@ -3227,12 +3238,12 @@ instance NFData IfaceWarnings where IfWarnSome vs ds -> rnf vs `seq` rnf ds instance NFData IfaceWarningTxt where - rnf = \case - IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 - IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 + rnf = \case + IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 + IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 instance NFData IfaceStringLiteral where - rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 + rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceAnnotation where - rnf (IfaceAnnotation f1 f2) = f1 `seq` f2 `seq` () + rnf (IfaceAnnotation f1 f2) = rnf f1 `seq` rnf f2 `seq` () ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -2577,6 +2577,11 @@ instance Binary (DefMethSpec IfaceType) where 0 -> return VanillaDM _ -> do { t <- get bh; return (GenericDM t) } +instance NFData (DefMethSpec IfaceType) where + rnf = \case + VanillaDM -> () + GenericDM t -> rnf t + instance NFData IfaceType where rnf = \case IfaceFreeTyVar f1 -> f1 `seq` () ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -148,6 +148,7 @@ import qualified GHC.Boot.TH.Ppr as TH #if defined(HAVE_INTERNAL_INTERPRETER) import Unsafe.Coerce ( unsafeCoerce ) import GHC.Desugar ( AnnotationWrapper(..) ) +import Control.DeepSeq #endif import Control.Monad @@ -1039,11 +1040,7 @@ convertAnnotationWrapper fhv = do -- annotation are exposed at this point. This is also why we are -- doing all this stuff inside the context of runMeta: it has the -- facilities to deal with user error in a meta-level expression - seqSerialized serialized `seq` serialized - --- | Force the contents of the Serialized value so weknow it doesn't contain any bottoms -seqSerialized :: Serialized -> () -seqSerialized (Serialized the_type bytes) = the_type `seq` bytes `seqList` () + rnf serialized `seq` serialized #endif ===================================== compiler/GHC/Types/Annotations.hs ===================================== @@ -31,7 +31,7 @@ import Control.Monad import Data.Maybe import Data.Typeable import Data.Word ( Word8 ) - +import Control.DeepSeq -- | Represents an annotation after it has been sufficiently desugared from -- it's initial form of 'GHC.Hs.Decls.AnnDecl' @@ -71,6 +71,10 @@ instance Binary name => Binary (AnnTarget name) where 0 -> liftM NamedTarget $ get bh _ -> liftM ModuleTarget $ get bh +instance NFData name => NFData (AnnTarget name) where + rnf (NamedTarget n) = rnf n + rnf (ModuleTarget m) = rnf m + instance Outputable Annotation where ppr ann = ppr (ann_target ann) ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -529,6 +529,10 @@ instance Binary FunctionOrData where 1 -> return IsData _ -> panic "Binary FunctionOrData" +instance NFData FunctionOrData where + rnf IsFunction = () + rnf IsData = () + {- ************************************************************************ * * @@ -871,6 +875,9 @@ data OverlapMode -- See Note [Rules for instance lookup] in GHC.Core.InstEnv instance Outputable OverlapFlag where ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag) +instance NFData OverlapFlag where + rnf (OverlapFlag mode safe) = rnf mode `seq` rnf safe + instance Outputable OverlapMode where ppr (NoOverlap _) = empty ppr (Overlappable _) = text "[overlappable]" @@ -879,6 +886,14 @@ instance Outputable OverlapMode where ppr (Incoherent _) = text "[incoherent]" ppr (NonCanonical _) = text "[noncanonical]" +instance NFData OverlapMode where + rnf (NoOverlap s) = rnf s + rnf (Overlappable s) = rnf s + rnf (Overlapping s) = rnf s + rnf (Overlaps s) = rnf s + rnf (Incoherent s) = rnf s + rnf (NonCanonical s) = rnf s + instance Binary OverlapMode where put_ bh (NoOverlap s) = putByte bh 0 >> put_ bh s put_ bh (Overlaps s) = putByte bh 1 >> put_ bh s @@ -1860,6 +1875,14 @@ instance Binary Activation where ab <- get bh return (ActiveAfter src ab) +instance NFData Activation where + rnf = \case + AlwaysActive -> () + NeverActive -> () + ActiveBefore src aa -> rnf src `seq` rnf aa + ActiveAfter src ab -> rnf src `seq` rnf ab + FinalActive -> () + instance Outputable RuleMatchInfo where ppr ConLike = text "CONLIKE" ppr FunLike = text "FUNLIKE" @@ -1872,6 +1895,11 @@ instance Binary RuleMatchInfo where if h == 1 then return ConLike else return FunLike +instance NFData RuleMatchInfo where + rnf = \case + ConLike -> () + FunLike -> () + instance Outputable InlineSpec where ppr (Inline src) = text "INLINE" <+> pprWithSourceText src empty ppr (NoInline src) = text "NOINLINE" <+> pprWithSourceText src empty @@ -1906,6 +1934,14 @@ instance Binary InlineSpec where s <- get bh return (Opaque s) +instance NFData InlineSpec where + rnf = \case + Inline s -> rnf s + NoInline s -> rnf s + Inlinable s -> rnf s + Opaque s -> rnf s + NoUserInlinePrag -> () + instance Outputable InlinePragma where ppr = pprInline @@ -1925,6 +1961,9 @@ instance Binary InlinePragma where d <- get bh return (InlinePragma s a b c d) +instance NFData InlinePragma where + rnf (InlinePragma s a b c d) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c `seq` rnf d + -- | Outputs string for pragma name for any of INLINE/INLINABLE/NOINLINE. This -- differs from the Outputable instance for the InlineSpec type where the pragma -- name string as well as the accompanying SourceText (if any) is printed. @@ -2017,6 +2056,13 @@ instance Binary UnfoldingSource where 2 -> return StableSystemSrc _ -> return VanillaSrc +instance NFData UnfoldingSource where + rnf = \case + CompulsorySrc -> () + StableUserSrc -> () + StableSystemSrc -> () + VanillaSrc -> () + instance Outputable UnfoldingSource where ppr CompulsorySrc = text "Compulsory" ppr StableUserSrc = text "StableUser" @@ -2161,6 +2207,19 @@ data TypeOrConstraint = TypeLike | ConstraintLike deriving( Eq, Ord, Data ) +instance Binary TypeOrConstraint where + put_ bh = \case + TypeLike -> putByte bh 0 + ConstraintLike -> putByte bh 1 + get bh = getByte bh >>= \case + 0 -> pure TypeLike + 1 -> pure ConstraintLike + _ -> panic "TypeOrConstraint.get: invalid value" + +instance NFData TypeOrConstraint where + rnf = \case + TypeLike -> () + ConstraintLike -> () {- ********************************************************************* * * ===================================== compiler/GHC/Types/CostCentre.hs ===================================== @@ -36,6 +36,7 @@ import GHC.Utils.Outputable import GHC.Types.SrcLoc import GHC.Data.FastString import GHC.Types.CostCentre.State +import Control.DeepSeq import Data.Data @@ -395,6 +396,21 @@ instance Binary CostCentre where -- CostCentre in the original module, it is not used by importing -- modules. +instance NFData CostCentre where + rnf (NormalCC aa ab ac ad) = rnf aa `seq` rnf ab `seq` rnf ac `seq` rnf ad + rnf (AllCafsCC ae ad) = rnf ae `seq` rnf ad + +instance NFData CCFlavour where + rnf CafCC = () + rnf (IndexedCC flav i) = rnf flav `seq` rnf i + +instance NFData IndexedCCFlavour where + rnf ExprCC = () + rnf DeclCC = () + rnf HpcCC = () + rnf LateCC = () + rnf CallerCC = () + getAllCAFsCC :: Module -> (CostCentre, CostCentreStack) getAllCAFsCC this_mod = let ===================================== compiler/GHC/Types/CostCentre/State.hs ===================================== @@ -15,6 +15,7 @@ import GHC.Data.FastString.Env import Data.Data import GHC.Utils.Binary +import Control.DeepSeq -- | Per-module state for tracking cost centre indices. -- @@ -29,6 +30,9 @@ newCostCentreState = CostCentreState emptyFsEnv newtype CostCentreIndex = CostCentreIndex { unCostCentreIndex :: Int } deriving (Eq, Ord, Data, Binary) +instance NFData CostCentreIndex where + rnf (CostCentreIndex i) = rnf i + -- | Get a new index for a given cost centre name. getCCIndex :: FastString -> CostCentreState ===================================== compiler/GHC/Types/ForeignCall.hs ===================================== @@ -30,6 +30,8 @@ import GHC.Types.SourceText ( SourceText, pprWithSourceText ) import Data.Char import Data.Data +import Control.DeepSeq (NFData(..)) + {- ************************************************************************ * * @@ -344,3 +346,31 @@ instance Binary Header where get bh = do s <- get bh h <- get bh return (Header s h) + +instance NFData ForeignCall where + rnf (CCall c) = rnf c + +instance NFData Safety where + rnf PlaySafe = () + rnf PlayInterruptible = () + rnf PlayRisky = () + +instance NFData CCallSpec where + rnf (CCallSpec t c s) = rnf t `seq` rnf c `seq` rnf s + +instance NFData CCallTarget where + rnf (StaticTarget s a b c) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c + rnf DynamicTarget = () + +instance NFData CCallConv where + rnf CCallConv = () + rnf StdCallConv = () + rnf PrimCallConv = () + rnf CApiConv = () + rnf JavaScriptCallConv = () + +instance NFData CType where + rnf (CType s mh fs) = rnf s `seq` rnf mh `seq` rnf fs + +instance NFData Header where + rnf (Header s h) = rnf s `seq` rnf h ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -84,6 +84,7 @@ import Data.Char import Data.Data ( Data ) import GHC.Exts( isTrue#, dataToTag#, (<#) ) import Numeric ( fromRat ) +import Control.DeepSeq {- ************************************************************************ @@ -204,6 +205,20 @@ instance Binary LitNumType where h <- getByte bh return (toEnum (fromIntegral h)) +instance NFData LitNumType where + rnf (LitNumBigNat) = () + rnf (LitNumInt) = () + rnf (LitNumInt8) = () + rnf (LitNumInt16) = () + rnf (LitNumInt32) = () + rnf (LitNumInt64) = () + rnf (LitNumWord) = () + rnf (LitNumWord8) = () + rnf (LitNumWord16) = () + rnf (LitNumWord32) = () + rnf (LitNumWord64) = () + + {- Note [BigNum literals] ~~~~~~~~~~~~~~~~~~~~~~ @@ -288,6 +303,16 @@ instance Binary Literal where return (LitNumber nt i) _ -> pprPanic "Binary:Literal" (int (fromIntegral h)) +instance NFData Literal where + rnf (LitChar c) = rnf c + rnf (LitNumber nt i) = rnf nt `seq` rnf i + rnf (LitString s) = rnf s + rnf LitNullAddr = () + rnf (LitFloat r) = rnf r + rnf (LitDouble r) = rnf r + rnf (LitLabel l1 k2) = rnf l1 `seq` rnf k2 + rnf (LitRubbish {}) = () -- LitRubbish is not contained within interface files. + -- See Note [Rubbish literals]. instance Outputable Literal where ppr = pprLiteral id ===================================== compiler/GHC/Types/SourceFile.hs ===================================== @@ -13,6 +13,7 @@ where import GHC.Prelude import GHC.Utils.Binary import GHC.Unit.Types +import Control.DeepSeq {- Note [HscSource types] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -53,6 +54,10 @@ data HsBootOrSig | Hsig -- ^ .hsig file deriving (Eq, Ord, Show) +instance NFData HsBootOrSig where + rnf HsBoot = () + rnf Hsig = () + data HscSource -- | .hs file = HsSrcFile @@ -73,6 +78,10 @@ hscSourceToIsBoot :: HscSource -> IsBootInterface hscSourceToIsBoot HsBootFile = IsBoot hscSourceToIsBoot _ = NotBoot +instance NFData HscSource where + rnf HsSrcFile = () + rnf (HsBootOrSig h) = rnf h + instance Binary HscSource where put_ bh HsSrcFile = putByte bh 0 put_ bh HsBootFile = putByte bh 1 ===================================== compiler/GHC/Types/SrcLoc.hs ===================================== @@ -223,7 +223,8 @@ data RealSrcLoc -- We use 'BufPos' in in GHC.Parser.PostProcess.Haddock to associate Haddock -- comments with parts of the AST using location information (#17544). newtype BufPos = BufPos { bufPos :: Int } - deriving (Eq, Ord, Show, Data) + deriving (Eq, Ord, Show, Data, NFData) + -- | Source Location data SrcLoc @@ -373,11 +374,13 @@ data RealSrcSpan } deriving Eq --- | StringBuffer Source Span data BufSpan = BufSpan { bufSpanStart, bufSpanEnd :: {-# UNPACK #-} !BufPos } deriving (Eq, Ord, Show, Data) +instance NFData BufSpan where + rnf (BufSpan a1 a2) = rnf a1 `seq` rnf a2 + instance Semigroup BufSpan where BufSpan start1 end1 <> BufSpan start2 end2 = BufSpan (min start1 start2) (max end1 end2) @@ -439,8 +442,18 @@ instance ToJson RealSrcSpan where end = JSObject [ ("line", JSInt srcSpanELine), ("column", JSInt srcSpanECol) ] +instance NFData RealSrcSpan where + rnf (RealSrcSpan' file line col endLine endCol) = rnf file `seq` rnf line `seq` rnf col `seq` rnf endLine `seq` rnf endCol instance NFData SrcSpan where - rnf x = x `seq` () + rnf (RealSrcSpan a1 a2) = rnf a1 `seq` rnf a2 + rnf (UnhelpfulSpan a1) = rnf a1 + +instance NFData UnhelpfulSpanReason where + rnf (UnhelpfulNoLocationInfo) = () + rnf (UnhelpfulWiredIn) = () + rnf (UnhelpfulInteractive) = () + rnf (UnhelpfulGenerated) = () + rnf (UnhelpfulOther a1) = rnf a1 getBufSpan :: SrcSpan -> Strict.Maybe BufSpan getBufSpan (RealSrcSpan _ mbspan) = mbspan ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -132,6 +132,7 @@ import GHC.Utils.Panic import GHC.Hs.Specificity () import Language.Haskell.Syntax.Specificity +import Control.DeepSeq import Data.Data @@ -734,6 +735,9 @@ instance (Binary tv, Binary vis) => Binary (VarBndr tv vis) where get bh = do { tv <- get bh; vis <- get bh; return (Bndr tv vis) } +instance (NFData tv, NFData vis) => NFData (VarBndr tv vis) where + rnf (Bndr tv vis) = rnf tv `seq` rnf vis + instance NamedThing tv => NamedThing (VarBndr tv flag) where getName (Bndr tv _) = getName tv ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -39,6 +39,7 @@ import Data.List (sortBy, sort, partition) import Data.Set (Set) import qualified Data.Set as Set import Data.Bifunctor +import Control.DeepSeq -- | Dependency information about ALL modules and packages below this one -- in the import hierarchy. This is the serialisable version of `ImportAvails`. @@ -104,6 +105,18 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +instance NFData Dependencies where + rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) + = rnf dmods + `seq` rnf dpkgs + `seq` rnf ppkgs + `seq` rnf hsigms + `seq` rnf tps + `seq` rnf bmods + `seq` rnf orphs + `seq` rnf finsts + `seq` () + -- | Extract information from the rename and typecheck phases to produce -- a dependencies information for the module being compiled. @@ -326,6 +339,13 @@ data Usage -- And of course, for modules that aren't imported directly we don't -- depend on their export lists +instance NFData Usage where + rnf (UsagePackageModule mod hash safe) = rnf mod `seq` rnf hash `seq` rnf safe `seq` () + rnf (UsageHomeModule mod uid hash entities exports safe) = rnf mod `seq` rnf uid `seq` rnf hash `seq` rnf entities `seq` rnf exports `seq` rnf safe `seq` () + rnf (UsageFile file hash label) = rnf file `seq` rnf hash `seq` rnf label `seq` () + rnf (UsageMergedRequirement mod hash) = rnf mod `seq` rnf hash `seq` () + rnf (UsageHomeModuleInterface mod uid hash) = rnf mod `seq` rnf uid `seq` rnf hash `seq` () + instance Binary Usage where put_ bh usg at UsagePackageModule{} = do putByte bh 0 ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -660,52 +660,46 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ - , mi_exports_, mi_fixities_, mi_warns_, mi_anns_ - , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ - , mi_fam_insts_, mi_rules_, mi_trust_, mi_trust_pkg_ - , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_ }) - = rnf mi_module_ - `seq` rnf mi_sig_of_ - `seq` mi_hsc_src_ - `seq` mi_hi_bytes_ - `seq` mi_deps_ - `seq` mi_exports_ - `seq` mi_fixities_ - `seq` rnf mi_warns_ - `seq` rnf mi_anns_ - `seq` rnf mi_decls_ - `seq` rnf mi_defaults_ - `seq` rnf mi_extra_decls_ - `seq` rnf mi_foreign_ - `seq` rnf mi_top_env_ - `seq` rnf mi_insts_ - `seq` rnf mi_fam_insts_ - `seq` rnf mi_rules_ - `seq` mi_trust_ - `seq` rnf mi_trust_pkg_ - `seq` rnf mi_complete_matches_ - `seq` rnf mi_docs_ - `seq` mi_final_exts_ - `seq` mi_ext_fields_ - `seq` () - -instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_mod_hash - , mi_orphan, mi_finsts, mi_exp_hash - , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn - , mi_hash_fn}) - = rnf mi_mod_hash - `seq` rnf mi_orphan - `seq` rnf mi_finsts - `seq` rnf mi_exp_hash - `seq` rnf mi_orphan_hash - `seq` rnf mi_decl_warn_fn - `seq` rnf mi_export_warn_fn - `seq` rnf mi_fix_fn - `seq` rnf mi_hash_fn + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + `seq` rnf a15 + `seq` rnf a16 + `seq` rnf a17 + `seq` rnf a18 + `seq` rnf a19 + `seq` rnf a20 + `seq` rnf a21 + `seq` rnf a22 + -- IfaceBinHandle + `seq` a23 + `seq` rnf a24 + + +instance NFData ModIfaceBackend where + rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 forceModIface :: ModIface -> IO () ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -517,6 +517,9 @@ newtype UnitId = UnitId } deriving (Data) +instance NFData UnitId where + rnf (UnitId fs) = rnf fs `seq` () + instance Binary UnitId where put_ bh (UnitId fs) = put_ bh fs get bh = do fs <- get bh; return (UnitId fs) @@ -704,6 +707,9 @@ data GenWithIsBoot mod = GWIB -- IsBootInterface: this is assumed to perform filtering of non-boot modules, -- e.g. in GHC.Driver.Env.hptModulesBelow +instance NFData mod => NFData (GenWithIsBoot mod) where + rnf (GWIB mod isBoot) = rnf mod `seq` rnf isBoot `seq` () + type ModuleNameWithIsBoot = GenWithIsBoot ModuleName type ModuleWithIsBoot = GenWithIsBoot Module ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,11 +2,11 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where -import Data.Data +import Data.Data (Data) import Data.Eq import Data.Ord import Data.Bool -import Data.Int (Int) +import Prelude import GHC.Data.FastString (FastString) import Control.DeepSeq @@ -134,5 +134,13 @@ data FixityDirection | InfixN deriving (Eq, Data) +instance NFData FixityDirection where + rnf InfixL = () + rnf InfixR = () + rnf InfixN = () + data Fixity = Fixity Int FixityDirection deriving (Eq, Data) + +instance NFData Fixity where + rnf (Fixity i d) = rnf i `seq` rnf d `seq` () ===================================== libraries/ghc-boot/GHC/Serialized.hs ===================================== @@ -22,11 +22,15 @@ import Prelude -- See note [Why do we import Prelude here?] import Data.Bits import Data.Word ( Word8 ) import Data.Data +import Control.DeepSeq -- | Represents a serialized value of a particular type. Attempts can be made to deserialize it at certain types data Serialized = Serialized TypeRep [Word8] +instance NFData Serialized where + rnf (Serialized tr ws) = rnf tr `seq` rnf ws + -- | Put a Typeable value that we are able to actually turn into bytes into a 'Serialized' value ready for deserialization later toSerialized :: forall a. Typeable a => (a -> [Word8]) -> a -> Serialized toSerialized serialize what = Serialized (typeOf what) (serialize what) ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -987,15 +987,6 @@ instance NFData RdrName where rnf (Orig m on) = m `deepseq` on `deepseq` () rnf (Exact n) = rnf n -instance NFData FixityDirection where - rnf InfixL = () - rnf InfixR = () - rnf InfixN = () - -instance NFData Fixity where - rnf (Fixity n dir) = - n `deepseq` dir `deepseq` () - instance NFData (EpAnn NameAnn) where rnf (EpAnn en ann cs) = en `deepseq` ann `deepseq` cs `deepseq` () @@ -1065,15 +1056,6 @@ instance NFData EpaCommentTok where rnf (EpaLineComment s) = rnf s rnf (EpaBlockComment s) = rnf s -instance NFData a => NFData (Strict.Maybe a) where - rnf Strict.Nothing = () - rnf (Strict.Just x) = rnf x - -instance NFData BufSpan where - rnf (BufSpan p1 p2) = p1 `deepseq` p2 `deepseq` () - -instance NFData BufPos where - rnf (BufPos n) = rnf n instance NFData DeltaPos where rnf (SameLine n) = rnf n View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c84e65f4b0b4c70fb822ced556089711a3eaceec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c84e65f4b0b4c70fb822ced556089711a3eaceec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/15199c60/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 7 21:29:28 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 07 Mar 2025 16:29:28 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Cmm: Add surface syntax for Word/Float bitcast ops Message-ID: <67cb653829c7b_10a0e7f80e445232@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 3a9a0f6b by Oleg Grenrus at 2025-03-07T16:29:20-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 45 changed files: - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Unique.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/999112bef6804efb851a5a5042e833bf55b875bb...3a9a0f6b0c9a7407c2edd3c825c8e64ab3a4a2f7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/999112bef6804efb851a5a5042e833bf55b875bb...3a9a0f6b0c9a7407c2edd3c825c8e64ab3a4a2f7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/d7bdcdbf/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 22:29:24 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Fri, 07 Mar 2025 17:29:24 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/wasm-jsffi-revamp Message-ID: <67cb7344cd497_159f4ec5c246245d@gitlab.mail> Cheng Shao pushed new branch wip/wasm-jsffi-revamp at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/wasm-jsffi-revamp You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/0216c0a6/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 7 23:45:59 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Fri, 07 Mar 2025 18:45:59 -0500 Subject: [Git][ghc/ghc][wip/T25577] 32 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67cb85376b0a6_177380c5ecc158c1@gitlab.mail> Cheng Shao pushed to branch wip/T25577 at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 631d9356 by Ben Gamari at 2025-03-07T23:33:39+00:00 testsuite: Add testcase for #25577 - - - - - e338c3d7 by Ben Gamari at 2025-03-07T23:45:19+00:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 4d539eda by Ben Gamari at 2025-03-07T23:45:24+00:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - e98c0f0d by Ben Gamari at 2025-03-07T23:45:24+00:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 127 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de7343a4cf222d88629f4e5279b55666aad5ce77...e98c0f0d2ec0a84ff9afb387e710da6fc6b6c00e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de7343a4cf222d88629f4e5279b55666aad5ce77...e98c0f0d2ec0a84ff9afb387e710da6fc6b6c00e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/b73f3a97/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 00:36:16 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Fri, 07 Mar 2025 19:36:16 -0500 Subject: [Git][ghc/ghc][wip/T25577] 3 commits: testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests Message-ID: <67cb910063765_185cea37e7a4718a1@gitlab.mail> Cheng Shao pushed to branch wip/T25577 at Glasgow Haskell Compiler / GHC Commits: 1f979f37 by Ben Gamari at 2025-03-08T00:35:48+00:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - b4db5ef4 by Ben Gamari at 2025-03-08T00:36:03+00:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 1857ebc5 by Ben Gamari at 2025-03-08T00:36:03+00:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 5 changed files: - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/tests/ghc-api/Makefile - testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T Changes: ===================================== rts/linker/MachO.c ===================================== @@ -68,9 +68,10 @@ static void encodeAddend(ObjectCode * oc, Section * section, /* Global Offset Table logic */ static bool isGotLoad(MachORelocationInfo * ri); -static bool needGotSlot(MachONList * symbol); +static bool needGotSlot(MachOSymbol * symbol); static bool makeGot(ObjectCode * oc); static void freeGot(ObjectCode * oc); +static void findInternalGotRefs(ObjectCode * oc); #endif /* aarch64_HOST_ARCH */ /* @@ -440,6 +441,48 @@ encodeAddend(ObjectCode * oc, Section * section, barf("unsupported relocation type: %d\n", ri->r_type); } +/* Note [Symbols in need of GOT entries] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * As GOT entries require memory, we ideally want to avoid reserving + * them for symbols where they are unnecessary. Specifically, most internal + * symbols will not be referenced by the GOT, even in position independent code + * (since you can instead use direct PC-relative addressing). + * + * However, it is nevertheless possible for internal symbols to be referenced + * via the GOT. Consequently, we use the following strategy to determine whether + * a symbol needs a GOT slot: + * + * a. all undefined external symbols are given GOT entries + * b. all external symbols with cross-section refrences are given GOT entries + * c. all internal symbols for which there are GOT relocations are given GOT + * entries. + * + * Failing to consider (c) lead to #25577. For this we explicitly traverse + * the relocations in findInternalGotRefs() looking for GOT relocations + * referencing internal symbols, setting the MachOSymbol.needs_got flag for + * each. + */ + +// See Note [Symbols in need of GOT entries] +static void +findInternalGotRefs(ObjectCode * oc) +{ + for (int curSection = 0; curSection < oc->n_sections; curSection++) { + Section * sect = &oc->sections[curSection]; + if (sect->info == NULL) + continue; + MachOSection * msect = sect->info->macho_section; // for access convenience + MachORelocationInfo * relocs = sect->info->relocation_info; + for(uint32_t i = 0; i < msect->nreloc; i++) { + MachORelocationInfo *ri = &relocs[i]; + if (isGotLoad(ri)) { + MachOSymbol* symbol = &oc->info->macho_symbols[ri->r_symbolnum]; + symbol->needs_got = true; + } + } + } +} + static bool isGotLoad(struct relocation_info * ri) { return ri->r_type == ARM64_RELOC_GOT_LOAD_PAGE21 @@ -448,14 +491,19 @@ isGotLoad(struct relocation_info * ri) { /* * Check if we need a global offset table slot for a - * given symbol + * given symbol. See Note [Symbols in need of GOT entries]. */ static bool -needGotSlot(MachONList * symbol) { - return (symbol->n_type & N_EXT) /* is an external symbol */ - && (N_UNDF == (symbol->n_type & N_TYPE) /* and is undefined */ - || NO_SECT != symbol->n_sect); /* or is defined in a - * different section */ +needGotSlot(MachOSymbol * symbol) { + // Does it have any internal references? + if (symbol->needs_got) { + return true; + } + + return (symbol->nlist->n_type & N_EXT) /* is an external symbol */ + && (N_UNDF == (symbol->nlist->n_type & N_TYPE) /* and is undefined */ + || NO_SECT != symbol->nlist->n_sect); /* or is defined in a + * different section */ } static bool @@ -463,7 +511,7 @@ makeGot(ObjectCode * oc) { size_t got_slots = 0; for(size_t i=0; i < oc->info->n_macho_symbols; i++) - if(needGotSlot(oc->info->macho_symbols[i].nlist)) + if(needGotSlot(&oc->info->macho_symbols[i])) got_slots += 1; if(got_slots > 0) { @@ -476,7 +524,7 @@ makeGot(ObjectCode * oc) { /* update got_addr */ size_t slot = 0; for(size_t i=0; i < oc->info->n_macho_symbols; i++) - if(needGotSlot(oc->info->macho_symbols[i].nlist)) + if(needGotSlot(&oc->info->macho_symbols[i])) oc->info->macho_symbols[i].got_addr = ((uint8_t*)oc->info->got_start) + (slot++ * sizeof(void *)); @@ -627,6 +675,7 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) barf("explicit_addend and addend can't be set at the same time."); uint64_t pc = (uint64_t)section->start + ri->r_address; uint64_t value = (uint64_t)(isGotLoad(ri) ? symbol->got_addr : symbol->addr); + ASSERT(!isGotLoad(ri) || (symbol->got_addr != 0)); encodeAddend(oc, section, ri, ((value + addend + explicit_addend) & (-4096)) - (pc & (-4096))); // reset, just in case. @@ -640,6 +689,7 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) if(!(explicit_addend == 0 || addend == 0)) barf("explicit_addend and addend can't be set at the same time."); uint64_t value = (uint64_t)(isGotLoad(ri) ? symbol->got_addr : symbol->addr); + ASSERT(!isGotLoad(ri) || (symbol->got_addr != 0)); encodeAddend(oc, section, ri, 0xFFF & (value + addend + explicit_addend)); // reset, just in case. @@ -1450,6 +1500,8 @@ ocGetNames_MachO(ObjectCode* oc) } } #if defined(aarch64_HOST_ARCH) + findInternalGotRefs(oc); + /* Setup the global offset table * This is for symbols that are external, and not defined here. * So that we can load their address indirectly. @@ -1556,7 +1608,7 @@ ocResolve_MachO(ObjectCode* oc) /* fill the GOT table */ for(size_t i = 0; i < oc->info->n_macho_symbols; i++) { MachOSymbol * symbol = &oc->info->macho_symbols[i]; - if(needGotSlot(symbol->nlist)) { + if(needGotSlot(symbol)) { if(N_UNDF == (symbol->nlist->n_type & N_TYPE)) { /* an undefined symbol. So we need to ensure we * have the address. ===================================== rts/linker/MachOTypes.h ===================================== @@ -31,6 +31,7 @@ typedef struct _MachOSymbol { SymbolAddr * addr; /* the final resting place of the symbol */ void * got_addr; /* address of the got slot for this symbol, if any */ MachONList * nlist; /* the nlist symbol entry */ + bool needs_got; /* See Note [Symbols in need of GOT entries] */ } MachOSymbol; struct ObjectCodeFormatInfo { ===================================== testsuite/tests/ghc-api/Makefile ===================================== @@ -2,29 +2,3 @@ TOP=../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk -clean: - rm -f *.o *.hi - -T6145: - rm -f T6145.o T6145.hi - '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc T6145 - ./T6145 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" - -T8639_api: - rm -f T8639_api.o T8639_api.hi - '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc T8639_api - ./T8639_api "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" - -T8628: - rm -f T8628.o T8628.hi - '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc -package exceptions T8628 - ./T8628 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" - -T9015: - rm -f T9015.o T9015.hi - '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc T9015 - ./T9015 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" - -.PHONY: clean T6145 T8639_api T8628 T9015 - - ===================================== testsuite/tests/ghc-api/T25577.hs ===================================== @@ -3,7 +3,6 @@ module Main where import GHC -import GHC.Paths import Unsafe.Coerce import Control.Monad.IO.Class import System.Environment (getArgs) ===================================== testsuite/tests/ghc-api/all.T ===================================== @@ -1,12 +1,38 @@ setTestOpts(when(arch('wasm32'), run_timeout_multiplier(2))) test('ghcApi', normal, compile_and_run, ['-package ghc']) -test('T6145', normal, makefile_test, ['T6145']) -test('T8639_api', req_rts_linker, - makefile_test, ['T8639_api']) -test('T8628', req_rts_linker, - makefile_test, ['T8628']) -test('T9595', [extra_run_opts('"' + config.libdir + '"')], + +test('T6145', + [extra_run_opts(f'"{config.libdir}"') + # needs to spawn c compiler process, and wasm doesn't have + # process support + , req_process], + compile_and_run, + ['-package ghc']) + +test('T8639_api', + [extra_run_opts(f'"{config.libdir}"') + # wasm rts linker only works in dyn ways, normal way statically + # linked wasm module doesn't support it + , req_rts_linker + , when(arch('wasm32'), skip)], + compile_and_run, + ['-package ghc']) + +test('T8628', + [extra_run_opts(f'"{config.libdir}"') + # same with T8639_api + , req_rts_linker + , when(arch('wasm32'), skip)], + compile_and_run, + ['-package ghc -package exceptions']) + +test('T9015', + [extra_run_opts(f'"{config.libdir}"'), req_rts_linker], + compile_and_run, + ['-package ghc']) + +test('T9595', [extra_run_opts(f'"{config.libdir}"')], compile_and_run, ['-package ghc']) test('T10508_api', [ extra_run_opts('"' + config.libdir + '"'), @@ -17,9 +43,6 @@ test('T10508_api', [ extra_run_opts('"' + config.libdir + '"'), test('T10942', [extra_run_opts('"' + config.libdir + '"')], compile_and_run, ['-package ghc']) -test('T9015', [extra_run_opts('"' + config.libdir + '"')], - compile_and_run, - ['-package ghc']) test('T11579', [extra_run_opts('"' + config.libdir + '"'), js_skip], compile_and_run, ['-package ghc']) test('T12099', normal, compile_and_run, ['-package ghc']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e98c0f0d2ec0a84ff9afb387e710da6fc6b6c00e...1857ebc59c8f3c8289e6cdd58de6da7acea7268d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e98c0f0d2ec0a84ff9afb387e710da6fc6b6c00e...1857ebc59c8f3c8289e6cdd58de6da7acea7268d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/50ba66f3/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 00:45:46 2025 From: gitlab at gitlab.haskell.org (Matthew Craven (@clyring)) Date: Fri, 07 Mar 2025 19:45:46 -0500 Subject: [Git][ghc/ghc][wip/TagToEnum-class] 91 commits: base: Label threads forked by IO operations Message-ID: <67cb933a76c64_185cea3779b872641@gitlab.mail> Matthew Craven pushed to branch wip/TagToEnum-class at Glasgow Haskell Compiler / GHC Commits: 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 39864d91 by Matthew Craven at 2025-03-06T18:24:24-05:00 WIP: Implement specially-solved TagToEnum class - - - - - 5683d18f by Matthew Craven at 2025-03-06T18:24:25-05:00 Move dataToTag# lint stuff into checkSpecialPrimOpTypeArgs (It remains commented out.) - - - - - 7f20805b by Matthew Craven at 2025-03-06T18:24:25-05:00 Remove old tagToEnum# typechecker errors - - - - - dccd3c8c by Matthew Craven at 2025-03-07T19:43:51-05:00 comments only - - - - - 414 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Builtin/Utils.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Inline.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Utils.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/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/ImpExp.hs - compiler/Setup.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Lint.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Builders/GenPrimopCode.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Parser.hs - libffi-tarballs - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Exts.hs - libraries/base/src/System/Timeout.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Exts.hs - + libraries/ghc-internal/src/GHC/Internal/Magic/TagToEnum.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/wasm/JSFFI.c - testsuite/driver/testlib.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/diagnostic-codes/codes.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod185.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/T4007.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T21286.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/all.T - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - testsuite/tests/type-data/should_fail/TDTagToEnum.stderr - + testsuite/tests/typecheck/should_compile/T25744.hs - + testsuite/tests/typecheck/should_compile/T8318.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/tcfail164.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60b11e934b354e5f584ff30d1c1496b3e7eb7b03...dccd3c8ccc2e136f89fbfff05a385ffa9b21d822 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60b11e934b354e5f584ff30d1c1496b3e7eb7b03...dccd3c8ccc2e136f89fbfff05a385ffa9b21d822 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/ab00f88c/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 00:55:12 2025 From: gitlab at gitlab.haskell.org (Matthew Craven (@clyring)) Date: Fri, 07 Mar 2025 19:55:12 -0500 Subject: [Git][ghc/ghc][wip/TagToEnum-class] Fix pattern match for MC3 of Note [Merge Nested Cases] Message-ID: <67cb957030636_185cea57f558746db@gitlab.mail> Matthew Craven pushed to branch wip/TagToEnum-class at Glasgow Haskell Compiler / GHC Commits: 48e410f4 by Matthew Craven at 2025-03-07T19:53:42-05:00 Fix pattern match for MC3 of Note [Merge Nested Cases] - - - - - 1 changed file: - compiler/GHC/Core/Utils.hs Changes: ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -679,7 +679,7 @@ mergeCaseAlts outer_bndr (Alt DEFAULT _ deflt_rhs : outer_alts) ; return ([], alts') } -- Deal with tagToEnumPrim# See Note [Merge Nested Cases] wrinkle (MC3) - go (App (App (Var f) (Type type_arg)) (Var v)) -- TODO: Fix this pattern match + go (Var f `App` _levity_arg `App` Type type_arg `App` Var v) | v == outer_bndr , Just TagToEnumOp <- isPrimOpId_maybe f , Just tc <- tyConAppTyCon_maybe type_arg View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/48e410f47a5e608115d43a7b1d3b98179eaaf452 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/48e410f47a5e608115d43a7b1d3b98179eaaf452 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250307/834a6e99/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 8 13:50:26 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 08:50:26 -0500 Subject: [Git][ghc/ghc][master] iface: Store flags in interface files Message-ID: <67cc4b2277655_285c5d92a72074643@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 18 changed files: - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout Changes: ===================================== compiler/GHC/Core/Opt/CallerCC/Types.hs ===================================== @@ -19,6 +19,7 @@ import GHC.Types.Name hiding (varName) import GHC.Utils.Panic import qualified GHC.Utils.Binary as B import Data.Char +import Control.DeepSeq import Language.Haskell.Syntax.Module.Name @@ -33,6 +34,11 @@ instance Outputable NamePattern where ppr (PWildcard rest) = char '*' <> ppr rest ppr PEnd = Outputable.empty +instance NFData NamePattern where + rnf (PChar c n) = rnf c `seq` rnf n + rnf (PWildcard np) = rnf np + rnf PEnd = () + instance B.Binary NamePattern where get bh = do tag <- B.get bh @@ -76,6 +82,9 @@ data CallerCcFilter , ccfFuncName :: NamePattern } +instance NFData CallerCcFilter where + rnf (CallerCcFilter mn n) = rnf mn `seq` rnf n + instance Outputable CallerCcFilter where ppr ccf = maybe (char '*') ppr (ccfModuleName ccf) ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -102,6 +102,7 @@ import GHC.Data.Maybe import GHC.Builtin.Names ( mAIN_NAME ) import GHC.Driver.Backend import GHC.Driver.Flags +import GHC.Driver.IncludeSpecs import GHC.Driver.Phases ( Phase(..), phaseInputExt ) import GHC.Driver.Plugins.External import GHC.Settings @@ -922,44 +923,6 @@ data PkgDbRef | PkgDbPath FilePath deriving Eq --- | Used to differentiate the scope an include needs to apply to. --- We have to split the include paths to avoid accidentally forcing recursive --- includes since -I overrides the system search paths. See #14312. -data IncludeSpecs - = IncludeSpecs { includePathsQuote :: [String] - , includePathsGlobal :: [String] - -- | See Note [Implicit include paths] - , includePathsQuoteImplicit :: [String] - } - deriving Show - --- | Append to the list of includes a path that shall be included using `-I` --- when the C compiler is called. These paths override system search paths. -addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs -addGlobalInclude spec paths = let f = includePathsGlobal spec - in spec { includePathsGlobal = f ++ paths } - --- | Append to the list of includes a path that shall be included using --- `-iquote` when the C compiler is called. These paths only apply when quoted --- includes are used. e.g. #include "foo.h" -addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs -addQuoteInclude spec paths = let f = includePathsQuote spec - in spec { includePathsQuote = f ++ paths } - --- | These includes are not considered while fingerprinting the flags for iface --- | See Note [Implicit include paths] -addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs -addImplicitQuoteInclude spec paths = let f = includePathsQuoteImplicit spec - in spec { includePathsQuoteImplicit = f ++ paths } - - --- | Concatenate and flatten the list of global and quoted includes returning --- just a flat list of paths. -flattenIncludes :: IncludeSpecs -> [String] -flattenIncludes specs = - includePathsQuote specs ++ - includePathsQuoteImplicit specs ++ - includePathsGlobal specs -- An argument to --reexported-module which can optionally specify a module renaming. ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -693,6 +693,7 @@ data GeneralFlag | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless | Opt_WriteInterface -- forces .hi files to be written even with -fno-code | Opt_WriteSelfRecompInfo + | Opt_WriteSelfRecompFlags -- ^ Include detailed flag information for self-recompilation debugging | Opt_WriteHie -- generate .hie files -- JavaScript opts ===================================== compiler/GHC/Driver/IncludeSpecs.hs ===================================== @@ -0,0 +1,48 @@ +module GHC.Driver.IncludeSpecs + ( IncludeSpecs(..) + , addGlobalInclude + , addQuoteInclude + , addImplicitQuoteInclude + , flattenIncludes + ) where + +import GHC.Prelude + +-- | Used to differentiate the scope an include needs to apply to. +-- We have to split the include paths to avoid accidentally forcing recursive +-- includes since -I overrides the system search paths. See #14312. +data IncludeSpecs + = IncludeSpecs { includePathsQuote :: [String] + , includePathsGlobal :: [String] + -- | See Note [Implicit include paths] + , includePathsQuoteImplicit :: [String] + } + deriving Show + +-- | Append to the list of includes a path that shall be included using `-I` +-- when the C compiler is called. These paths override system search paths. +addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs +addGlobalInclude spec paths = let f = includePathsGlobal spec + in spec { includePathsGlobal = f ++ paths } + +-- | Append to the list of includes a path that shall be included using +-- `-iquote` when the C compiler is called. These paths only apply when quoted +-- includes are used. e.g. #include "foo.h" +addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs +addQuoteInclude spec paths = let f = includePathsQuote spec + in spec { includePathsQuote = f ++ paths } + +-- | These includes are not considered while fingerprinting the flags for iface +-- | See Note [Implicit include paths] +addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs +addImplicitQuoteInclude spec paths = let f = includePathsQuoteImplicit spec + in spec { includePathsQuoteImplicit = f ++ paths } + + +-- | Concatenate and flatten the list of global and quoted includes returning +-- just a flat list of paths. +flattenIncludes :: IncludeSpecs -> [String] +flattenIncludes specs = + includePathsQuote specs ++ + includePathsQuoteImplicit specs ++ + includePathsGlobal specs \ No newline at end of file ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2528,7 +2528,8 @@ fFlagsDeps = [ flagSpec "use-rpaths" Opt_RPath, flagSpec "write-interface" Opt_WriteInterface, flagSpec "write-if-simplified-core" Opt_WriteIfSimplifiedCore, - flagSpec "write-if-self-recomp" Opt_WriteSelfRecompInfo, + flagSpec "write-if-self-recomp" Opt_WriteSelfRecompInfo, + flagSpec "write-if-self-recomp-flags" Opt_WriteSelfRecompFlags, flagSpec "write-ide-info" Opt_WriteHie, flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields, flagSpec "unbox-strict-fields" Opt_UnboxStrictFields, ===================================== compiler/GHC/Iface/Env.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Iface.Env ( ifaceExportNames, - trace_if, trace_hi_diffs, + trace_if, trace_hi_diffs, trace_hi_diffs_io, -- Name-cache stuff allocateGlobalBinder, @@ -270,6 +270,12 @@ trace_if :: Logger -> SDoc -> IO () {-# INLINE trace_if #-} -- see Note [INLINE conditional tracing utilities] trace_if logger doc = when (logHasDumpFlag logger Opt_D_dump_if_trace) $ putMsg logger doc +trace_hi_diffs_io :: Logger -> IO SDoc -> IO () +{-# INLINE trace_hi_diffs_io #-} -- see Note [INLINE conditional tracing utilities] +trace_hi_diffs_io logger doc = + when (logHasDumpFlag logger Opt_D_dump_hi_diffs) $ + doc >>= putMsg logger + trace_hi_diffs :: Logger -> SDoc -> IO () {-# INLINE trace_hi_diffs #-} -- see Note [INLINE conditional tracing utilities] -trace_hi_diffs logger doc = when (logHasDumpFlag logger Opt_D_dump_hi_diffs) $ putMsg logger doc +trace_hi_diffs logger doc = trace_hi_diffs_io logger (pure doc) ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -0,0 +1,200 @@ +-- | Datatype definitions for the flag representation stored in interface files +module GHC.Iface.Flags ( + IfaceDynFlags(..) + , IfaceGeneralFlag(..) + , IfaceProfAuto(..) + , IfaceExtension(..) + , IfaceLanguage(..) + , IfaceCppOptions(..) + , pprIfaceDynFlags + , missingExtraFlagInfo + ) where + +import GHC.Prelude + +import GHC.Utils.Outputable +import Control.DeepSeq +import GHC.Utils.Fingerprint +import GHC.Utils.Binary + +import GHC.Driver.DynFlags +import GHC.Types.SafeHaskell +import GHC.Core.Opt.CallerCC.Types + +import qualified GHC.LanguageExtensions as LangExt + +-- The part of DynFlags which recompilation information needs +data IfaceDynFlags = IfaceDynFlags + { ifaceMainIs :: Maybe (Maybe String) + , ifaceSafeMode :: IfaceTrustInfo + , ifaceLang :: Maybe IfaceLanguage + , ifaceExts :: [IfaceExtension] + , ifaceCppOptions :: IfaceCppOptions + , ifaceJsOptions :: IfaceCppOptions + , ifaceCmmOptions :: IfaceCppOptions + , ifacePaths :: [String] + , ifaceProf :: Maybe IfaceProfAuto + , ifaceTicky :: [IfaceGeneralFlag] + , ifaceCodeGen :: [IfaceGeneralFlag] + , ifaceFatIface :: Bool + , ifaceDebugLevel :: Int + , ifaceCallerCCFilters :: [CallerCcFilter] + } + +pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc +pprIfaceDynFlags (f, mflags) = + vcat $ + [ text "fingerprint:" <+> (ppr f) + ] + ++ case mflags of + Nothing -> [missingExtraFlagInfo] + Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> + [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] + +missingExtraFlagInfo :: SDoc +missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" + where + -- If you modify the name of this flag, you have to modify this string. + _placeholder = Opt_WriteSelfRecompFlags + +instance Binary IfaceDynFlags where + put_ bh (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = do + put_ bh a1 + put_ bh a2 + put_ bh a3 + put_ bh a4 + put_ bh a5 + put_ bh a6 + put_ bh a7 + put_ bh a8 + put_ bh a9 + put_ bh a10 + put_ bh a11 + put_ bh a12 + put_ bh a13 + put_ bh a14 + get bh = IfaceDynFlags <$> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + <*> get bh + +instance NFData IfaceDynFlags where + rnf (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +newtype IfaceGeneralFlag = IfaceGeneralFlag GeneralFlag + +instance NFData IfaceGeneralFlag where + rnf (IfaceGeneralFlag !_) = () + +instance Binary IfaceGeneralFlag where + put_ bh (IfaceGeneralFlag f) = put_ bh (fromEnum f) + get bh = IfaceGeneralFlag . toEnum <$> get bh + +instance Outputable IfaceGeneralFlag where + ppr (IfaceGeneralFlag f) = text (show f) + +newtype IfaceProfAuto = IfaceProfAuto ProfAuto + +instance NFData IfaceProfAuto where + rnf (IfaceProfAuto !_) = () + +instance Binary IfaceProfAuto where + put_ bh (IfaceProfAuto f) = put_ bh (fromEnum f) + get bh = IfaceProfAuto . toEnum <$> get bh + +instance Outputable IfaceProfAuto where + ppr (IfaceProfAuto f) = text (show f) + + +newtype IfaceExtension = IfaceExtension LangExt.Extension + +instance NFData IfaceExtension where + rnf (IfaceExtension !_) = () + +instance Binary IfaceExtension where + put_ bh (IfaceExtension f) = put_ bh (fromEnum f) + get bh = IfaceExtension . toEnum <$> get bh + +instance Outputable IfaceExtension where + ppr (IfaceExtension f) = text (show f) + +newtype IfaceLanguage = IfaceLanguage Language + +instance NFData IfaceLanguage where + rnf (IfaceLanguage !_) = () + +instance Binary IfaceLanguage where + put_ bh (IfaceLanguage f) = put_ bh (fromEnum f) + get bh = IfaceLanguage . toEnum <$> get bh + +instance Outputable IfaceLanguage where + ppr (IfaceLanguage f) = text (show f) + +data IfaceCppOptions = IfaceCppOptions { ifaceCppIncludes :: [FilePath] + , ifaceCppOpts :: [String] + , ifaceCppSig :: ([String], Fingerprint) + } + +instance NFData IfaceCppOptions where + rnf (IfaceCppOptions is os s) = rnf is `seq` rnf os `seq` rnf s + +instance Binary IfaceCppOptions where + put_ bh (IfaceCppOptions is os s) = do + put_ bh is + put_ bh os + put_ bh s + get bh = IfaceCppOptions <$> get bh <*> get bh <*> get bh + +instance Outputable IfaceCppOptions where + ppr (IfaceCppOptions is os (wos, fp)) = + vcat [text "includes:" + , nest 2 $ hcat (map text is) + , text "opts:" + , nest 2 $ hcat (map text os) + , text "signature:" + , nest 2 $ parens (ppr fp) <+> ppr (map (text @SDoc) wos) + + ] \ No newline at end of file ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,6 +59,7 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields +import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -1271,7 +1272,7 @@ pprModIface unit_state iface , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flag hash:" <+> ppr flag_hash) + , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) , nest 2 (text "opt_hash:" <+> ppr opt_hash) , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) @@ -1310,6 +1311,7 @@ pprModIface unit_state iface pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty + {- When printing export lists, we print like this: Avail f f ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -29,8 +29,10 @@ import GHC.Driver.DynFlags import GHC.Driver.Ppr import GHC.Driver.Plugins + import GHC.Iface.Syntax import GHC.Iface.Recomp.Binary +import GHC.Iface.Recomp.Types import GHC.Iface.Load import GHC.Iface.Recomp.Flags import GHC.Iface.Env @@ -70,6 +72,8 @@ import GHC.Unit.Module.Warnings import GHC.Unit.Module.Deps import Control.Monad +import Control.Monad.Trans.State +import Control.Monad.Trans.Class import Data.List (sortBy, sort, sortOn) import qualified Data.Map as Map import qualified Data.Set as Set @@ -189,6 +193,7 @@ data RecompReason | FileChanged FilePath | CustomReason String | FlagsChanged + | LinkFlagsChanged | OptimFlagsChanged | HpcFlagsChanged | MissingBytecode @@ -201,6 +206,7 @@ data RecompReason | THWithJS deriving (Eq) + instance Outputable RecompReason where ppr = \case UnitDepRemoved uid -> ppr uid <+> text "removed" @@ -223,6 +229,7 @@ instance Outputable RecompReason where FileChanged fp -> text fp <+> text "changed" CustomReason s -> text s FlagsChanged -> text "Flags changed" + LinkFlagsChanged -> text "Flags changed" OptimFlagsChanged -> text "Optimisation flags changed" HpcFlagsChanged -> text "HPC flags changed" MissingBytecode -> text "Missing bytecode" @@ -524,13 +531,46 @@ checkHie dflags mod_summary = checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let old_hash = mi_sr_flag_hash self_recomp - new_hash <- fingerprintDynFlags hsc_env iface_mod putNameLiterally - case old_hash == new_hash of - True -> up_to_date logger (text "Module flags unchanged") - False -> out_of_date_hash logger FlagsChanged - (text " Module flags have changed") - old_hash new_hash + let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally + if old_fp == new_fp + then up_to_date logger (text "Module flags unchanged") + else do + -- Do not perform this computation unless -ddump-hi-diffs is on + let diffs = case old_flags of + Nothing -> pure [missingExtraFlagInfo] + Just old_flags -> checkIfaceFlags old_flags new_flags + out_of_date logger FlagsChanged (fmap vcat diffs) + + +checkIfaceFlags :: IfaceDynFlags -> IfaceDynFlags -> IO [SDoc] +checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) + (IfaceDynFlags b1 b2 b3 b4 b5 b6 b7 b8 b9 b10 b11 b12 b13 b14) = + flip execStateT [] $ do + check_one "main is" (ppr . fmap (fmap (text @SDoc))) a1 b1 + check_one_simple "safemode" a2 b2 + check_one_simple "lang" a3 b3 + check_one_simple "exts" a4 b4 + check_one_simple "cpp option" a5 b5 + check_one_simple "js option" a6 b6 + check_one_simple "cmm option" a7 b7 + check_one "paths" (ppr . map (text @SDoc)) a8 b8 + check_one_simple "prof" a9 b9 + check_one_simple "ticky" a10 b10 + check_one_simple "codegen" a11 b11 + check_one_simple "fat iface" a12 b12 + check_one_simple "debug level" a13 b13 + check_one_simple "caller cc filter" a14 b14 + where + diffSimple p a b = vcat [text "before:" <+> p a + , text "after:" <+> p b ] + + check_one_simple s a b = check_one s ppr a b + + check_one s p a b = do + a' <- lift $ computeFingerprint putNameLiterally a + b' <- lift $ computeFingerprint putNameLiterally b + if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired @@ -828,7 +868,7 @@ checkEntityUsage :: Logger checkEntityUsage logger reason new_hash (name,old_hash) = do case new_hash name of -- We used it before, but it ain't there now - Nothing -> out_of_date logger reason (sep [text "No longer exported:", ppr name]) + Nothing -> out_of_date logger reason (pure $ sep [text "No longer exported:", ppr name]) -- It's there, but is it up to date? Just (_, new_hash) | new_hash == old_hash @@ -840,12 +880,12 @@ checkEntityUsage logger reason new_hash (name,old_hash) = do up_to_date :: Logger -> SDoc -> IO RecompileRequired up_to_date logger msg = trace_hi_diffs logger msg >> return UpToDate -out_of_date :: Logger -> RecompReason -> SDoc -> IO RecompileRequired -out_of_date logger reason msg = trace_hi_diffs logger msg >> return (needsRecompileBecause reason) +out_of_date :: Logger -> RecompReason -> IO SDoc -> IO RecompileRequired +out_of_date logger reason msg = trace_hi_diffs_io logger msg >> return (needsRecompileBecause reason) out_of_date_hash :: Logger -> RecompReason -> SDoc -> Fingerprint -> Fingerprint -> IO RecompileRequired out_of_date_hash logger reason msg old_hash new_hash - = out_of_date logger reason (hsep [msg, ppr old_hash, text "->", ppr new_hash]) + = out_of_date logger reason (pure $ hsep [msg, ppr old_hash, text "->", ppr new_hash]) -- --------------------------------------------------------------------------- -- Compute fingerprints for the interface @@ -950,7 +990,7 @@ mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRec mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env - flag_hash <- fingerprintDynFlags hsc_env this_mod putNameLiterally + dyn_flags_info <- fingerprintDynFlags hsc_env this_mod putNameLiterally opt_hash <- fingerprintOptFlags dflags putNameLiterally @@ -958,8 +998,13 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do plugin_hash <- fingerprintPlugins (hsc_plugins hsc_env) + let include_detailed_flags (flag_hash, flags) = + if gopt Opt_WriteSelfRecompFlags dflags + then (flag_hash, Just flags) + else (flag_hash, Nothing) + return (ModIfaceSelfRecomp - { mi_sr_flag_hash = flag_hash + { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash , mi_sr_plugin_hash = plugin_hash ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -19,10 +19,13 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary -import GHC.Core.Opt.CallerCC () -- for Binary instances +import GHC.Iface.Flags import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) +import Data.Maybe + +-- The subset of DynFlags which is used by the recompilation checker. -- | Produce a fingerprint of a @DynFlags@ value. We only base -- the finger print on important fields in @DynFlags@ so that @@ -32,7 +35,7 @@ import System.FilePath (normalise) -- file, not the actual 'Module' according to our 'DynFlags'. fingerprintDynFlags :: HscEnv -> Module -> (WriteBinHandle -> Name -> IO ()) - -> IO Fingerprint + -> IO (Fingerprint, IfaceDynFlags) fingerprintDynFlags hsc_env this_mod nameio = let dflags at DynFlags{..} = hsc_dflags hsc_env @@ -43,53 +46,61 @@ fingerprintDynFlags hsc_env this_mod nameio = -- oflags = sort $ filter filterOFlags $ flags dflags -- all the extension flags and the language - lang = (fmap fromEnum language, - map fromEnum $ EnumSet.toList extensionFlags) + lang = fmap IfaceLanguage language + exts = map IfaceExtension $ EnumSet.toList extensionFlags -- avoid fingerprinting the absolute path to the directory of the source file -- see Note [Implicit include paths] includePathsMinusImplicit = includePaths { includePathsQuoteImplicit = [] } -- -I, -D and -U flags affect Haskell C/CPP Preprocessor - cpp = ( map normalise $ flattenIncludes includePathsMinusImplicit - -- normalise: eliminate spurious differences due to "./foo" vs "foo" - , picPOpts dflags - , opt_P_signature dflags) + cpp = IfaceCppOptions + { ifaceCppIncludes = map normalise $ flattenIncludes includePathsMinusImplicit + -- normalise: eliminate spurious differences due to "./foo" vs "foo" + , ifaceCppOpts = picPOpts dflags + , ifaceCppSig = opt_P_signature dflags + } -- See Note [Repeated -optP hashing] + -- -I, -D and -U flags affect JavaScript C/CPP Preprocessor - js = ( map normalise $ flattenIncludes includePathsMinusImplicit + js = IfaceCppOptions + { ifaceCppIncludes = map normalise $ flattenIncludes includePathsMinusImplicit -- normalise: eliminate spurious differences due to "./foo" vs "foo" - , picPOpts dflags - , opt_JSP_signature dflags) + , ifaceCppOpts = picPOpts dflags + , ifaceCppSig = opt_JSP_signature dflags + } -- See Note [Repeated -optP hashing] -- -I, -D and -U flags affect C-- CPP Preprocessor - cmm = ( map normalise $ flattenIncludes includePathsMinusImplicit + cmm = IfaceCppOptions { + ifaceCppIncludes = map normalise $ flattenIncludes includePathsMinusImplicit -- normalise: eliminate spurious differences due to "./foo" vs "foo" - , picPOpts dflags - , opt_CmmP_signature dflags) + , ifaceCppOpts = picPOpts dflags + , ifaceCppSig = ([], opt_CmmP_signature dflags) + } -- Note [path flags and recompilation] paths = [ hcSuf ] -- -fprof-auto etc. - prof = if sccProfilingEnabled dflags then fromEnum profAuto else 0 + prof = if sccProfilingEnabled dflags then Just (IfaceProfAuto profAuto) else Nothing -- Ticky ticky = - map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk, Opt_Ticky_Tag] + mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk, Opt_Ticky_Tag] -- Other flags which affect code generation - codegen = map (`gopt` dflags) (EnumSet.toList codeGenFlags) + codegen = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) (EnumSet.toList codeGenFlags) -- Did we include core for all bindings? fat_iface = gopt Opt_WriteIfSimplifiedCore dflags - flags = ((mainis, safeHs, lang, cpp, js, cmm), (paths, prof, ticky, codegen, debugLevel, callerCcFilters, fat_iface)) + f = IfaceDynFlags mainis safeHs lang exts cpp js cmm paths prof ticky codegen fat_iface debugLevel callerCcFilters - in -- pprTrace "flags" (ppr flags) $ - computeFingerprint nameio flags + in do + fp <- computeFingerprint nameio f + return (fp, f) -- Fingerprint the optimisation info. We keep this separate from the rest of -- the flags because GHCi users (especially) may wish to ignore changes in ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,9 +1,14 @@ -module GHC.Iface.Recomp.Types ( ModIfaceSelfRecomp(..) - ) where +module GHC.Iface.Recomp.Types ( + ModIfaceSelfRecomp(..), + IfaceDynFlags(..), + pprIfaceDynFlags, + missingExtraFlagInfo, +) where import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable +import GHC.Iface.Flags import GHC.Unit.Module.Deps import GHC.Utils.Binary @@ -64,7 +69,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !Fingerprint + , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -99,7 +104,7 @@ instance Outputable ModIfaceSelfRecomp where = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash , text "usages:" <+> ppr (length mi_sr_usages) - , text "flag hash:" <+> ppr mi_sr_flag_hash + , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash ===================================== compiler/GHC/Types/ProfAuto.hs ===================================== @@ -12,4 +12,4 @@ data ProfAuto | ProfAutoTop -- ^ top-level functions annotated only | ProfAutoExports -- ^ exported functions annotated only | ProfAutoCalls -- ^ annotate call-sites - deriving (Eq,Enum) + deriving (Eq,Enum, Show) ===================================== compiler/GHC/Types/SafeHaskell.hs ===================================== @@ -14,6 +14,7 @@ import GHC.Prelude import GHC.Utils.Binary import GHC.Utils.Outputable +import Control.DeepSeq import Data.Word @@ -31,6 +32,15 @@ data SafeHaskellMode | Sf_Ignore -- ^ @-fno-safe-haskell@ state deriving (Eq) +instance NFData SafeHaskellMode where + rnf x = case x of + Sf_None -> () + Sf_Unsafe -> () + Sf_Trustworthy -> () + Sf_Safe -> () + Sf_SafeInferred -> () + Sf_Ignore -> () + instance Show SafeHaskellMode where show Sf_None = "None" show Sf_Unsafe = "Unsafe" @@ -46,6 +56,10 @@ instance Outputable SafeHaskellMode where -- Simply a wrapper around SafeHaskellMode to separate iface and flags newtype IfaceTrustInfo = TrustInfo SafeHaskellMode +instance NFData IfaceTrustInfo where + rnf (TrustInfo shm) = rnf shm + + getSafeMode :: IfaceTrustInfo -> SafeHaskellMode getSafeMode (TrustInfo x) = x ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -103,6 +103,7 @@ import GHC.Prelude import GHC.Hs import GHC.Iface.Syntax +import GHC.Iface.Flags import GHC.Iface.Ext.Fields import GHC.Iface.Recomp.Types @@ -395,7 +396,7 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe Fingerprint +mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint @@ -613,7 +614,6 @@ instance Binary ModIface where }}) - emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface ===================================== compiler/ghc.cabal.in ===================================== @@ -511,6 +511,7 @@ Library GHC.Driver.Config.Tidy GHC.Driver.Config.StgToJS GHC.Driver.DynFlags + GHC.Driver.IncludeSpecs GHC.Driver.Env GHC.Driver.Env.KnotVars GHC.Driver.Env.Types @@ -609,6 +610,7 @@ Library GHC.Iface.Recomp.Types GHC.Iface.Rename GHC.Iface.Syntax + GHC.Iface.Flags GHC.Iface.Tidy GHC.Iface.Tidy.StaticPtrTable GHC.Iface.Warnings ===================================== docs/users_guide/phases.rst ===================================== @@ -705,7 +705,6 @@ Options affecting code generation .. ghc-flag:: -fwrite-if-self-recomp :shortdesc: Write information for self-recompilation checking in an interface file :type: dynamic - :category: codegen :default: on @@ -718,6 +717,14 @@ Options affecting code generation there is less chance of build paths leaking into the interface file and affecting determinism. +.. ghc-flag:: -fwrite-if-self-recomp-flags + :shortdesc: Include detailed flag information for self-recompilation checking + :type: dynamic + + Include detailed information about which flags were used during compilation + in an interface file. This makes it easier to debug issues with recompilation + by providing more context about the compilation environment. This flag is + primarily intended for debugging recompilation problems with ``-ddump-hi-diffs`` ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -91,6 +91,7 @@ GHC.Driver.Backend GHC.Driver.Backend.Internal GHC.Driver.DynFlags GHC.Driver.Flags +GHC.Driver.IncludeSpecs GHC.Driver.Phases GHC.Driver.Pipeline.Monad GHC.Driver.Plugins.External @@ -111,6 +112,7 @@ GHC.Hs.Type GHC.Hs.Utils GHC.Iface.Errors.Types GHC.Iface.Ext.Fields +GHC.Iface.Flags GHC.Iface.Recomp.Binary GHC.Iface.Recomp.Types GHC.Iface.Syntax ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -95,6 +95,7 @@ GHC.Driver.Backpack.Syntax GHC.Driver.DynFlags GHC.Driver.Errors.Types GHC.Driver.Flags +GHC.Driver.IncludeSpecs GHC.Driver.Phases GHC.Driver.Pipeline.Monad GHC.Driver.Plugins.External @@ -117,6 +118,7 @@ GHC.HsToCore.Errors.Types GHC.HsToCore.Pmc.Solver.Types GHC.Iface.Errors.Types GHC.Iface.Ext.Fields +GHC.Iface.Flags GHC.Iface.Recomp.Binary GHC.Iface.Recomp.Types GHC.Iface.Syntax View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/44bf5fa13ddccacd9d91650fca6eb1dcf3f4cfb6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/44bf5fa13ddccacd9d91650fca6eb1dcf3f4cfb6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/7eedea32/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 13:51:15 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 08:51:15 -0500 Subject: [Git][ghc/ghc][master] Run fix-whitespace on compiler/ Message-ID: <67cc4b53252b1_285c5d8e52b07768b@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 21 changed files: - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Utils/Unique.hs Changes: ===================================== compiler/GHC/Cmm/CallConv.hs ===================================== @@ -321,4 +321,4 @@ backend is liable to compile code using e.g. the ZMM1 STG register to uses of X86 machine registers xmm1, xmm2, xmm3, xmm4, instead of just zmm1. This would mean that LLVM produces ABI-incompatible code that would result in segfaults in the RTS. --} \ No newline at end of file +-} ===================================== compiler/GHC/Cmm/Liveness.hs ===================================== @@ -155,4 +155,3 @@ xferLiveL platform (BlockCC eNode middle xNode) fBase = !result = foldNodesBwdOO (gen_killL platform) middle joined in mapSingleton (entryLabel eNode) result - ===================================== compiler/GHC/CmmToAsm/Reg/Linear/Base.hs ===================================== @@ -207,4 +207,3 @@ data RA_State freeRegs } - ===================================== compiler/GHC/CmmToAsm/X86/RegInfo.hs ===================================== @@ -68,4 +68,3 @@ normalRegColors platform = -- ,"#afafaf","#b6b6b6","#bdbdbd","#c4c4c4","#cbcbcb" -- ,"#d2d2d2","#d9d9d9","#e0e0e0"] - ===================================== compiler/GHC/Core/LateCC/TopLevelBinds.hs ===================================== @@ -125,4 +125,4 @@ topLevelBindsCC pred core_bind = let name = idName bndr cc_loc = nameSrcSpan name cc_name = getOccFS name - insertCC cc_name cc_loc rhs \ No newline at end of file + insertCC cc_name cc_loc rhs ===================================== compiler/GHC/Data/BooleanFormula.hs ===================================== @@ -237,4 +237,4 @@ pprBooleanFormulaNormal = go go (And xs) = fsep $ punctuate comma (map (go . unLoc) xs) go (Or []) = keyword $ text "FALSE" go (Or xs) = fsep $ intersperse vbar (map (go . unLoc) xs) - go (Parens x) = parens (go $ unLoc x) \ No newline at end of file + go (Parens x) = parens (go $ unLoc x) ===================================== compiler/GHC/Data/Graph/Color.hs ===================================== @@ -380,5 +380,3 @@ selectColor colors graph u in chooseColor - - ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -594,4 +594,4 @@ deriving instance Data XViaStrategyPs -- --------------------------------------------------------------------- deriving instance (Typeable p, Data (Anno (IdGhcP p)), Data (IdGhcP p)) => Data (BooleanFormula (GhcPass p)) ---------------------------------------------------------------------- \ No newline at end of file +--------------------------------------------------------------------- ===================================== compiler/GHC/Hs/Specificity.hs ===================================== @@ -49,4 +49,3 @@ instance NFData ForAllTyFlag where rnf (Invisible spec) = rnf spec rnf Required = () - ===================================== compiler/GHC/JS/Opt/Expr.hs ===================================== @@ -183,4 +183,4 @@ eqVal (JStr s1) (JStr s2) = s1 == s2 eqVal (JBool b1) (JBool b2) = b1 == b2 eqVal (JDouble (SaneDouble d1)) (JDouble (SaneDouble d2)) | not (isNaN d1) && not (isNaN d2) = d1 == d2 -eqVal _ _ = False \ No newline at end of file +eqVal _ _ = False ===================================== compiler/GHC/JS/Opt/Simple.hs ===================================== @@ -604,4 +604,4 @@ isClosureAllocator "h$c21" = True isClosureAllocator "h$c22" = True isClosureAllocator "h$c23" = True isClosureAllocator "h$c24" = True -isClosureAllocator _ = False \ No newline at end of file +isClosureAllocator _ = False ===================================== compiler/GHC/Platform/LoongArch64.hs ===================================== @@ -6,4 +6,4 @@ import GHC.Prelude #define MACHREGS_NO_REGS 0 #define MACHREGS_loongarch64 1 -#include "CodeGen.Platform.h" \ No newline at end of file +#include "CodeGen.Platform.h" ===================================== compiler/GHC/StgToCmm/TagCheck.hs ===================================== @@ -175,4 +175,3 @@ checkArgStatic msg MarkedStrict arg = whenCheckTags $ then return () else pprPanic "Arg not tagged as expected" (ppr msg <+> ppr arg) - ===================================== compiler/GHC/Tc/Errors/Hole/FitTypes.hs ===================================== @@ -128,4 +128,3 @@ hfIsLcl hf@(HoleFit {}) = case hfCand hf of NameHFCand _ -> False GreHFCand gre -> gre_lcl gre - ===================================== compiler/GHC/Tc/Errors/Hole/Plugin.hs ===================================== @@ -26,4 +26,4 @@ data HoleFitPluginR = forall s. HoleFitPluginR -- ^ The function defining the plugin itself , hfPluginStop :: TcRef s -> TcM () -- ^ Cleanup of state, guaranteed to be called even on error - } \ No newline at end of file + } ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -1538,4 +1538,3 @@ runTcPluginSolvers solvers all_cts CtGiven {} -> (ct:givens, wanteds) CtWanted {} -> (givens, (ev,ct):wanteds) - ===================================== compiler/GHC/Tc/TyCl/Class.hs ===================================== @@ -598,4 +598,4 @@ warnMissingAT name $ InvalidAssoc $ InvalidAssocInstance $ AssocInstanceMissing name ; diagnosticTc (warn && hsc_src == HsSrcFile) diag - } \ No newline at end of file + } ===================================== compiler/GHC/Tc/Types/TcRef.hs ===================================== @@ -34,4 +34,4 @@ updTcRefM ref upd = do { contents <- readTcRef ref ; !new_contents <- upd contents ; writeTcRef ref new_contents } -{-# INLINE updTcRefM #-} \ No newline at end of file +{-# INLINE updTcRefM #-} ===================================== compiler/GHC/Types/PkgQual.hs ===================================== @@ -57,4 +57,3 @@ instance Binary PkgQual where 2 -> do u <- get bh return (OtherPkg u) _ -> fail "instance Binary PkgQual: Invalid tag" - ===================================== compiler/GHC/Types/SptEntry.hs ===================================== @@ -14,4 +14,3 @@ data SptEntry = SptEntry Id Fingerprint instance Outputable SptEntry where ppr (SptEntry id fpr) = ppr id <> colon <+> ppr fpr - ===================================== compiler/GHC/Utils/Unique.hs ===================================== @@ -32,4 +32,4 @@ sameUnique x y = getUnique x == getUnique y {-# INLINE anyOfUnique #-} #endif anyOfUnique :: Uniquable a => a -> [Unique] -> Bool -anyOfUnique tc xs = getUnique tc `elem` xs \ No newline at end of file +anyOfUnique tc xs = getUnique tc `elem` xs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/324222bd2d67af2131f5355cb220584bd499295f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/324222bd2d67af2131f5355cb220584bd499295f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/41eef473/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 14:22:20 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 09:22:20 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Run fix-whitespace on compiler/ Message-ID: <67cc529cd03e0_285c5d118406087131@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 2793eb47 by sheaf at 2025-03-08T09:22:05-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - aaf11747 by Andreas Klebinger at 2025-03-08T09:22:07-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - c64d5f46 by Andreas Klebinger at 2025-03-08T09:22:08-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - 50 changed files: - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Utils/Unique.hs - docs/users_guide/9.14.1-notes.rst - testsuite/driver/perf_notes.py - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a9a0f6b0c9a7407c2edd3c825c8e64ab3a4a2f7...c64d5f466fc9f1cd8d42e0f79a6ba0d526788579 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a9a0f6b0c9a7407c2edd3c825c8e64ab3a4a2f7...c64d5f466fc9f1cd8d42e0f79a6ba0d526788579 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/7142f75c/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 8 15:14:52 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 08 Mar 2025 10:14:52 -0500 Subject: [Git][ghc/ghc][wip/T25647] 3 commits: Refactor HsOuterTyVarBndrs to include implicit variable bindings and update... Message-ID: <67cc5eec8b1d0_2b6a5af9218629ab@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 131c1485 by Patrick at 2025-03-08T02:11:52+08:00 Refactor HsOuterTyVarBndrs to include implicit variable bindings and update related functions for consistency - - - - - 2e7666eb by Patrick at 2025-03-08T23:06:28+08:00 Enhance HsOuterTyVarBndrs to support implicit variable bindings and update related functions for consistency - - - - - 653aa8da by Patrick at 2025-03-08T23:14:13+08:00 Add new test case T25647d - - - - - 16 changed files: - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/Language/Haskell/Syntax/Type.hs - + testsuite/tests/typecheck/should_compile/T25647d.hs - testsuite/tests/typecheck/should_compile/all.T - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs Changes: ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -594,4 +594,4 @@ deriving instance Data XViaStrategyPs -- --------------------------------------------------------------------- deriving instance (Typeable p, Data (Anno (IdGhcP p)), Data (IdGhcP p)) => Data (BooleanFormula (GhcPass p)) ---------------------------------------------------------------------- \ No newline at end of file +--------------------------------------------------------------------- ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -312,7 +312,7 @@ dropWildCards sig_ty = hswc_body sig_ty hsOuterTyVarNames :: HsOuterTyVarBndrs flag GhcRn -> [Name] hsOuterTyVarNames (HsOuterImplicit{hso_ximplicit = imp_tvs}) = imp_tvs -hsOuterTyVarNames (HsOuterExplicit{hso_bndrs = bndrs}) = hsLTyVarNames bndrs +hsOuterTyVarNames (HsOuterExplicit{hso_bndrs = bndrs, hso_ximplicit= imp_tvs}) = hsLTyVarNames bndrs ++ imp_tvs hsOuterExplicitBndrs :: HsOuterTyVarBndrs flag (GhcPass p) -> [LHsTyVarBndr flag (NoGhcTc (GhcPass p))] @@ -325,7 +325,9 @@ mkHsOuterImplicit = HsOuterImplicit{hso_ximplicit = noExtField} mkHsOuterExplicit :: EpAnnForallInvis -> [LHsTyVarBndr flag GhcPs] -> HsOuterTyVarBndrs flag GhcPs mkHsOuterExplicit an bndrs = HsOuterExplicit { hso_xexplicit = an - , hso_bndrs = bndrs } + , hso_bndrs = bndrs + , hso_ximplicit = NoExtField + } mkHsImplicitSigType :: LHsType GhcPs -> HsSigType GhcPs mkHsImplicitSigType body = @@ -1243,8 +1245,12 @@ instance (OutputableBndrFlag flag p, GhcPs -> ppr imp_tvs GhcRn -> ppr imp_tvs GhcTc -> ppr imp_tvs - ppr (HsOuterExplicit{hso_bndrs = exp_tvs}) = + ppr (HsOuterExplicit{hso_bndrs = exp_tvs, hso_ximplicit=imp_tvs}) = text "HsOuterExplicit:" <+> ppr exp_tvs + <+> case ghcPass @p of + GhcPs -> ppr imp_tvs + GhcRn -> ppr imp_tvs + GhcTc -> ppr imp_tvs instance OutputableBndrId p => Outputable (HsForAllTelescope (GhcPass p)) where ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -1224,7 +1224,7 @@ addHsOuterSigTyVarBinds outer_bndrs thing_inside = case outer_bndrs of HsOuterImplicit{hso_ximplicit = imp_tvs} -> do th_nil <- coreListM tyVarBndrSpecTyConName [] addSimpleTyVarBinds FreshNamesOnly imp_tvs $ thing_inside th_nil - HsOuterExplicit{hso_bndrs = exp_bndrs} -> + HsOuterExplicit{hso_bndrs = exp_bndrs, hso_ximplicit= imp_tvs} -> addHsTyVarBinds FreshNamesOnly exp_bndrs thing_inside -- | If a type implicitly quantifies its outermost type variables, return ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1872,7 +1872,10 @@ instance ToHie (TScoped (LocatedA (HsSigType GhcRn))) where instance Data flag => ToHie (TVScoped (HsOuterTyVarBndrs flag GhcRn)) where toHie (TVS tsc sc bndrs) = case bndrs of HsOuterImplicit xs -> bindingsOnly $ map (C $ TyVarBind sc tsc) xs - HsOuterExplicit _ xs -> toHie $ tvScopes tsc sc xs + HsOuterExplicit _ xs ys -> do + implicits <- bindingsOnly (map (C $ TyVarBind sc tsc) ys) + explicits <- toHie (tvScopes tsc sc xs); + pure $ implicits ++ explicits toHieForAllTele :: HsForAllTelescope GhcRn -> SrcSpan -> HieM [HieAST Type] toHieForAllTele (HsForAllVis { hsf_vis_bndrs = bndrs }) loc = ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -818,7 +818,7 @@ mkGadtDecl loc names dcol ty = do let bndrs_loc = case outer_bndrs of HsOuterImplicit{} -> getLoc ty - HsOuterExplicit an _ -> EpAnn (entry an) noAnn emptyComments + HsOuterExplicit an _ _ -> EpAnn (entry an) noAnn emptyComments let l = EpAnn (spanAsAnchor loc) noAnn csa ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -29,7 +29,8 @@ module GHC.Rename.HsType ( checkPrecMatch, checkSectionPrec, -- Binding related stuff - bindHsOuterTyVarBndrs, bindHsForAllTelescope, + RnBindFam(..), + bindHsOuterTyVarBndrs, bindHsOuterTyVarBndrs', bindHsForAllTelescope, bindLHsTyVarBndr, bindLHsTyVarBndrs, WarnUnusedForalls(..), rnImplicitTvOccs, bindSigTyVarsFV, bindHsQTyVars, FreeKiTyVars, filterInScopeM, @@ -1091,6 +1092,7 @@ an LHsQTyVars can be semantically significant. As a result, we suppress -Wunused-foralls warnings in exactly one place: in bindHsQTyVars. -} +data RnBindFam = BindFam | NotBindFam bindHsOuterTyVarBndrs :: OutputableBndrFlag flag 'Renamed => HsDocContext -> Maybe assoc @@ -1099,7 +1101,18 @@ bindHsOuterTyVarBndrs :: OutputableBndrFlag flag 'Renamed -> HsOuterTyVarBndrs flag GhcPs -> (HsOuterTyVarBndrs flag GhcRn -> RnM (a, FreeVars)) -> RnM (a, FreeVars) -bindHsOuterTyVarBndrs doc mb_cls implicit_vars outer_bndrs thing_inside = +bindHsOuterTyVarBndrs = bindHsOuterTyVarBndrs' NotBindFam + +bindHsOuterTyVarBndrs' :: OutputableBndrFlag flag 'Renamed + => RnBindFam + -> HsDocContext + -> Maybe assoc + -- ^ @'Just' _@ => an associated type decl + -> FreeKiTyVars + -> HsOuterTyVarBndrs flag GhcPs + -> (HsOuterTyVarBndrs flag GhcRn -> RnM (a, FreeVars)) + -> RnM (a, FreeVars) +bindHsOuterTyVarBndrs' bind_fam doc mb_cls implicit_vars outer_bndrs thing_inside = case outer_bndrs of HsOuterImplicit{} -> rnImplicitTvOccs mb_cls implicit_vars $ \implicit_vars' -> @@ -1110,9 +1123,15 @@ bindHsOuterTyVarBndrs doc mb_cls implicit_vars outer_bndrs thing_inside = -- scope here. This is an explicit forall, so we want fresh names, not -- class variables. Thus: always pass Nothing. bindLHsTyVarBndrs doc WarnUnusedForalls Nothing exp_bndrs $ \exp_bndrs' -> do - checkForAllTelescopeWildcardBndrs doc exp_bndrs' - thing_inside $ HsOuterExplicit { hso_xexplicit = noExtField - , hso_bndrs = exp_bndrs' } + rnImplicitTvOccs mb_cls fam_implicit_vars $ \implicit_vars' -> do + checkForAllTelescopeWildcardBndrs doc exp_bndrs' + thing_inside $ HsOuterExplicit { hso_xexplicit = noExtField + , hso_bndrs = exp_bndrs' + , hso_ximplicit = implicit_vars' } + where + fam_implicit_vars = case bind_fam of + BindFam -> filterFreeVarsToBind (mapMaybe hsLTyVarLocName $ hso_bndrs outer_bndrs) implicit_vars + NotBindFam -> [] -- See Note [Term variable capture and implicit quantification] warn_term_var_capture :: LocatedN RdrName -> RnM () ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -700,7 +700,7 @@ rnFamEqn doc atfi -- bound by the instance head with filterInScopeM (#19649). ; all_imp_vars <- filterInScopeM $ (pat_kity_vars ++ payload_kvs) - ; bindHsOuterTyVarBndrs doc mb_cls all_imp_vars outer_bndrs $ \rn_outer_bndrs -> + ; bindHsOuterTyVarBndrs' BindFam doc mb_cls all_imp_vars outer_bndrs $ \rn_outer_bndrs -> do { (pats', pat_fvs) <- rnLHsTypeArgs (FamPatCtx tycon) pats ; (payload', rhs_fvs) <- rn_payload doc payload @@ -717,6 +717,7 @@ rnFamEqn doc atfi groups :: [NonEmpty (LocatedN RdrName)] groups = equivClasses cmpLocated pat_kity_vars + ; traceRn "rnFamEqn: rn_outer_bndrs: " (ppr outer_bndrs <+> ppr rn_outer_bndrs') ; nms_dups <- mapM (lookupOccRn . unLoc) $ [ tv | (tv :| (_:_)) <- groups ] -- Add to the used variables ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -44,7 +44,7 @@ module GHC.Tc.Gen.HsType ( etaExpandAlgTyCon, -- tyvars - zonkAndScopedSort, + zonkAndScopedSort, zonkAndScopedSortFam, -- Kind-checking types -- No kind generalisation, no checkValidType @@ -72,7 +72,7 @@ module GHC.Tc.Gen.HsType ( HoleMode(..), -- Utils - tyLitFromLit, tyLitFromOverloadedLit, + tyLitFromLit, tyLitFromOverloadedLit, scopedSortOuterFam, ) where @@ -2264,7 +2264,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) } -- see Note [Implementation tweak for wildCards in family instances] mk_wc_details = case hole_mode of - HM_FamPat FreeArg -> newTyVarMetaVarDetailsAtLevel + HM_FamPat FreeArg -> newTauTvDetailsAtLevel HM_FamPat ClassArg -> newTauTvDetailsAtLevel HM_FamPat SigArg -> newTauTvDetailsAtLevel _ -> newTauTvDetailsAtLevel @@ -3274,22 +3274,35 @@ tcTKTelescope mode tele thing_inside = case tele of -------------------------------------- -- HsOuterTyVarBndrs -------------------------------------- +bindOuterTKBndrsX' :: OutputableBndrFlag flag 'Renamed -- Only to support traceTc + => + SkolemMode + -> HsOuterTyVarBndrs flag GhcRn + -> TcM a + -> TcM (HsOuterTyVarBndrs flag GhcTc, a) +bindOuterTKBndrsX' x = bindOuterTKBndrsX x x bindOuterTKBndrsX :: OutputableBndrFlag flag 'Renamed -- Only to support traceTc - => SkolemMode + => + SkolemMode -- implicit + -> SkolemMode -- explict -> HsOuterTyVarBndrs flag GhcRn -> TcM a -> TcM (HsOuterTyVarBndrs flag GhcTc, a) -bindOuterTKBndrsX skol_mode outer_bndrs thing_inside +bindOuterTKBndrsX i_skol_mode e_skol_mode outer_bndrs thing_inside = case outer_bndrs of HsOuterImplicit{hso_ximplicit = imp_tvs} -> - do { (imp_tvs', thing) <- bindImplicitTKBndrsX skol_mode imp_tvs thing_inside + do { (imp_tvs', thing) <- bindImplicitTKBndrsX i_skol_mode imp_tvs thing_inside ; return ( HsOuterImplicit{hso_ximplicit = imp_tvs'} , thing) } - HsOuterExplicit{hso_bndrs = exp_bndrs} -> - do { (exp_tvs', thing) <- bindExplicitTKBndrsX skol_mode exp_bndrs thing_inside + HsOuterExplicit{hso_bndrs = exp_bndrs, hso_ximplicit = imp_tvs} -> + do { (exp_tvs', (imp_tvs', thing)) <- + bindExplicitTKBndrsX e_skol_mode exp_bndrs + $ bindImplicitTKBndrsX i_skol_mode imp_tvs thing_inside ; return ( HsOuterExplicit { hso_xexplicit = exp_tvs' - , hso_bndrs = exp_bndrs } + , hso_bndrs = exp_bndrs + , hso_ximplicit = imp_tvs' + } , thing) } --------------- @@ -3297,30 +3310,44 @@ outerTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] -- The returned [TcTyVar] is not necessarily in dependency order -- at least for the HsOuterImplicit case outerTyVars (HsOuterImplicit { hso_ximplicit = tvs }) = tvs -outerTyVars (HsOuterExplicit { hso_xexplicit = tvbs }) = binderVars tvbs +outerTyVars (HsOuterExplicit { hso_xexplicit = tvbs, hso_ximplicit = tvs }) = binderVars tvbs ++ tvs --------------- outerTyVarBndrs :: HsOuterTyVarBndrs Specificity GhcTc -> [InvisTVBinder] outerTyVarBndrs (HsOuterImplicit{hso_ximplicit = imp_tvs}) = [Bndr tv SpecifiedSpec | tv <- imp_tvs] -outerTyVarBndrs (HsOuterExplicit{hso_xexplicit = exp_tvs}) = exp_tvs +outerTyVarBndrs (HsOuterExplicit{hso_xexplicit = exp_tvs, hso_ximplicit = imp_tvs}) = exp_tvs ++ [Bndr tv SpecifiedSpec | tv <- imp_tvs] --------------- -scopedSortOuter :: HsOuterTyVarBndrs flag GhcTc -> TcM (HsOuterTyVarBndrs flag GhcTc) +scopedSortOuter :: HsOuterSigTyVarBndrs GhcTc -> TcM (HsOuterSigTyVarBndrs GhcTc) -- Sort any /implicit/ binders into dependency order -- (zonking first so we can see the dependencies) -- /Explicit/ ones are already in the right order scopedSortOuter (HsOuterImplicit{hso_ximplicit = imp_tvs}) = do { imp_tvs <- zonkAndScopedSort imp_tvs ; return (HsOuterImplicit { hso_ximplicit = imp_tvs }) } -scopedSortOuter bndrs@(HsOuterExplicit{}) +scopedSortOuter bndrs@(HsOuterExplicit{ hso_ximplicit =imp_tvs }) = -- No need to dependency-sort (or zonk) explicit quantifiers - return bndrs + do { imp_tvs <- zonkAndScopedSort imp_tvs + ; return bndrs{ hso_ximplicit = imp_tvs } } + +--------------- +scopedSortOuterFam :: HsOuterFamEqnTyVarBndrs GhcTc -> TcM (HsOuterFamEqnTyVarBndrs GhcTc) +-- Sort any /implicit/ binders into dependency order +-- (zonking first so we can see the dependencies) +-- /Explicit/ ones are already in the right order +scopedSortOuterFam (HsOuterImplicit{hso_ximplicit = imp_tvs}) + = do { imp_tvs <- zonkAndScopedSortFam imp_tvs + ; return (HsOuterImplicit { hso_ximplicit = imp_tvs }) } +scopedSortOuterFam bndrs@(HsOuterExplicit{ hso_ximplicit =imp_tvs }) + = -- No need to dependency-sort (or zonk) explicit quantifiers + do { imp_tvs <- zonkAndScopedSortFam imp_tvs + ; return bndrs{ hso_ximplicit = imp_tvs } } --------------- bindOuterSigTKBndrs_Tv :: HsOuterSigTyVarBndrs GhcRn -> TcM a -> TcM (HsOuterSigTyVarBndrs GhcTc, a) bindOuterSigTKBndrs_Tv - = bindOuterTKBndrsX (smVanilla { sm_clone = True, sm_tvtv = SMDTyVarTv }) + = bindOuterTKBndrsX' (smVanilla { sm_clone = True, sm_tvtv = SMDTyVarTv }) bindOuterSigTKBndrs_Tv_M :: TcTyMode -> HsOuterSigTyVarBndrs GhcRn @@ -3330,14 +3357,14 @@ bindOuterSigTKBndrs_Tv_M :: TcTyMode -- Note [Using TyVarTvs for kind-checking GADTs] in GHC.Tc.TyCl -- Note [Checking partial type signatures] bindOuterSigTKBndrs_Tv_M mode - = bindOuterTKBndrsX (smVanilla { sm_clone = True, sm_tvtv = SMDTyVarTv + = bindOuterTKBndrsX' (smVanilla { sm_clone = True, sm_tvtv = SMDTyVarTv , sm_holes = mode_holes mode }) bindOuterFamEqnTKBndrs_Q_Tv :: HsOuterFamEqnTyVarBndrs GhcRn -> TcM a -> TcM (HsOuterFamEqnTyVarBndrs GhcTc, a) bindOuterFamEqnTKBndrs_Q_Tv hs_bndrs thing_inside - = bindOuterTKBndrsX (smVanilla { sm_clone = False, sm_parent = True + = bindOuterTKBndrsX' (smVanilla { sm_clone = False, sm_parent = True , sm_tvtv = SMDTyVarTv }) hs_bndrs thing_inside -- sm_clone=False: see Note [Cloning for type variable binders] @@ -3347,15 +3374,17 @@ bindOuterFamEqnTKBndrs :: SkolemInfo -> TcM a -> TcM (HsOuterFamEqnTyVarBndrs GhcTc, a) bindOuterFamEqnTKBndrs skol_info - = bindOuterTKBndrsX (smVanilla { sm_clone = False, sm_parent = True - , sm_tvtv = SMDSkolemTv skol_info }) + = bindOuterTKBndrsX + (smVanilla { sm_clone = False, sm_parent = True + , sm_tvtv = SMDTauTv }) + (smVanilla { sm_clone = False, sm_parent = True + , sm_tvtv = SMDSkolemTv skol_info }) -- sm_clone=False: see Note [Cloning for type variable binders] --------------- -tcOuterTKBndrs :: OutputableBndrFlag flag 'Renamed -- Only to support traceTc - => SkolemInfo - -> HsOuterTyVarBndrs flag GhcRn - -> TcM a -> TcM (HsOuterTyVarBndrs flag GhcTc, a) +tcOuterTKBndrs :: SkolemInfo + -> HsOuterSigTyVarBndrs GhcRn + -> TcM a -> TcM (HsOuterSigTyVarBndrs GhcTc, a) tcOuterTKBndrs skol_info = tcOuterTKBndrsX (smVanilla { sm_clone = False , sm_tvtv = SMDSkolemTv skol_info }) @@ -3363,10 +3392,10 @@ tcOuterTKBndrs skol_info -- Do not clone the outer binders -- See Note [Cloning for type variable binders] under "must not" -tcOuterTKBndrsX :: OutputableBndrFlag flag 'Renamed -- Only to support traceTc - => SkolemMode -> SkolemInfo - -> HsOuterTyVarBndrs flag GhcRn - -> TcM a -> TcM (HsOuterTyVarBndrs flag GhcTc, a) +tcOuterTKBndrsX :: + SkolemMode -> SkolemInfo + -> HsOuterSigTyVarBndrs GhcRn + -> TcM a -> TcM (HsOuterSigTyVarBndrs GhcTc, a) -- Push level, capture constraints, make implication tcOuterTKBndrsX skol_mode skol_info outer_bndrs thing_inside = case outer_bndrs of @@ -3377,8 +3406,12 @@ tcOuterTKBndrsX skol_mode skol_info outer_bndrs thing_inside HsOuterExplicit{hso_bndrs = exp_bndrs} -> do { (exp_tvs', thing) <- tcExplicitTKBndrsX skol_mode exp_bndrs thing_inside ; return ( HsOuterExplicit { hso_xexplicit = exp_tvs' - , hso_bndrs = exp_bndrs } - , thing) } + , hso_bndrs = exp_bndrs + -- note nothing should be here since + -- sig + , hso_ximplicit = [] } + , thing) + } -------------------------------------- -- Explicit tyvar binders @@ -3392,7 +3425,7 @@ tcExplicitTKBndrs :: OutputableBndrFlag flag 'Renamed -- Only to suppor trace tcExplicitTKBndrs skol_info = tcExplicitTKBndrsX (smVanilla { sm_clone = True, sm_tvtv = SMDSkolemTv skol_info }) -tcExplicitTKBndrsX :: OutputableBndrFlag flag 'Renamed -- Only to suppor traceTc +tcExplicitTKBndrsX :: forall flag a. OutputableBndrFlag flag 'Renamed -- Only to suppor traceTc => SkolemMode -> [LHsTyVarBndr flag GhcRn] -> TcM a @@ -3544,6 +3577,7 @@ newTyVarBndr (SM { sm_clone = clone, sm_tvtv = tvtv }) name kind ; return (setNameUnique name uniq) } False -> return name ; details <- case tvtv of + SMDTauTv -> newMetaDetails TauTv SMDTyVarTv -> newMetaDetails TyVarTv SMDSkolemTv skol_info -> do { lvl <- getTcLevel @@ -3636,6 +3670,7 @@ data SkolemMode data SkolemModeDetails = SMDTyVarTv | SMDSkolemTv SkolemInfo + | SMDTauTv smVanilla :: HasDebugCallStack => SkolemMode @@ -3759,6 +3794,17 @@ zonkAndScopedSort spec_tkvs -- Note [Ordering of implicit variables] in GHC.Rename.HsType ; return (scopedSort spec_tkvs) } +-- zonkAndScopedSortFam is a version of zonkAndScopedSort that works does not check +-- the zonking result is still a TcTyVar +zonkAndScopedSortFam :: [TcTyVar] -> TcM [TcTyVar] +zonkAndScopedSortFam spec_tkvs + = do { spec_tkvs <- liftZonkM $ zonkTcTyVarsToTcTyVarsMaybe spec_tkvs + -- Zonk the kinds, to we can do the dependency analysis + + -- Do a stable topological sort, following + -- Note [Ordering of implicit variables] in GHC.Rename.HsType + ; return (scopedSort spec_tkvs) } + -- | Generalize some of the free variables in the given type. -- All such variables should be *kind* variables; any type variables -- should be explicitly quantified (with a `forall`) before now. ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -3298,7 +3298,7 @@ tcTyFamInstEqn fam_tc mb_clsinfo <- tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_bndrs hs_pats hs_rhs_ty -- Don't print results they may be knot-tied - -- (tcFamInstEqnGuts zonks to Type) + -- (tcTyFamInstEqnGuts zonks to Type) ; let ax = mkCoAxBranch qtvs [] [] pats rhs_ty (map (const Nominal) qtvs) @@ -3448,7 +3448,8 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty ; rhs_ty <- tcCheckLHsTypeInContext hs_rhs_ty (TheKind rhs_kind) ; return (lhs_ty, rhs_ty) } - ; outer_bndrs <- scopedSortOuter outer_bndrs + ; traceTc "tcTyFamInstEqnGuts 0" (ppr outer_bndrs $$ ppr skol_info) + ; outer_bndrs <- scopedSortOuterFam outer_bndrs ; let outer_tvs = outerTyVars outer_bndrs ; checkFamTelescope tclvl outer_hs_bndrs outer_tvs @@ -3461,9 +3462,9 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty -- check there too! -- See Note [Generalising in tcTyFamInstEqnGuts] - ; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty + ; dvs <- candidateQTyVarsOfType lhs_ty ; qtvs <- quantifyTyVars skol_info dvs - ; let final_tvs = scopedSort (qtvs ++ outer_tvs) + ; let final_tvs = scopedSort qtvs -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ; reportUnsolvedEqualities skol_info final_tvs tclvl wanted ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -964,7 +964,7 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity , lhs_applied_kind , res_kind ) } - ; outer_bndrs <- scopedSortOuter outer_bndrs + ; outer_bndrs <- scopedSortOuterFam outer_bndrs ; let outer_tvs = outerTyVars outer_bndrs ; checkFamTelescope tclvl hs_outer_bndrs outer_tvs @@ -975,14 +975,14 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity -- check there too! -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty + ; dvs <- candidateQTyVarsOfType lhs_ty ; qtvs <- quantifyTyVars skol_info dvs -- Have to make a same defaulting choice for reuslt kind here -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; let final_tvs = scopedSort (qtvs ++ outer_tvs) + ; let final_tvs = scopedSort qtvs -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ; reportUnsolvedEqualities skol_info final_tvs tclvl wanted ===================================== compiler/GHC/Tc/Zonk/TcType.hs ===================================== @@ -20,6 +20,7 @@ module GHC.Tc.Zonk.TcType , zonkTcTyVarToTcTyVar, zonkTcTyVarsToTcTyVars , zonkInvisTVBinder , zonkCo + , zonkTcTyVarsToTcTyVarsMaybe -- ** Zonking 'TyCon's , zonkTcTyCon @@ -83,7 +84,7 @@ import GHC.Core.Predicate import GHC.Utils.Constants import GHC.Utils.Outputable import GHC.Utils.Misc -import GHC.Utils.Monad ( mapAccumLM ) +import GHC.Utils.Monad ( mapAccumLM, mapMaybeM ) import GHC.Utils.Panic import GHC.Data.Bag @@ -269,6 +270,9 @@ zonkTcTyVar tv zonkTcTyVarsToTcTyVars :: HasDebugCallStack => [TcTyVar] -> ZonkM [TcTyVar] zonkTcTyVarsToTcTyVars = mapM zonkTcTyVarToTcTyVar +zonkTcTyVarsToTcTyVarsMaybe :: HasDebugCallStack => [TcTyVar] -> ZonkM [TcTyVar] +zonkTcTyVarsToTcTyVarsMaybe = mapMaybeM (fmap getTyVar_maybe . zonkTcTyVar) + zonkTcTyVarToTcTyVar :: HasDebugCallStack => TcTyVar -> ZonkM TcTyVar zonkTcTyVarToTcTyVar tv = do { ty <- zonkTcTyVar tv ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -382,6 +382,8 @@ data HsOuterTyVarBndrs flag pass -- @f :: forall a b. a -> b -> b@ { hso_xexplicit :: XHsOuterExplicit pass flag , hso_bndrs :: [LHsTyVarBndr flag (NoGhcTc pass)] + , hso_ximplicit :: XHsOuterImplicit pass + -- used only for Type family instances } | XHsOuterTyVarBndrs !(XXHsOuterTyVarBndrs pass) ===================================== testsuite/tests/typecheck/should_compile/T25647d.hs ===================================== @@ -0,0 +1,28 @@ +{-# LANGUAGE DataKinds, TypeFamilies, PolyKinds, MagicHash #-} + +module T25647d where + +import GHC.Exts +import Data.Kind +import GHC.Exts (RuntimeRep) +import Data.Type.Equality ((:~:)(Refl) ) + +type Cast0 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type +type family Cast0 r s a b c d p where + Cast0 _ c _ _ Refl Refl (p->q) = Int + +type Cast1 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type +type family Cast1 r s a b c d p where + Cast1 _ c _ b Refl Refl (p->q) = Int + +type Cast2 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type +type family Cast2 r s a b c d p where + Cast2 _ c _ b Refl Refl (p->q) = Int + +type Cast3 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type +type family Cast3 r s a b c d p where + forall. Cast3 _ c _ b Refl Refl (p->q) = Int + +type Cast4 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type +type family Cast4 r s a b c d p where + forall aa cc. Cast4 aa cc _ b Refl Refl (p->q) = Int ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -937,5 +937,6 @@ test('T25597', normal, compile, ['']) test('T25647a', normal, compile, ['']) test('T25647b', normal, compile, ['']) test('T25647c', normal, compile, ['']) +test('T25647d', normal, compile, ['']) test('T25647_fail', normal, compile_fail, ['']) test('T25725', normal, compile, ['']) ===================================== utils/haddock/haddock-api/src/Haddock/GhcUtils.hs ===================================== @@ -483,8 +483,8 @@ reparenOuterTyVarBndrs => HsOuterTyVarBndrs flag a -> HsOuterTyVarBndrs flag a reparenOuterTyVarBndrs imp at HsOuterImplicit{} = imp -reparenOuterTyVarBndrs (HsOuterExplicit x exp_bndrs) = - HsOuterExplicit x (map (mapXRec @(NoGhcTc a) reparenTyVar) exp_bndrs) +reparenOuterTyVarBndrs (HsOuterExplicit x exp_bndrs imp_bndrs) = + HsOuterExplicit x (map (mapXRec @(NoGhcTc a) reparenTyVar) exp_bndrs) imp_bndrs reparenOuterTyVarBndrs v at XHsOuterTyVarBndrs{} = v -- | Add parentheses around the types in an 'HsForAllTelescope' (see 'reparenTypePrec') ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs ===================================== @@ -939,8 +939,8 @@ renameOuterTyVarBndrs -> RnM (HsOuterTyVarBndrs flag DocNameI) renameOuterTyVarBndrs (HsOuterImplicit{}) = pure $ HsOuterImplicit{hso_ximplicit = noExtField} -renameOuterTyVarBndrs (HsOuterExplicit{hso_bndrs = exp_bndrs}) = - HsOuterExplicit noExtField <$> mapM (renameLTyVarBndr return) exp_bndrs +renameOuterTyVarBndrs (HsOuterExplicit{hso_bndrs = exp_bndrs}) = do + HsOuterExplicit noExtField <$> mapM (renameLTyVarBndr return) exp_bndrs <*> pure NoExtField renameWc :: (in_thing -> RnM out_thing) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ebed7dcec5f0b07ef821d694dc251fd37d64e3a2...653aa8da0bc5d42018f2f68e57b72460f0b9a907 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ebed7dcec5f0b07ef821d694dc251fd37d64e3a2...653aa8da0bc5d42018f2f68e57b72460f0b9a907 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/cdd23dde/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 16:42:37 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 08 Mar 2025 11:42:37 -0500 Subject: [Git][ghc/ghc][wip/T25647] Remove unused implicit variable bindings from HsOuterExplicit in addHsOuterSigTyVarBinds function Message-ID: <67cc737dae514_2b6a5ad393987251b@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 3cc1c261 by Patrick at 2025-03-09T00:42:28+08:00 Remove unused implicit variable bindings from HsOuterExplicit in addHsOuterSigTyVarBinds function - - - - - 1 changed file: - compiler/GHC/HsToCore/Quote.hs Changes: ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -1224,7 +1224,7 @@ addHsOuterSigTyVarBinds outer_bndrs thing_inside = case outer_bndrs of HsOuterImplicit{hso_ximplicit = imp_tvs} -> do th_nil <- coreListM tyVarBndrSpecTyConName [] addSimpleTyVarBinds FreshNamesOnly imp_tvs $ thing_inside th_nil - HsOuterExplicit{hso_bndrs = exp_bndrs, hso_ximplicit= imp_tvs} -> + HsOuterExplicit{hso_bndrs = exp_bndrs} -> addHsTyVarBinds FreshNamesOnly exp_bndrs thing_inside -- | If a type implicitly quantifies its outermost type variables, return View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3cc1c261559eb59203e049688a8350be87883a50 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3cc1c261559eb59203e049688a8350be87883a50 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/b4496958/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 8 17:45:34 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 08 Mar 2025 12:45:34 -0500 Subject: [Git][ghc/ghc][wip/T25647] Add forall quantifiers to MultMul type family for clarity Message-ID: <67cc823e9bafd_2b6a5a15f016c87466@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 0ee138ae by Patrick at 2025-03-09T01:45:20+08:00 Add forall quantifiers to MultMul type family for clarity - - - - - 1 changed file: - libraries/ghc-internal/src/GHC/Internal/Types.hs Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Types.hs ===================================== @@ -261,10 +261,10 @@ type ZeroBitType = TYPE ZeroBitRep data Multiplicity = Many | One type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity where - MultMul 'One x = x - MultMul x 'One = x - MultMul 'Many x = 'Many - MultMul x 'Many = 'Many + forall x. MultMul 'One x = x + forall x. MultMul x 'One = x + forall x. MultMul 'Many x = 'Many + forall x. MultMul x 'Many = 'Many {- ********************************************************************* * * View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0ee138aeddc7423808660c19134a28ad9aa647d4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0ee138aeddc7423808660c19134a28ad9aa647d4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/e2a3c2d9/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 21:32:56 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 16:32:56 -0500 Subject: [Git][ghc/ghc][master] Allow defaulting of representational equalities Message-ID: <67ccb788c7944_31b9aab6ff6c19617@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - 14 changed files: - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - docs/users_guide/9.14.1-notes.rst - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr Changes: ===================================== compiler/GHC/Tc/Solver/Default.hs ===================================== @@ -1,3 +1,5 @@ +{-# LANGUAGE MultiWayIf #-} + module GHC.Tc.Solver.Default( tryDefaulting, tryUnsatisfiableGivens, isInteractiveClass, isNumClass @@ -26,7 +28,7 @@ import GHC.Core.Reduction( Reduction, reductionCoercion ) import GHC.Core import GHC.Core.DataCon import GHC.Core.Make -import GHC.Core.Coercion( mkNomReflCo, isReflCo ) +import GHC.Core.Coercion( isReflCo, mkReflCo, mkSubCo ) import GHC.Core.Unify ( tcMatchTyKis ) import GHC.Core.Predicate import GHC.Core.Type @@ -362,9 +364,9 @@ tryConstraintDefaulting wc where go_wc :: WantedConstraints -> TcS WantedConstraints go_wc wc@(WC { wc_simple = simples, wc_impl = implics }) - = do { mb_simples <- mapMaybeBagM go_simple simples + = do { simples' <- mapMaybeBagM go_simple simples ; mb_implics <- mapMaybeBagM go_implic implics - ; return (wc { wc_simple = mb_simples, wc_impl = mb_implics }) } + ; return (wc { wc_simple = simples', wc_impl = mb_implics }) } go_simple :: Ct -> TcS (Maybe Ct) go_simple ct = do { solved <- tryCtDefaultingStrategy ct @@ -403,7 +405,7 @@ defaultExceptionContext ct ; let ev = ctEvidence ct ev_tm = mkEvCast (Var empty_ec_id) (wrapIP (ctEvPred ev)) ; setEvBindIfWanted ev EvCanonical ev_tm - -- EvCanonical: see Note [CallStack and ExecptionContext hack] + -- EvCanonical: see Note [CallStack and ExceptionContext hack] -- in GHC.Tc.Solver.Dict ; return True } | otherwise @@ -423,19 +425,54 @@ defaultCallStack ct defaultEquality :: CtDefaultingStrategy -- See Note [Defaulting equalities] defaultEquality ct - | EqPred NomEq ty1 ty2 <- classifyPredType (ctPred ct) + | EqPred eq_rel ty1 ty2 <- classifyPredType (ctPred ct) = do { -- Remember: `ct` may not be zonked; -- see (DE3) in Note [Defaulting equalities] z_ty1 <- TcS.zonkTcType ty1 ; z_ty2 <- TcS.zonkTcType ty2 - + ; case eq_rel of + { NomEq -> -- Now see if either LHS or RHS is a bare type variable -- You might think the type variable will only be on the LHS -- but with a type function we might get F t1 ~ alpha - ; case (getTyVar_maybe z_ty1, getTyVar_maybe z_ty2) of + case (getTyVar_maybe z_ty1, getTyVar_maybe z_ty2) of (Just z_tv1, _) -> try_default_tv z_tv1 z_ty2 (_, Just z_tv2) -> try_default_tv z_tv2 z_ty1 - _ -> return False } + _ -> return False ; + + ; ReprEq + -- See Note [Defaulting representational equalities] + | CIrredCan (IrredCt { ir_reason }) <- ct + , isInsolubleReason ir_reason + -- Don't do this for definitely insoluble representational + -- equalities such as Int ~R# Bool. + -> return False + | otherwise + -> + do { traceTcS "defaultEquality ReprEq {" $ vcat + [ text "ct:" <+> ppr ct + , text "z_ty1:" <+> ppr z_ty1 + , text "z_ty2:" <+> ppr z_ty2 + ] + -- Promote this representational equality to a nominal equality. + -- + -- This handles cases such as @IO alpha[tau] ~R# IO Int@ + -- by defaulting @alpha := Int@, which is useful in practice + -- (see Note [Defaulting representational equalities]). + ; (co, new_eqs, _unifs, _rw) <- + wrapUnifierX (ctEvidence ct) Nominal $ + -- NB: nominal equality! + \ uenv -> uType uenv z_ty1 z_ty2 + -- Only accept this solution if no new equalities are produced + -- by the unifier. + -- + -- See Note [Defaulting representational equalities]. + ; if null new_eqs + then do { setEvBindIfWanted (ctEvidence ct) EvCanonical $ + (evCoercion $ mkSubCo co) + ; return True } + else return False + } } } | otherwise = return False @@ -477,8 +514,10 @@ defaultEquality ct ; unifyTyVar lhs_tv rhs_ty -- NB: unifyTyVar adds to the -- TcS unification counter ; setEvBindIfWanted (ctEvidence ct) EvCanonical $ - evCoercion (mkNomReflCo rhs_ty) - ; return True } + evCoercion (mkReflCo Nominal rhs_ty) + ; return True + } + combineStrategies :: CtDefaultingStrategy -> CtDefaultingStrategy -> CtDefaultingStrategy combineStrategies default1 default2 ct @@ -518,29 +557,42 @@ too drastic. Note [Defaulting equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +In top-level defaulting (as per Note [Top-level Defaulting Plan]), it makes +sense to try to default equality constraints, in addition to e.g. typeclass +defaulting: this doesn't threaten principal types (see DE1 below), but +allows GHC to accept strictly more programs. + +This Note explains defaulting nominal equalities; see also +Note [Defaulting representational equalities] which describes +the defaulting of representational equalities. + Consider + f :: forall a. (forall t. (F t ~ Int) => a -> Int) -> Int g :: Int g = f id We'll typecheck + id :: forall t. (F t ~ Int) => alpha[1] -> Int + where the `alpha[1]` comes from instantiating `f`. So we'll end up with the implication constraint + forall[2] t. (F t ~ Int) => alpha[1] ~ Int -And that can't be solved because `alpha` is untouchable under the + +and that can't be solved because `alpha` is untouchable under the equality (F t ~ Int). This is tiresome, and gave rise to user complaints: #25125 and #25029. Moreover, in this case there is no good reason not to unify alpha:=Int. Doing so solves the constraint, and since `alpha` is not otherwise -constrained, it does no harm. So the new plan is this: +constrained, it does no harm. - * For the Wanted constraint - [W] alpha ~ ty - if the only reason for not unifying is untouchability, then during - top-level defaulting, go ahead and unify +In conclusion, for a Wanted equality constraint [W] lhs ~ rhs, if the only +reason for not unifying is that either lhs or rhs is an untouchable metavariable +then, in top-level defaulting, go ahead and unify. In top-level defaulting, we already do several other somewhat-ad-hoc, but terribly convenient, unifications. This is just one more. @@ -555,12 +607,11 @@ Wrinkles: f x = case x of T1 -> True Should we infer f :: T a -> Bool, or f :: T a -> a. Both are valid, but - neither is more general than the other + neither is more general than the other. (DE2) We still can't unify if there is a skolem-escape check, or an occurs check, or it it'd mean unifying a TyVarTv with a non-tyvar. It's only the - "untouchability test" that we lift. We can lift it by saying that the innermost - given equality is at top level. + "untouchability test" that we lift. (DE3) The contraint we are looking at may not be fully zonked; for example, an earlier defaulting might have affected it. So we zonk-on-the fly in @@ -568,7 +619,7 @@ Wrinkles: (DE4) Promotion. Suppose we see alpha[2] := Maybe beta[4]. We want to promote beta[4] to level 2 and unify alpha[2] := Maybe beta'[2]. This is done by - checkTyEqRhs. + checkTyEqRhs called in defaultEquality. (DE5) Promotion. Suppose we see alpha[2] := F beta[4], where F is a type family. Then we still want to promote beta to beta'[2], and unify. This is @@ -587,6 +638,64 @@ Then when we default 'a' we can solve the constraint. And we want to do that before starting in on type classes. We MUST do it before reporting errors, because it isn't an error! #7967 was due to this. +Note [Defaulting representational equalities] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we end up with [W] alpha ~#R Int, with no other constraints on alpha. +Then it makes sense to simply unify alpha := Int -- the alternative is to +reject the program due to an ambiguous metavariable alpha, so it makes sense +to unify and accept instead. + +This is particularly convenient for users of `coerce`, as it lessens the +amount of type annotations required (see #21003). Consider for example: + + -- 'foldMap' defined using 'traverse' + foldMapUsingTraverse :: forall t m a. (Traversable t, Monoid m) => (a -> m) -> t a -> m + foldMapUsingTraverse = coerce $ traverse @t @(Const m) + + -- 'traverse_' defined using 'foldMap' + traverse_UsingFoldMap :: forall f t a. (Foldable t, Applicative f) => (a -> f ()) -> t a -> f () + traverse_UsingFoldMap = coerce $ foldMap @t @(Ap f ()) + +Typechecking these functions results in unsolved Wanted constraints of the form +[W] alpha[tau] ~R# some_ty; accepting such programs by unifying +alpha := some_ty avoids the need for users to specify tiresome additional +type annotations, such as: + + foldMapUsingTraverse = coerce $ traverse @t @(Const m) @a + traverse_UsingFoldMap = coerce $ foldMap @t @(Ap f ()) @a + +Consider also the following example: + + -- 'sequence_', but for two nested 'Foldable' structures + sequenceNested_ :: forall f1 f2. (Foldable f1, Foldable f2) => f1 (f2 (IO ())) -> IO () + sequenceNested_ = coerce $ sequence_ @( Compose f1 f2 ) + +Here, we end up with [W] mu[tau] beta[tau] ~#R IO (), and it similarly makes +sense to default mu := IO, beta := (). This avoids requiring the +user to provide additional type applications: + + sequenceNested_ = coerce $ sequence_ @( Compose f1 f2 ) @IO @() + +The plan for defaulting a representational equality, say [W] ty1 ~R# ty2, +is thus as follows: + + 1. attempt to unify ty1 ~# ty2 (at nominal role) + 2. a. if this succeeds without deferring any constraints, accept this solution + b. otherwise, keep the original constraint. + +(2b) ensures that we don't degrade all error messages by always turning unsolved +representational equalities into nominal ones; we only want to default a +representational equality when we can fully solve it. + +Note that this does not threaten principle types. Recall that the original worry +(as per Note [Do not unify representational equalities]) was that we might have + + [W] alpha ~R# Int + [W] alpha ~ Age + +in which case unifying alpha := Int would be wrong, as the correct solution is +alpha := Age. This worry doesn't concern us in top-level defaulting, because +defaulting takes place after generalisation; it is fully monomorphic. ********************************************************************************* * * ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -189,9 +189,9 @@ solveCallStack ev ev_cs = do { cs_tm <- evCallStack ev_cs ; let ev_tm = mkEvCast cs_tm (wrapIP (ctEvPred ev)) ; setEvBindIfWanted ev EvCanonical ev_tm } - -- EvCanonical: see Note [CallStack and ExecptionContext hack] + -- EvCanonical: see Note [CallStack and ExceptionContext hack] -{- Note [CallStack and ExecptionContext hack] +{- Note [CallStack and ExceptionContext hack] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ It isn't really right that we treat CallStack and ExceptionContext dictionaries as canonical, in the sense of Note [Coherence and specialisation: overview]. @@ -199,7 +199,7 @@ They definitely are not! But if we use EvNonCanonical here we get lots of nospec (error @Int) dict string -(since `error` takes a HasCallStack dict), and that isn't bottomng (at least not +(since `error` takes a HasCallStack dict), and that isn't bottoming (at least not without extra work) So, hackily, we just say that HasCallStack and ExceptionContext are canonical, even though they aren't really. ===================================== compiler/GHC/Tc/Solver/Equality.hs ===================================== @@ -2708,6 +2708,10 @@ and we want to get alpha := N b. See also #15144, which was caused by unifying a representational equality. +Note that it does however make sense to perform such unifications, as a last +resort, when doing top-level defaulting. +See Note [Defaulting representational equalities]. + Note [Solve by unification] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ If we solve ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -64,6 +64,8 @@ module GHC.Tc.Solver.Monad ( getTcEvTyCoVars, getTcEvBindsMap, setTcEvBindsMap, tcLookupClass, tcLookupId, tcLookupTyCon, + getUnifiedRef, + -- Inerts updInertSet, updInertCans, @@ -98,7 +100,7 @@ module GHC.Tc.Solver.Monad ( instDFunType, -- Unification - wrapUnifierTcS, unifyFunDeps, uPairsTcM, unifyForAllBody, + wrapUnifierX, wrapUnifierTcS, unifyFunDeps, uPairsTcM, unifyForAllBody, -- MetaTyVars newFlexiTcSTy, instFlexiX, ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -3110,7 +3110,7 @@ mapCheck f xs ----------------------------- -- | Options describing how to deal with a type equality --- in the pure unifier. See 'checkTyEqRhs' +-- in the eager unifier. See 'checkTyEqRhs' data TyEqFlags m a -- | LHS is a type family application; we are not unifying. = TEFTyFam ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Language * Multiline strings are now accepted in foreign imports. (#25157) +* GHC now does a better job at inferring types in calls to ``coerce``: instead of + complaining about ambiguous type variables, GHC will consider that such type + variables are determined by the ``Coercible`` constraints they appear in. + Compiler ~~~~~~~~ ===================================== testsuite/tests/default/default-fail08.hs ===================================== @@ -1,12 +1,16 @@ --- | Default for a partially applied Coercible constraint doesn't trigger panic +-- | Default for a partially applied constraint doesn't trigger panic {-# LANGUAGE Haskell2010, ConstraintKinds, MultiParamTypeClasses, NamedDefaults #-} -import Data.Coerce (Coercible, coerce) import Data.Functor.Identity (Identity (Identity)) -type CoercibleFromInt = Coercible Int +class C a b where + meth :: a -> b +instance C Int Integer where + meth = fromIntegral -default CoercibleFromInt (Identity Int) +type CInt = C Int -main = print (coerce (4 :: Int)) +default CInt (Integer) + +main = print (meth (4 :: Int)) ===================================== testsuite/tests/default/default-fail08.stderr ===================================== @@ -1,7 +1,23 @@ +default-fail08.hs:16:8: error: [GHC-39999] + • Ambiguous type variable ‘a0’ arising from a use of ‘print’ + prevents the constraint ‘(Show a0)’ from being solved. + Probable fix: use a type annotation to specify what ‘a0’ should be. + Potentially matching instances: + instance Show Ordering -- Defined in ‘GHC.Internal.Show’ + instance Show Integer -- Defined in ‘GHC.Internal.Show’ + ...plus 25 others + ...plus 15 instances involving out-of-scope types + (use -fprint-potential-instances to see them all) + • In the expression: print (meth (4 :: Int)) + In an equation for ‘main’: main = print (meth (4 :: Int)) + +default-fail08.hs:16:15: error: [GHC-39999] + • Ambiguous type variable ‘a0’ arising from a use of ‘meth’ + prevents the constraint ‘(C Int a0)’ from being solved. + Probable fix: use a type annotation to specify what ‘a0’ should be. + Potentially matching instance: + instance C Int Integer -- Defined at default-fail08.hs:9:10 + • In the first argument of ‘print’, namely ‘(meth (4 :: Int))’ + In the expression: print (meth (4 :: Int)) + In an equation for ‘main’: main = print (meth (4 :: Int)) -default-fail08.hs:12:15: [GHC-10283] - Couldn't match representation of type ‘a0’ with that of ‘Int’ - arising from a use of ‘coerce’ - In the first argument of ‘print’, namely ‘(coerce (4 :: Int))’ - In the expression: print (coerce (4 :: Int)) - In an equation for ‘main’: main = print (coerce (4 :: Int)) ===================================== testsuite/tests/rep-poly/T14561b.stderr ===================================== @@ -1,10 +1,10 @@ - T14561b.hs:12:9: error: [GHC-55287] • The first argument of ‘coerce’ does not have a fixed runtime representation. Its type is: - a0 :: TYPE k0 + b0 :: TYPE k0 Cannot unify ‘r’ with the type variable ‘k0’ because the former is not a concrete ‘RuntimeRep’. • In the expression: coerce In an equation for ‘badId’: badId = coerce + ===================================== testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr ===================================== @@ -1,10 +1,10 @@ - UnliftedNewtypesCoerceFail.hs:14:8: error: [GHC-55287] • The first argument of ‘coerce’ does not have a fixed runtime representation. Its type is: - a0 :: TYPE k0 + b0 :: TYPE k0 Cannot unify ‘rep’ with the type variable ‘k0’ because the former is not a concrete ‘RuntimeRep’. • In the expression: coerce In an equation for ‘goof’: goof = coerce + ===================================== testsuite/tests/typecheck/should_compile/T21003.hs ===================================== @@ -0,0 +1,35 @@ +{-# LANGUAGE TypeApplications #-} + +module T21003 where + +import Data.IntMap (IntMap, mapKeysMonotonic, Key) +import Data.Coerce (coerce) + +import Data.Functor.Compose (Compose(..)) +import Data.Functor.Const (Const(..)) +import Data.Foldable (sequence_) +import Data.Monoid (Ap(..)) + +-- Original example from #21003 +newtype MyMap = MyMap (IntMap Bool) +shouldWork :: (Key -> Key) -> MyMap -> MyMap +shouldWork = coerce mapKeysMonotonic + +-- Examples included in documentation + +-- 'foldMap' defined using 'traverse' +foldMapUsingTraverse :: forall t m a. (Traversable t, Monoid m) => (a -> m) -> t a -> m +foldMapUsingTraverse = coerce $ traverse @t @(Const m) + +-- 'traverse_' defined using 'foldMap' +traverse_UsingFoldMap :: forall f t a. (Foldable t, Applicative f) => (a -> f ()) -> t a -> f () +traverse_UsingFoldMap = coerce $ foldMap @t @(Ap f ()) + +-- 'sequence_', but for two nested 'Foldable' structures +sequenceNested_ :: forall f1 f2. (Foldable f1, Foldable f2) => f1 (f2 (IO ())) -> IO () +sequenceNested_ = coerce $ sequence_ @(Compose f1 f2) + +-- Minimisation of an example from the 'vulkan' library +newtype Size = Size Word +test :: Size -> (Int -> ()) -> () +test sz f = f (fromIntegral $ coerce sz) ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -913,6 +913,7 @@ test('T23918', normal, compile, ['']) test('T17564', normal, compile, ['']) test('T24146', normal, compile, ['']) test('T22788', normal, compile, ['']) +test('T21003', normal, compile, ['']) test('T21206', normal, compile, ['']) test('T17594a', req_th, compile, ['']) test('T17594f', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T10495.hs ===================================== @@ -1,5 +1,6 @@ module T10495 where -import Data.Coerce +class C a b where + meth :: a -> b -foo = coerce +foo = meth ===================================== testsuite/tests/typecheck/should_fail/T10495.stderr ===================================== @@ -1,8 +1,5 @@ +T10495.hs:6:7: error: [GHC-39999] + • No instance for ‘C a0 b0’ arising from a use of ‘meth’ + • In the expression: meth + In an equation for ‘foo’: foo = meth -T10495.hs:5:7: error: [GHC-10283] - • Couldn't match representation of type ‘a0’ with that of ‘b0’ - arising from a use of ‘coerce’ - • In the expression: coerce - In an equation for ‘foo’: foo = coerce - • Relevant bindings include - foo :: a0 -> b0 (bound at T10495.hs:5:1) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1e53277af36d3f0b6ad5491f70ffc5593a49dcfd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1e53277af36d3f0b6ad5491f70ffc5593a49dcfd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/f5b873b8/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 21:33:33 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 16:33:33 -0500 Subject: [Git][ghc/ghc][master] Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." Message-ID: <67ccb7ada7625_31b9aab9d9a822477@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 14 changed files: - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Unique/Supply.hs Changes: ===================================== compiler/GHC/Cmm/ThreadSanitizer.hs ===================================== @@ -145,7 +145,7 @@ mkUnsafeCall env ftgt formals args = -- arguments as Cmm-Lint checks this. To accomplish this we instead bind -- the arguments to local registers. arg_regs :: [CmmReg] - arg_regs = zipWith arg_reg (uniqListFromSupply arg_us) args + arg_regs = zipWith arg_reg (uniqsFromSupply arg_us) args where arg_reg :: Unique -> CmmExpr -> CmmReg arg_reg u expr = CmmLocal $ LocalReg u (cmmExprType (platform env) expr) @@ -169,7 +169,7 @@ saveRestoreCallerRegs us platform = nodes :: [(CmmNode O O, CmmNode O O)] nodes = - zipWith mk_reg regs_to_save (uniqListFromSupply us) + zipWith mk_reg regs_to_save (uniqsFromSupply us) where mk_reg :: GlobalReg -> Unique -> (CmmNode O O, CmmNode O O) mk_reg reg u = ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -1,6 +1,5 @@ {-# language GADTs, LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE LambdaCase #-} module GHC.CmmToAsm.AArch64.CodeGen ( cmmTopCodeGen , generateJumpTableForInstr @@ -51,9 +50,7 @@ import GHC.Types.Unique.DSM import GHC.Data.OrdList import GHC.Utils.Outputable -import Control.Monad ( join, mapAndUnzipM ) -import Data.List.NonEmpty ( NonEmpty (..), nonEmpty ) -import qualified Data.List.NonEmpty as NE +import Control.Monad ( mapAndUnzipM ) import GHC.Float import GHC.Types.Basic @@ -1590,7 +1587,7 @@ genCondJump bid expr = do _ -> pprPanic "AArch64.genCondJump: " (text $ show expr) -- A conditional jump with at least +/-128M jump range -genCondFarJump :: MonadGetUnique m => Cond -> Target -> m (NonEmpty Instr) +genCondFarJump :: MonadGetUnique m => Cond -> Target -> m InstrBlock genCondFarJump cond far_target = do skip_lbl_id <- newBlockId jmp_lbl_id <- newBlockId @@ -1600,13 +1597,11 @@ genCondFarJump cond far_target = do -- need to consider float orderings. -- So we take the hit of the additional jump in the false -- case for now. - pure - ( BCOND cond (TBlock jmp_lbl_id) :| - B (TBlock skip_lbl_id) : - NEWBLOCK jmp_lbl_id : - B far_target : - NEWBLOCK skip_lbl_id : - [] ) + return $ toOL [ BCOND cond (TBlock jmp_lbl_id) + , B (TBlock skip_lbl_id) + , NEWBLOCK jmp_lbl_id + , B far_target + , NEWBLOCK skip_lbl_id] genCondBranch :: BlockId -- the true branch target -> BlockId -- the false branch target @@ -2462,49 +2457,48 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks = -- Replace out of range conditional jumps with unconditional jumps. replace_blk :: LabelMap Int -> Int -> GenBasicBlock Instr -> UniqDSM (Int, [GenBasicBlock Instr]) - replace_blk !m !pos (BasicBlock lbl instrs) = case nonEmpty instrs of - Nothing -> pure (0, []) - Just instrs -> do - -- Account for a potential info table before the label. - let !block_pos = pos + infoTblSize_maybe lbl - (!pos', instrs') <- mapAccumLM (replace_jump m) block_pos instrs - let instrs'' = join instrs' - -- We might have introduced new labels, so split the instructions into basic blocks again if neccesary. - let (top, split_blocks, no_data) = foldr mkBlocks ([],[],[]) instrs'' - -- There should be no data in the instruction stream at this point - massert (null no_data) - - let final_blocks = BasicBlock lbl top : split_blocks - pure (pos', final_blocks) - - replace_jump :: LabelMap Int -> Int -> Instr -> UniqDSM (Int, NonEmpty Instr) + replace_blk !m !pos (BasicBlock lbl instrs) = do + -- Account for a potential info table before the label. + let !block_pos = pos + infoTblSize_maybe lbl + (!pos', instrs') <- mapAccumLM (replace_jump m) block_pos instrs + let instrs'' = concat instrs' + -- We might have introduced new labels, so split the instructions into basic blocks again if neccesary. + let (top, split_blocks, no_data) = foldr mkBlocks ([],[],[]) instrs'' + -- There should be no data in the instruction stream at this point + massert (null no_data) + + let final_blocks = BasicBlock lbl top : split_blocks + pure (pos', final_blocks) + + replace_jump :: LabelMap Int -> Int -> Instr -> UniqDSM (Int, [Instr]) replace_jump !m !pos instr = do case instr of ANN ann instr -> do - replace_jump m pos instr >>= \ - (idx,instr':|instrs') -> - pure (idx, ANN ann instr':|instrs') + replace_jump m pos instr >>= \case + (idx,instr':instrs') -> + pure (idx, ANN ann instr':instrs') + (idx,[]) -> pprPanic "replace_jump" (text "empty return list for " <+> ppr idx) BCOND cond t -> case target_in_range m t pos of - InRange -> pure (pos+long_bc_jump_size, NE.singleton instr) + InRange -> pure (pos+long_bc_jump_size,[instr]) NotInRange far_target -> do jmp_code <- genCondFarJump cond far_target - pure (pos+long_bc_jump_size, jmp_code) + pure (pos+long_bc_jump_size, fromOL jmp_code) CBZ op t -> long_zero_jump op t EQ CBNZ op t -> long_zero_jump op t NE instr - | isMetaInstr instr -> pure (pos, NE.singleton instr) - | otherwise -> pure (pos+1, NE.singleton instr) + | isMetaInstr instr -> pure (pos,[instr]) + | otherwise -> pure (pos+1, [instr]) where -- cmp_op: EQ = CBZ, NEQ = CBNZ long_zero_jump op t cmp_op = case target_in_range m t pos of - InRange -> pure (pos+long_bz_jump_size, NE.singleton instr) + InRange -> pure (pos+long_bz_jump_size,[instr]) NotInRange far_target -> do jmp_code <- genCondFarJump cmp_op far_target -- TODO: Fix zero reg so we can use it here - pure (pos + long_bz_jump_size, CMP op (OpImm (ImmInt 0)) NE.<| jmp_code) + pure (pos + long_bz_jump_size, CMP op (OpImm (ImmInt 0)) : fromOL jmp_code) target_in_range :: LabelMap Int -> Target -> Int -> BlockInRange ===================================== compiler/GHC/Core/Opt/SetLevels.hs ===================================== @@ -1,5 +1,7 @@ {-# LANGUAGE PatternSynonyms #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + {- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 @@ -118,16 +120,12 @@ import GHC.Builtin.Types import GHC.Builtin.Names ( runRWKey ) import GHC.Data.FastString -import GHC.Data.Pair ( Pair (..) ) import GHC.Utils.FV import GHC.Utils.Misc import GHC.Utils.Outputable import GHC.Utils.Panic -import Data.Foldable ( toList ) -import Data.Functor.Identity ( Identity (..) ) -import Data.List.NonEmpty ( NonEmpty (..) ) import Data.Maybe {- @@ -453,14 +451,14 @@ lvlCase env scrut_fvs scrut' case_bndr ty alts , ManyTy <- idMult case_bndr -- See Note [Floating linear case] = -- Always float the case if possible -- Unlike lets we don't insist that it escapes a value lambda - do { (env1, case_bndr' :| bs') <- cloneCaseBndrs env dest_lvl (case_bndr :| bs) + do { (env1, (case_bndr' : bs')) <- cloneCaseBndrs env dest_lvl (case_bndr : bs) ; let rhs_env = extendCaseBndrEnv env1 case_bndr scrut' ; body' <- lvlMFE rhs_env True body ; let alt' = Alt con (map (stayPut dest_lvl) bs') body' ; return (Case scrut' (TB case_bndr' (FloatMe dest_lvl)) ty' [alt']) } | otherwise -- Stays put - = do { let (alts_env1, Identity case_bndr') = substAndLvlBndrs NonRecursive env incd_lvl (Identity case_bndr) + = do { let (alts_env1, [case_bndr']) = substAndLvlBndrs NonRecursive env incd_lvl [case_bndr] alts_env = extendCaseBndrEnv alts_env1 case_bndr scrut' ; alts' <- mapM (lvl_alt alts_env) alts ; return (Case scrut' case_bndr' ty' alts') } @@ -651,7 +649,7 @@ lvlMFE env strict_ctxt ann_expr -- See Note [Test cheapness with exprOkForSpeculation] , BI_Box { bi_data_con = box_dc, bi_inst_con = boxing_expr , bi_boxed_type = box_ty } <- boxingDataCon expr_ty - , let Pair bx_bndr ubx_bndr = mkTemplateLocals (Pair box_ty expr_ty) + , let [bx_bndr, ubx_bndr] = mkTemplateLocals [box_ty, expr_ty] = do { expr1 <- lvlExpr rhs_env ann_expr ; let l1r = incMinorLvlFrom rhs_env float_rhs = mkLams abs_vars_w_lvls $ @@ -1229,7 +1227,7 @@ lvlBind env (AnnNonRec bndr rhs) = -- No float do { rhs' <- lvlRhs env NonRecursive is_bot_lam mb_join_arity rhs ; let bind_lvl = incMinorLvl (le_ctxt_lvl env) - (env', Identity bndr') = substAndLvlBndrs NonRecursive env bind_lvl (Identity bndr) + (env', [bndr']) = substAndLvlBndrs NonRecursive env bind_lvl [bndr] ; return (NonRec bndr' rhs', env') } -- Otherwise we are going to float @@ -1237,7 +1235,7 @@ lvlBind env (AnnNonRec bndr rhs) = do { -- No type abstraction; clone existing binder rhs' <- lvlFloatRhs [] dest_lvl env NonRecursive is_bot_lam NotJoinPoint rhs - ; (env', Identity bndr') <- cloneLetVars NonRecursive env dest_lvl (Identity bndr) + ; (env', [bndr']) <- cloneLetVars NonRecursive env dest_lvl [bndr] ; let bndr2 = annotateBotStr bndr' 0 mb_bot_str ; return (NonRec (TB bndr2 (FloatMe dest_lvl)) rhs', env') } @@ -1245,7 +1243,7 @@ lvlBind env (AnnNonRec bndr rhs) = do { -- Yes, type abstraction; create a new binder, extend substitution, etc rhs' <- lvlFloatRhs abs_vars dest_lvl env NonRecursive is_bot_lam NotJoinPoint rhs - ; (env', Identity bndr') <- newPolyBndrs dest_lvl env abs_vars (Identity bndr) + ; (env', [bndr']) <- newPolyBndrs dest_lvl env abs_vars [bndr] ; let bndr2 = annotateBotStr bndr' n_extra mb_bot_str ; return (NonRec (TB bndr2 (FloatMe dest_lvl)) rhs', env') } @@ -1303,13 +1301,13 @@ lvlBind env (AnnRec pairs) let (rhs_env, abs_vars_w_lvls) = lvlLamBndrs env dest_lvl abs_vars rhs_lvl = le_ctxt_lvl rhs_env - (rhs_env', Identity new_bndr) <- cloneLetVars Recursive rhs_env rhs_lvl (Identity bndr) + (rhs_env', [new_bndr]) <- cloneLetVars Recursive rhs_env rhs_lvl [bndr] let (lam_bndrs, rhs_body) = collectAnnBndrs rhs (body_env1, lam_bndrs1) = substBndrsSL NonRecursive rhs_env' lam_bndrs (body_env2, lam_bndrs2) = lvlLamBndrs body_env1 rhs_lvl lam_bndrs1 new_rhs_body <- lvlRhs body_env2 Recursive is_bot NotJoinPoint rhs_body - (poly_env, Identity poly_bndr) <- newPolyBndrs dest_lvl env abs_vars (Identity bndr) + (poly_env, [poly_bndr]) <- newPolyBndrs dest_lvl env abs_vars [bndr] return (Rec [(TB poly_bndr (FloatMe dest_lvl) , mkLams abs_vars_w_lvls $ mkLams lam_bndrs2 $ @@ -1481,26 +1479,24 @@ Use lvlExpr otherwise. A little subtle, and I got it wrong at least twice ************************************************************************ -} -substAndLvlBndrs :: Traversable f => RecFlag -> LevelEnv -> Level -> f InVar -> (LevelEnv, f LevelledBndr) +substAndLvlBndrs :: RecFlag -> LevelEnv -> Level -> [InVar] -> (LevelEnv, [LevelledBndr]) substAndLvlBndrs is_rec env lvl bndrs = lvlBndrs subst_env lvl subst_bndrs where (subst_env, subst_bndrs) = substBndrsSL is_rec env bndrs -{-# INLINE substAndLvlBndrs #-} -substBndrsSL :: Traversable f => RecFlag -> LevelEnv -> f InVar -> (LevelEnv, f OutVar) +substBndrsSL :: RecFlag -> LevelEnv -> [InVar] -> (LevelEnv, [OutVar]) -- So named only to avoid the name clash with GHC.Core.Subst.substBndrs substBndrsSL is_rec env@(LE { le_subst = subst, le_env = id_env }) bndrs = ( env { le_subst = subst' - , le_env = foldl' add_id id_env (toList bndrs `zip` toList bndrs') } + , le_env = foldl' add_id id_env (bndrs `zip` bndrs') } , bndrs') where (subst', bndrs') = case is_rec of NonRecursive -> substBndrs subst bndrs Recursive -> substRecBndrs subst bndrs -{-# INLINE substBndrsSL #-} -lvlLamBndrs :: Traversable f => LevelEnv -> Level -> f OutVar -> (LevelEnv, f LevelledBndr) +lvlLamBndrs :: LevelEnv -> Level -> [OutVar] -> (LevelEnv, [LevelledBndr]) -- Compute the levels for the binders of a lambda group lvlLamBndrs env lvl bndrs = lvlBndrs env new_lvl bndrs @@ -1514,18 +1510,17 @@ lvlLamBndrs env lvl bndrs -- true of a type variable -- there is no point in floating -- out of a big lambda. -- See Note [Computing one-shot info] in GHC.Types.Demand -{-# INLINE lvlLamBndrs #-} -lvlJoinBndrs :: Traversable f => LevelEnv -> Level -> RecFlag -> f OutVar - -> (LevelEnv, f LevelledBndr) -lvlJoinBndrs env lvl rec = lvlBndrs env new_lvl +lvlJoinBndrs :: LevelEnv -> Level -> RecFlag -> [OutVar] + -> (LevelEnv, [LevelledBndr]) +lvlJoinBndrs env lvl rec bndrs + = lvlBndrs env new_lvl bndrs where new_lvl | isRec rec = incMajorLvl lvl | otherwise = incMinorLvl lvl -- Non-recursive join points are one-shot; recursive ones are not -{-# INLINE lvlJoinBndrs #-} -lvlBndrs :: Traversable f => LevelEnv -> Level -> f CoreBndr -> (LevelEnv, f LevelledBndr) +lvlBndrs :: LevelEnv -> Level -> [CoreBndr] -> (LevelEnv, [LevelledBndr]) -- The binders returned are exactly the same as the ones passed, -- apart from applying the substitution, but they are now paired -- with a (StayPut level) @@ -1538,8 +1533,7 @@ lvlBndrs :: Traversable f => LevelEnv -> Level -> f CoreBndr -> (LevelEnv, f Lev lvlBndrs env@(LE { le_lvl_env = lvl_env }) new_lvl bndrs = ( env { le_ctxt_lvl = new_lvl , le_lvl_env = addLvls new_lvl lvl_env bndrs } - , fmap (stayPut new_lvl) bndrs) -{-# INLINE lvlBndrs #-} + , map (stayPut new_lvl) bndrs) stayPut :: Level -> OutVar -> LevelledBndr stayPut new_lvl bndr = TB bndr (StayPut new_lvl) @@ -1699,8 +1693,8 @@ initialEnv float_lams binds addLvl :: Level -> VarEnv Level -> OutVar -> VarEnv Level addLvl dest_lvl env v' = extendVarEnv env v' dest_lvl -addLvls :: Foldable f => Level -> VarEnv Level -> f OutVar -> VarEnv Level -addLvls = foldl' . addLvl +addLvls :: Level -> VarEnv Level -> [OutVar] -> VarEnv Level +addLvls dest_lvl env vs = foldl' (addLvl dest_lvl) env vs floatLams :: LevelEnv -> Maybe Int floatLams le = floatOutLambdas (le_switches le) @@ -1798,15 +1792,17 @@ type LvlM result = UniqSM result initLvl :: UniqSupply -> UniqSM a -> a initLvl = initUs_ -newPolyBndrs :: (MonadUnique m, Traversable t) => Level -> LevelEnv -> [OutVar] -> t InId -> m (LevelEnv, t OutId) +newPolyBndrs :: Level -> LevelEnv -> [OutVar] -> [InId] + -> LvlM (LevelEnv, [OutId]) -- The envt is extended to bind the new bndrs to dest_lvl, but -- the le_ctxt_lvl is unaffected newPolyBndrs dest_lvl env@(LE { le_lvl_env = lvl_env, le_subst = subst, le_env = id_env }) abs_vars bndrs = assert (all (not . isCoVar) bndrs) $ -- What would we add to the CoSubst in this case. No easy answer. - do { bndr_prs <- withUniquesM (\ uniq bndr -> (bndr, mk_poly_bndr bndr uniq)) bndrs - ; let new_bndrs = fmap snd bndr_prs + do { uniqs <- getUniquesM + ; let new_bndrs = zipWith mk_poly_bndr bndrs uniqs + bndr_prs = bndrs `zip` new_bndrs env' = env { le_lvl_env = addLvls dest_lvl lvl_env new_bndrs , le_subst = foldl' add_subst subst bndr_prs , le_env = foldl' add_id id_env bndr_prs } @@ -1832,10 +1828,6 @@ newPolyBndrs dest_lvl = new_bndr `asJoinId` join_arity + length abs_vars | otherwise = new_bndr -{-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> [InId] -> m (LevelEnv, [OutId]) #-} -{-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> Identity InId -> m (LevelEnv, Identity OutId) #-} -{-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> NonEmpty InId -> m (LevelEnv, NonEmpty OutId) #-} -{-# SPECIALIZE newPolyBndrs :: (MonadUnique m) => Level -> LevelEnv -> [OutVar] -> Pair InId -> m (LevelEnv, Pair OutId) #-} newLvlVar :: LevelledExpr -- The RHS of the new binding -> JoinPointHood -- Its join arity, if it is a join point @@ -1859,7 +1851,7 @@ newLvlVar lvld_rhs join_arity_maybe is_mk_static = mkSysLocal (mkFastString "lvl") uniq ManyTy rhs_ty -- | Clone the binders bound by a single-alternative case. -cloneCaseBndrs :: Traversable t => LevelEnv -> Level -> t Var -> LvlM (LevelEnv, t Var) +cloneCaseBndrs :: LevelEnv -> Level -> [Var] -> LvlM (LevelEnv, [Var]) cloneCaseBndrs env@(LE { le_subst = subst, le_lvl_env = lvl_env, le_env = id_env }) new_lvl vs = do { (subst', vs') <- cloneBndrsM subst vs @@ -1868,11 +1860,12 @@ cloneCaseBndrs env@(LE { le_subst = subst, le_lvl_env = lvl_env, le_env = id_env -- See Note [Setting levels when floating single-alternative cases]. ; let env' = env { le_lvl_env = addLvls new_lvl lvl_env vs' , le_subst = subst' - , le_env = foldl' add_id id_env (toList vs `zip` toList vs') } + , le_env = foldl' add_id id_env (vs `zip` vs') } + ; return (env', vs') } -cloneLetVars - :: Traversable t => RecFlag -> LevelEnv -> Level -> t InVar -> LvlM (LevelEnv, t OutVar) +cloneLetVars :: RecFlag -> LevelEnv -> Level -> [InVar] + -> LvlM (LevelEnv, [OutVar]) -- See Note [Need for cloning during float-out] -- Works for Ids bound by let(rec) -- The dest_lvl is attributed to the binders in the new env, @@ -1880,12 +1873,12 @@ cloneLetVars cloneLetVars is_rec env@(LE { le_subst = subst, le_lvl_env = lvl_env, le_env = id_env }) dest_lvl vs - = do { let vs1 = fmap zap vs + = do { let vs1 = map zap vs ; (subst', vs2) <- case is_rec of NonRecursive -> cloneBndrsM subst vs1 Recursive -> cloneRecIdBndrsM subst vs1 - ; let prs = toList vs `zip` toList vs2 + ; let prs = vs `zip` vs2 env' = env { le_lvl_env = addLvls dest_lvl lvl_env vs2 , le_subst = subst' , le_env = foldl' add_id id_env prs } @@ -1901,10 +1894,6 @@ cloneLetVars is_rec -- See Note [Zapping JoinId when floating] zap_join | isTopLvl dest_lvl = zapJoinId | otherwise = id -{-# SPECIALIZE cloneLetVars :: RecFlag -> LevelEnv -> Level -> [InVar] -> LvlM (LevelEnv, [OutVar]) #-} -{-# SPECIALIZE cloneLetVars :: RecFlag -> LevelEnv -> Level -> Identity InVar -> LvlM (LevelEnv, Identity OutVar) #-} -{-# SPECIALIZE cloneLetVars :: RecFlag -> LevelEnv -> Level -> NonEmpty InVar -> LvlM (LevelEnv, NonEmpty OutVar) #-} -{-# SPECIALIZE cloneLetVars :: RecFlag -> LevelEnv -> Level -> Pair InVar -> LvlM (LevelEnv, Pair OutVar) #-} add_id :: IdEnv ([Var], LevelledExpr) -> (Var, Var) -> IdEnv ([Var], LevelledExpr) add_id id_env (v, v1) ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -2414,7 +2414,7 @@ prepareAlts :: OutExpr -> InId -> [InAlt] -> SimplM ([AltCon], [InAlt]) -- Note that case_bndr is an InId; see Note [Shadowing in prepareAlts] prepareAlts scrut case_bndr alts | Just (tc, tys) <- splitTyConApp_maybe (idType case_bndr) - = do { us <- getUniqueListM + = do { us <- getUniquesM ; let (idcs1, alts1) = filterAlts tc tys imposs_cons alts (yes2, alts2) = refineDefaultAlt us (idMult case_bndr) tc tys idcs1 alts1 -- The multiplicity on case_bndr's is the multiplicity of the @@ -2765,7 +2765,7 @@ mkCase2 mode scrut bndr alts_ty alts | not (isNullaryRepDataCon dc) = -- For non-nullary data cons we must invent some fake binders -- See Note [caseRules for dataToTag] in GHC.Core.Opt.ConstantFold - do { us <- getUniqueListM + do { us <- getUniquesM ; let (ex_tvs, arg_ids) = dataConRepInstPat us (idMult new_bndr) dc (tyConAppArgs (idType new_bndr)) ; return (ex_tvs ++ arg_ids) } ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -971,7 +971,7 @@ unbox_one_arg :: WwOpts unbox_one_arg opts arg_var DataConPatContext { dcpc_dc = dc, dcpc_tc_args = tc_args , dcpc_co = co, dcpc_args = ds } - = do { pat_bndrs_uniqs <- getUniqueListM + = do { pat_bndrs_uniqs <- getUniquesM ; let ex_name_fss = map getOccFS $ dataConExTyCoVars dc -- Create new arguments we get when unboxing dc @@ -1563,7 +1563,7 @@ unbox_one_result opts res_bndr -- ( case i of I# a -> ) | -- ( case j of I# b -> ) | ( (<i>, <j>) ) -- ( <hole> ) | - pat_bndrs_uniqs <- getUniqueListM + pat_bndrs_uniqs <- getUniquesM let (_exs, arg_ids) = dataConRepFSInstPat (repeat ww_prefix) pat_bndrs_uniqs cprCaseBndrMult dc tc_args massert (null _exs) -- Should have been caught by canUnboxResult ===================================== compiler/GHC/Core/Subst.hs ===================================== @@ -415,23 +415,20 @@ cloneIdBndr subst us old_id -- | Applies 'cloneIdBndr' to a number of 'Id's, accumulating a final -- substitution from left to right -- Discards non-Stable unfoldings -cloneIdBndrs :: Traversable t => Subst -> UniqSupply -> t Id -> (Subst, t Id) +cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) cloneIdBndrs subst us ids - = mapAccumL (clone_id subst) subst (withUniques (flip (,)) us ids) -{-# SPECIALIZE cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) #-} + = mapAccumL (clone_id subst) subst (ids `zip` uniqsFromSupply us) -cloneBndrs :: Traversable t => Subst -> UniqSupply -> t Var -> (Subst, t Var) +cloneBndrs :: Subst -> UniqSupply -> [Var] -> (Subst, [Var]) -- Works for all kinds of variables (typically case binders) -- not just Ids cloneBndrs subst us vs - = mapAccumL (\subst (v, u) -> cloneBndr subst u v) subst (withUniques (flip (,)) us vs) -{-# SPECIALIZE cloneBndrs :: Subst -> UniqSupply -> [Var] -> (Subst, [Var]) #-} + = mapAccumL (\subst (v, u) -> cloneBndr subst u v) subst (vs `zip` uniqsFromSupply us) -cloneBndrsM :: (Traversable t, MonadUnique m) => Subst -> t Var -> m (Subst, t Var) +cloneBndrsM :: MonadUnique m => Subst -> [Var] -> m (Subst, [Var]) -- Works for all kinds of variables (typically case binders) -- not just Ids cloneBndrsM subst vs = cloneBndrs subst `flip` vs <$> getUniqueSupplyM -{-# INLINE cloneBndrsM #-} cloneBndr :: Subst -> Unique -> Var -> (Subst, Var) cloneBndr subst uniq v @@ -439,16 +436,14 @@ cloneBndr subst uniq v | otherwise = clone_id subst subst (v,uniq) -- Works for coercion variables too -- | Clone a mutually recursive group of 'Id's -cloneRecIdBndrs :: Traversable t => Subst -> UniqSupply -> t Id -> (Subst, t Id) +cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) cloneRecIdBndrs subst us ids = - let x@(subst', _) = mapAccumL (clone_id subst') subst (withUniques (flip (,)) us ids) + let x@(subst', _) = mapAccumL (clone_id subst') subst (ids `zip` uniqsFromSupply us) in x -{-# SPECIALIZE cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) #-} -- | Clone a mutually recursive group of 'Id's -cloneRecIdBndrsM :: (Traversable t, MonadUnique m) => Subst -> t Id -> m (Subst, t Id) +cloneRecIdBndrsM :: MonadUnique m => Subst -> [Id] -> m (Subst, [Id]) cloneRecIdBndrsM subst ids = cloneRecIdBndrs subst `flip` ids <$> getUniqueSupplyM -{-# INLINE cloneRecIdBndrsM #-} -- Just like substIdBndr, except that it always makes a new unique -- It is given the unique to use ===================================== compiler/GHC/Iface/Env.hs ===================================== @@ -262,9 +262,11 @@ newIfaceName occ = do { uniq <- newUnique ; return $! mkInternalName uniq occ noSrcSpan } -newIfaceNames :: Traversable t => t OccName -> IfL (t Name) -newIfaceNames = withUniquesM (\ uniq occ -> mkInternalName uniq occ noSrcSpan) -{-# INLINE newIfaceNames #-} +newIfaceNames :: [OccName] -> IfL [Name] +newIfaceNames occs + = do { uniqs <- getUniquesM + ; return [ mkInternalName uniq occ noSrcSpan + | (occ,uniq) <- occs `zip` uniqs] } trace_if :: Logger -> SDoc -> IO () {-# INLINE trace_if #-} -- see Note [INLINE conditional tracing utilities] ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -1722,7 +1722,7 @@ tcIfaceAlt scrut mult (tycon, inst_tys) (IfaceAlt (IfaceDataAlt data_occ) arg_st tcIfaceDataAlt :: Mult -> DataCon -> [Type] -> [IfLclName] -> IfaceExpr -> IfL CoreAlt tcIfaceDataAlt mult con inst_tys arg_strs rhs - = do { uniqs <- getUniqueListM + = do { uniqs <- getUniquesM ; let (ex_tvs, arg_ids) = dataConRepFSInstPat (map ifLclNameFS arg_strs) uniqs mult con inst_tys ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -629,7 +629,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do newTyVars :: UniqSupply -> [TcTyVar] -> Subst -- Similarly, clone the type variables mentioned in the types -- we have here, *and* make them all RuntimeUnk tyvars - newTyVars us tvs = foldl' new_tv emptySubst (tvs `zip` uniqListFromSupply us) + newTyVars us tvs = foldl' new_tv emptySubst (tvs `zip` uniqsFromSupply us) new_tv subst (tv,uniq) = extendTCvSubstWithClone subst tv new_tv where new_tv = mkRuntimeUnkTyVar (setNameUnique (tyVarName tv) uniq) ===================================== compiler/GHC/Stg/Unarise.hs ===================================== @@ -731,8 +731,7 @@ unariseAlts rho (MultiValAlt _) bndr [GenStgAlt{ alt_con = DEFAULT unariseAlts rho (MultiValAlt _) bndr alts | isUnboxedSumBndr bndr - = do (rho_sum_bndrs, scrt_bndrs) <- unariseConArgBinder rho bndr - let tag_bndr:|real_bndrs = expectNonEmpty scrt_bndrs + = do (rho_sum_bndrs, scrt_bndrs@(tag_bndr : real_bndrs)) <- unariseConArgBinder rho bndr alts' <- unariseSumAlts rho_sum_bndrs (map StgVarArg real_bndrs) alts let inner_case = StgCase (StgApp tag_bndr []) tag_bndr tagAltTy alts' return [GenStgAlt{ alt_con = DataAlt (tupleDataCon Unboxed (length scrt_bndrs)) @@ -850,7 +849,7 @@ mapSumIdBinders alt_bndr args rhs rho0 mkCastInput :: (Id,PrimRep,UniqSupply) -> ([(PrimOp,Type,Unique)],Id,Id) mkCastInput (id,rep,bndr_us) = let (ops,types) = unzip $ getCasts (typePrimRepU $ idType id) rep - cst_opts = zip3 ops types $ uniqListFromSupply bndr_us + cst_opts = zip3 ops types $ uniqsFromSupply bndr_us out_id = case cst_opts of [] -> id _ -> let (_,ty,uq) = last cst_opts @@ -961,7 +960,7 @@ mkUbxSum dc ty_args args0 us , (ops,types) <- unzip $ getCasts (stgArgRepU arg) $ slotPrimRep slot_ty , not . null $ ops = let (us1,us2) = splitUniqSupply us - cast_uqs = uniqListFromSupply us1 + cast_uqs = uniqsFromSupply us1 cast_opts = zip3 ops types cast_uqs (_op,out_ty,out_uq) = last cast_opts casts = castArgRename cast_opts arg :: StgExpr -> StgExpr ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -3939,7 +3939,9 @@ splitTyConKind skol_info in_scope avoid_occs kind name = mkInternalName uniq occ loc tv = mkTcTyVar name arg' details subst' = extendSubstInScope subst tv - Inf uniq uniqs' = uniqs + (uniq,uniqs') = case uniqs of + uniq:uniqs' -> (uniq,uniqs') + _ -> panic "impossible" Inf occ occs' = occs Just (Named (Bndr tv vis), kind') ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -745,9 +745,11 @@ newSysLocalId fs w ty = do { u <- newUnique ; return (mkSysLocal fs u w ty) } -newSysLocalIds :: (Traversable t) => FastString -> t (Scaled TcType) -> TcRnIf gbl lcl (t TcId) -newSysLocalIds fs = withUniquesM (\ u (Scaled w t) -> mkSysLocal fs u w t) -{-# INLINE newSysLocalIds #-} +newSysLocalIds :: FastString -> [Scaled TcType] -> TcRnIf gbl lcl [TcId] +newSysLocalIds fs tys + = do { us <- getUniquesM + ; let mkId' n (Scaled w t) = mkSysLocal fs n w t + ; return (zipWith mkId' us tys) } instance MonadUnique (IOEnv (Env gbl lcl)) where getUniqueM = newUnique ===================================== compiler/GHC/Types/Id.hs ===================================== @@ -172,8 +172,6 @@ import GHC.Utils.Misc import GHC.Utils.Outputable import GHC.Utils.Panic -import Control.Monad.Trans.State (evalState, state) - -- infixl so you can say (id `set` a `set` b) infixl 1 `setIdUnfolding`, `setIdArity`, @@ -400,14 +398,12 @@ mkScaledTemplateLocal i (Scaled w ty) = mkSysLocalOrCoVar (fsLit "v") (mkBuiltin -- and "~" and "~~" have coercion "superclasses". -- | Create a template local for a series of types -mkTemplateLocals :: Traversable f => f Type -> f Id +mkTemplateLocals :: [Type] -> [Id] mkTemplateLocals = mkTemplateLocalsNum 1 -{-# SPECIALIZE mkTemplateLocals :: [Type] -> [Id] #-} -- | Create a template local for a series of type, but start from a specified template local -mkTemplateLocalsNum :: Traversable f => Int -> f Type -> f Id -mkTemplateLocalsNum n = flip evalState n . traverse (state . \ ty n -> (mkTemplateLocal n ty, succ n)) -{-# SPECIALIZE mkTemplateLocalsNum :: Int -> [Type] -> [Id] #-} +mkTemplateLocalsNum :: Int -> [Type] -> [Id] +mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys {- Note [Exported LocalIds] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Types/Unique/Supply.hs ===================================== @@ -14,14 +14,12 @@ module GHC.Types.Unique.Supply ( UniqSupply, -- Abstractly -- ** Operations on supplies - uniqFromSupply, uniqsFromSupply, uniqListFromSupply, -- basic ops + uniqFromSupply, uniqsFromSupply, -- basic ops takeUniqFromSupply, uniqFromTag, mkSplitUniqSupply, splitUniqSupply, listSplitUniqSupply, - withUniques, withUniquesM, - -- * Unique supply monad and its abstraction UniqSM, MonadUnique(..), @@ -29,26 +27,23 @@ module GHC.Types.Unique.Supply ( initUs, initUs_, -- * Set supply strategy - initUniqSupply, + initUniqSupply ) where import GHC.Prelude -import GHC.Data.List.Infinite import GHC.Types.Unique +import GHC.Utils.Panic.Plain import GHC.IO import GHC.Utils.Monad +import Control.Monad import Data.Word import GHC.Exts( Ptr(..), noDuplicate#, oneShot ) import Foreign.Storable import GHC.Utils.Monad.State.Strict as Strict -#if defined(DEBUG) -import GHC.Utils.Panic.Plain -#endif - #include "MachDeps.h" #if WORD_SIZE_IN_BITS != 64 @@ -297,9 +292,7 @@ listSplitUniqSupply :: UniqSupply -> [UniqSupply] -- ^ Create an infinite list of 'UniqSupply' from a single one uniqFromSupply :: UniqSupply -> Unique -- ^ Obtain the 'Unique' from this particular 'UniqSupply' -uniqsFromSupply :: UniqSupply -> Infinite Unique --- ^ Obtain an infinite list of 'Unique' that can be generated by constant splitting of the supply -uniqListFromSupply :: UniqSupply -> [Unique] +uniqsFromSupply :: UniqSupply -> [Unique] -- Infinite -- ^ Obtain an infinite list of 'Unique' that can be generated by constant splitting of the supply takeUniqFromSupply :: UniqSupply -> (Unique, UniqSupply) -- ^ Obtain the 'Unique' from this particular 'UniqSupply', and a new supply @@ -308,24 +301,11 @@ splitUniqSupply (MkSplitUniqSupply _ s1 s2) = (s1, s2) listSplitUniqSupply (MkSplitUniqSupply _ s1 s2) = s1 : listSplitUniqSupply s2 uniqFromSupply (MkSplitUniqSupply n _ _) = mkUniqueGrimily n -uniqsFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily n `Inf` uniqsFromSupply s2 -uniqListFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily n : uniqListFromSupply s2 +uniqsFromSupply (MkSplitUniqSupply n _ s2) = mkUniqueGrimily n : uniqsFromSupply s2 takeUniqFromSupply (MkSplitUniqSupply n s1 _) = (mkUniqueGrimily n, s1) {-# INLINE splitUniqSupply #-} -withUniques :: Traversable t => (Unique -> a -> b) -> UniqSupply -> t a -> t b -withUniques f us = initUs_ us . traverse (\ a -> flip f a <$> getUniqueUs) -{-# INLINE withUniques #-} - -withUniquesM :: (MonadUnique m, Traversable t) => (Unique -> a -> b) -> t a -> m (t b) -withUniquesM f = \ as -> ($ as) <$> withUniquesM' f -{-# INLINE withUniquesM #-} - -withUniquesM' :: (MonadUnique m, Traversable t) => (Unique -> a -> b) -> m (t a -> t b) -withUniquesM' f = withUniques f <$> getUniqueSupplyM -{-# INLINE withUniquesM' #-} - {- ************************************************************************ * * @@ -350,6 +330,10 @@ mkUniqSM :: (UniqSupply -> UniqResult a) -> UniqSM a mkUniqSM f = USM (oneShot f) {-# INLINE mkUniqSM #-} +-- TODO: try to get rid of this instance +instance MonadFail UniqSM where + fail = panic + -- | Run the 'UniqSM' action, returning the final 'UniqSupply' initUs :: UniqSupply -> UniqSM a -> (a, UniqSupply) initUs init_us m = case unUSM m init_us of { UniqResult r us -> (r, us) } @@ -374,17 +358,14 @@ class Monad m => MonadUnique m where -- | Get a new unique identifier getUniqueM :: m Unique -- | Get an infinite list of new unique identifiers - getUniquesM :: m (Infinite Unique) - -- | Get an infinite list of new unique identifiers - getUniqueListM :: m [Unique] + getUniquesM :: m [Unique] -- This default definition of getUniqueM, while correct, is not as -- efficient as it could be since it needlessly generates and throws away -- an extra Unique. For your instances consider providing an explicit -- definition for 'getUniqueM' which uses 'takeUniqFromSupply' directly. - getUniqueM = fmap uniqFromSupply getUniqueSupplyM - getUniquesM = fmap uniqsFromSupply getUniqueSupplyM - getUniqueListM = fmap uniqListFromSupply getUniqueSupplyM + getUniqueM = liftM uniqFromSupply getUniqueSupplyM + getUniquesM = liftM uniqsFromSupply getUniqueSupplyM instance MonadUnique UniqSM where getUniqueSupplyM = getUs @@ -395,6 +376,6 @@ getUniqueUs :: UniqSM Unique getUniqueUs = mkUniqSM (\us0 -> case takeUniqFromSupply us0 of (u,us1) -> UniqResult u us1) -getUniquesUs :: UniqSM (Infinite Unique) +getUniquesUs :: UniqSM [Unique] getUniquesUs = mkUniqSM (\us0 -> case splitUniqSupply us0 of (us1,us2) -> UniqResult (uniqsFromSupply us1) us2) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d6c40afc24314aa604ccd326a198c5df262c6878 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d6c40afc24314aa604ccd326a198c5df262c6878 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/0abfd9cb/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 21:34:02 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 16:34:02 -0500 Subject: [Git][ghc/ghc][master] Properly describe acceptance window for stat tests. Message-ID: <67ccb7ca4f1b1_31b9aaf854942522c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - 1 changed file: - testsuite/driver/perf_notes.py Changes: ===================================== testsuite/driver/perf_notes.py ===================================== @@ -162,7 +162,7 @@ class RelativeMetricAcceptanceWindow(MetricAcceptanceWindow): return (lowerBound, upperBound) def describe(self) -> str: - return '+/- %1.1f%%' % (100*self.__tol) + return '+/- %1.1f%%' % (self.__tol) def parse_perf_stat(stat_str: str) -> PerfStat: field_vals = stat_str.strip('\t').split('\t') View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/68310e1184dfb7e8fad4dba4ba19930005ac5282 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/68310e1184dfb7e8fad4dba4ba19930005ac5282 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/595f4b10/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 8 21:45:11 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 08 Mar 2025 16:45:11 -0500 Subject: [Git][ghc/ghc][wip/T25647] Refactor bindHsOuterTyVarBndrs' Message-ID: <67ccba67a4067_31b9aa12564e8289f9@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 484bef1c by Patrick at 2025-03-09T05:45:01+08:00 Refactor bindHsOuterTyVarBndrs' - - - - - 1 changed file: - compiler/GHC/Rename/HsType.hs Changes: ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -1128,10 +1128,10 @@ bindHsOuterTyVarBndrs' bind_fam doc mb_cls implicit_vars outer_bndrs thing_insid thing_inside $ HsOuterExplicit { hso_xexplicit = noExtField , hso_bndrs = exp_bndrs' , hso_ximplicit = implicit_vars' } - where - fam_implicit_vars = case bind_fam of - BindFam -> filterFreeVarsToBind (mapMaybe hsLTyVarLocName $ hso_bndrs outer_bndrs) implicit_vars - NotBindFam -> [] + where + fam_implicit_vars = case bind_fam of + BindFam -> filterFreeVarsToBind (mapMaybe hsLTyVarLocName exp_bndrs) implicit_vars + NotBindFam -> [] -- See Note [Term variable capture and implicit quantification] warn_term_var_capture :: LocatedN RdrName -> RnM () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/484bef1c547b39bdf8acaa5491408c85ba6ee76d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/484bef1c547b39bdf8acaa5491408c85ba6ee76d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/b4cdbdaa/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 8 22:04:46 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 17:04:46 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Allow defaulting of representational equalities Message-ID: <67ccbefe83187_3466c0c5cec759f4@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - fffa5b76 by Cheng Shao at 2025-03-08T17:04:34-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - cbe3e1e2 by Cheng Shao at 2025-03-08T17:04:34-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - 464cda34 by Cheng Shao at 2025-03-08T17:04:34-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 40 changed files: - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Unique/Supply.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/wasm.rst - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c64d5f466fc9f1cd8d42e0f79a6ba0d526788579...464cda340dffdeaaf2a986f714280acdc79eba6f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c64d5f466fc9f1cd8d42e0f79a6ba0d526788579...464cda340dffdeaaf2a986f714280acdc79eba6f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/4c0fb0d3/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 8 22:44:33 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 08 Mar 2025 17:44:33 -0500 Subject: [Git][ghc/ghc][wip/T25647] Add empty implicit variable bindings to HsOuterExplicit in mkEmptySigType Message-ID: <67ccc85175959_3466c087d37c78855@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 02c75cf1 by Patrick at 2025-03-09T06:44:25+08:00 Add empty implicit variable bindings to HsOuterExplicit in mkEmptySigType - - - - - 1 changed file: - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs Changes: ===================================== utils/haddock/haddock-api/src/Haddock/GhcUtils.hs ===================================== @@ -166,6 +166,7 @@ mkEmptySigType lty@(L loc ty) = L loc $ case ty of HsOuterExplicit { hso_xexplicit = noExtField , hso_bndrs = bndrs + , hso_ximplicit = [] } , sig_body = body } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/02c75cf16269065031da26ec8248639cce68e935 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/02c75cf16269065031da26ec8248639cce68e935 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/44f46a4b/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 00:02:14 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Sat, 08 Mar 2025 19:02:14 -0500 Subject: [Git][ghc/ghc][wip/int-index/retry-instds] 60 commits: wasm: bump dyld v8 heap size limit Message-ID: <67ccda86eb84c_373d6fccbf0485e@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/retry-instds at Glasgow Haskell Compiler / GHC Commits: fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - 54688cae by Vladislav Zavialov at 2025-03-09T02:45:10+03:00 Draft: retry instance declarations - - - - - 336 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/Instance.hs-boot - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Unique.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/wasm/JSFFI.c - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/dependent/should_compile/T12088a.hs - + testsuite/tests/dependent/should_compile/T12088b.hs - + testsuite/tests/dependent/should_compile/T12088c.hs - + testsuite/tests/dependent/should_compile/T12088d.hs - + testsuite/tests/dependent/should_compile/T12088sg1.hs - + testsuite/tests/dependent/should_compile/T12088sg2.hs - + testsuite/tests/dependent/should_compile/T12088sg3.hs - + testsuite/tests/dependent/should_compile/T12239.hs - + testsuite/tests/dependent/should_compile/T14668a.hs - + testsuite/tests/dependent/should_compile/T14668b.hs - + testsuite/tests/dependent/should_compile/T22257a.hs - + testsuite/tests/dependent/should_compile/T22257b.hs - + testsuite/tests/dependent/should_compile/T25238.hs - + testsuite/tests/dependent/should_compile/T25834.hs - testsuite/tests/dependent/should_compile/all.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/doc/conf.py - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/410f03ba4a66c101da50581818c324580dbabc39...54688cae45e27476c6c449373e2b9ea182e98f7c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/410f03ba4a66c101da50581818c324580dbabc39...54688cae45e27476c6c449373e2b9ea182e98f7c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/d93f67ab/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 03:05:03 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 22:05:03 -0500 Subject: [Git][ghc/ghc][master] wasm: do not use wasm type reflection in dyld Message-ID: <67cd055f3a865_373d6f1203784593a6@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 1 changed file: - utils/jsffi/dyld.mjs Changes: ===================================== utils/jsffi/dyld.mjs ===================================== @@ -1,4 +1,4 @@ -#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --experimental-wasm-type-reflection --max-old-space-size=65536 --no-turbo-fast-api-calls --wasm-lazy-validation +#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --max-old-space-size=65536 --no-turbo-fast-api-calls --wasm-lazy-validation // Note [The Wasm Dynamic Linker] // ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -693,30 +693,15 @@ class DyLD { continue; } - // For lazy GOT.func entries we can do better than poison: - // insert a stub in the table, so we at least get an error - // message that includes the missing function's name, not a - // mysterious table trap. The function type is Cmm function - // type as a best effort guess, if there's a type mismatch - // then call_indirect would trap. - // - // Also set a __poison field since we can't compare value - // against DyLD.#poison. + // Can't find this function, so poison it like GOT.mem. + // TODO: when wasm type reflection is widely available in + // browsers, use the WebAssembly.Function constructor to + // dynamically create a stub function that does better error + // reporting this.#gotFunc[name] = new WebAssembly.Global( { value: "i32", mutable: true }, - this.#table.grow( - 1, - new WebAssembly.Function( - { parameters: [], results: ["i32"] }, - () => { - throw new WebAssembly.RuntimeError( - `non-existent function ${name}` - ); - } - ) - ) + DyLD.#poison ); - this.#gotFunc[name].__poison = true; continue; } @@ -754,8 +739,7 @@ class DyLD { if (this.#gotFunc[k]) { // ghc-prim/ghc-internal may export functions imported by // rts - assert(this.#gotFunc[k].__poison); - delete this.#gotFunc[k].__poison; + assert(this.#gotFunc[k].value === DyLD.#poison); this.#table.set(this.#gotFunc[k].value, v); } continue; @@ -830,7 +814,7 @@ class DyLD { if (this.#gotMem[sym] && this.#gotMem[sym].value !== DyLD.#poison) { return this.#gotMem[sym].value; } - if (this.#gotFunc[sym] && !this.#gotFunc[sym].__poison) { + if (this.#gotFunc[sym] && this.#gotFunc[sym].value !== DyLD.#poison) { return this.#gotFunc[sym].value; } // Not in GOT.func yet, create the entry on demand View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cca68421831d0b5aadb82a649921188e343094e0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cca68421831d0b5aadb82a649921188e343094e0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/768e5a55/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 03:05:45 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Mar 2025 22:05:45 -0500 Subject: [Git][ghc/ghc][master] 2 commits: wasm: don't create a wasm global for dyld poison Message-ID: <67cd0589b04fa_373d6f175cc6c6192b@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 11 changed files: - docs/users_guide/wasm.rst - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/tests/jsffi/jsffigc.hs - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs Changes: ===================================== docs/users_guide/wasm.rst ===================================== @@ -189,9 +189,9 @@ use of ``freeJSVal`` when you’re sure about a ``JSVal``\ ’s lifetime, especially for the temporary ``JSVal``\ s. This will help reducing the memory footprint at runtime. -Note that ``freeJSVal`` is not idempotent and it’s only safe to call it -exactly once or not at all. Once it’s called, any subsequent usage of -that ``JSVal`` results in a runtime panic. +Note that ``freeJSVal`` is idempotent and it’s safe to call it more +than once. After it’s called, any subsequent usage of that ``JSVal`` +by passing to the JavaScript side results in a runtime panic. .. _wasm-jsffi-import: @@ -390,7 +390,7 @@ callback and intends to call it later, so the Haskell function closure is still retained by default. Still, the runtime can gradually drop these retainers by using -``FinalizerRegistry`` to invoke the finalizers to free the underlying +``FinalizationRegistry`` to invoke the finalizers to free the underlying stable pointers once the JavaScript callbacks are recycled. One last corner case is cyclic reference between the two heaps: if a ===================================== libraries/ghc-experimental/src/GHC/Wasm/Prim.hs ===================================== @@ -1,22 +1,21 @@ {-# LANGUAGE NoImplicitPrelude #-} module GHC.Wasm.Prim ( - -- User-facing JSVal type and freeJSVal + -- * User-facing 'JSVal' and related utilities JSVal, freeJSVal, mkWeakJSVal, - -- The JSString type and conversion from/to Haskell String + -- * 'JSString' and conversion from/to Haskell 'String' JSString (..), fromJSString, toJSString, - -- Exception types related to JSFFI + -- * Exception types related to JSFFI JSException (..), WouldBlockException (..), - PromisePendingException (..), - -- Is JSFFI used in the current wasm module? + -- * Is JSFFI used in the current wasm module? isJSFFIUsed ) where ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs ===================================== @@ -1,22 +1,21 @@ {-# LANGUAGE NoImplicitPrelude #-} module GHC.Internal.Wasm.Prim ( - -- User-facing JSVal type and freeJSVal + -- * User-facing 'JSVal' and related utilities JSVal (..), freeJSVal, mkWeakJSVal, - -- The JSString type and conversion from/to Haskell String + -- * 'JSString' and conversion from/to Haskell 'String' JSString (..), fromJSString, toJSString, - -- Exception types related to JSFFI + -- * Exception types related to JSFFI JSException (..), WouldBlockException (..), - PromisePendingException (..), - -- Is JSFFI used in the current wasm module? + -- * Is JSFFI used in the current wasm module? isJSFFIUsed ) where ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs ===================================== @@ -43,10 +43,14 @@ import GHC.Internal.Word mkJSCallback :: (StablePtr a -> IO JSVal) -> a -> IO JSVal mkJSCallback adjustor f = do sp@(StablePtr sp#) <- newStablePtr f - JSVal v w _ <- adjustor sp - let r = JSVal v w sp# - js_callback_register r sp - pure r + v@(JSVal p) <- adjustor sp + IO $ \s0 -> case stg_setJSVALsp p sp# s0 of + (# s1 #) -> (# s1, () #) + js_callback_register v sp + pure v + +foreign import prim "stg_setJSVALsp" + stg_setJSVALsp :: JSVal# -> StablePtr# a -> State# RealWorld -> (# State# RealWorld #) foreign import javascript unsafe "__ghc_wasm_jsffi_finalization_registry.register($1, $2, $1)" js_callback_register :: JSVal -> StablePtr a -> IO () ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs ===================================== @@ -7,4 +7,8 @@ where import GHC.Internal.Base +-- | If the current wasm module has any JSFFI functionality linked in, +-- this would be 'True' at runtime and 'False' otherwise. If this is +-- 'False', the wasm module would be a self-contained wasm32-wasi +-- module that can be run by non-web runtimes as well. foreign import ccall unsafe "rts_JSFFI_used" isJSFFIUsed :: Bool ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -1,7 +1,9 @@ {-# LANGUAGE GHC2021 #-} +{-# LANGUAGE GHCForeignImportPrim #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE UnliftedFFITypes #-} {-# LANGUAGE UnliftedNewtypes #-} module GHC.Internal.Wasm.Prim.Types ( @@ -26,7 +28,6 @@ import GHC.Internal.IO import GHC.Internal.IO.Encoding import GHC.Internal.Num import GHC.Internal.Show -import GHC.Internal.Stable import GHC.Internal.Weak {- @@ -38,76 +39,150 @@ On wasm, the Haskell heap lives in the linear memory space, and it can only contain bit patterns, not opaque references of the host JavaScript heap. As long as we have two heaps that coexist in this way, the best we can do is representing JavaScript references as -unique ids in the Haskell heap. - -In JavaScript, we have a JSValManager which exposes some interfaces as -wasm imports. The JSValManager is in charge of allocating unique ids -and managing the mapping from ids to the actual JavaScript values. In -fact we can implement the entire JSValManager in wasm, using a wasm -table with externref elements to hold the JavaScript values and a -special allocator to manage free slots in the table. That'll take more -work to implement though, with one more caveat: browsers typically -limit max wasm table size to 10000000 which may not be large enough -for some use cases. We can workaround the table size restriction by -managing a pool or tree of wasm tables, but at this point we really -should ditch the idea of doing everything in wasm just because we can. - -Next, we have the unlifted JSVal# type, defined in jsval.cmm and -contains one non-pointer word which is the id allocated by -JSValManager. On top of JSVal#, we have the user-facing lifted JSVal -type, which carries the JSVal#, as well as a weak pointer and a stable -pointer. - -The weak pointer is used to garbage collect JSVals. Its key is the -JSVal# closure, and it has a C finalizer that tells the JSValManager -to drop the mapping when the JSVal# closure is collected. Since we -want to provide freeJSVal to allow eager freeing of JSVals, we need to -carry it as a field of JSVal. - -The stable pointer field is NULL for normal JSVals created via foreign -import results or foreign export arguments. But for JSFFI dynamic -exports that wraps a Haskell function closure as a JavaScript callback -and returns that callback's JSVal, it is a stable pointer that pins -that Haskell function closure. If this JSVal is garbage collected, -then we can only rely on a JavaScript FinalizerRegistry to free the -stable pointer in the future, but if we eagerly free the callback with -freeJSVal, then we can eagerly free this stable pointer as well. - -The lifted JSVal type is meant to be an abstract type. Its creation -and consumption is mainly handled by the RTS API functions rts_mkJSVal -and rts_getJSVal, which are used in C stub files generated when -desugaring JSFFI foreign imports/exports. +ids in the Haskell heap. + +First, we have the unlifted JSVal# type, defined in jsval.cmm with the +following memory layout: + ++--------------+-----+----+----------+ +|stg_JSVAL_info|Weak#|Int#|StablePtr#| ++--------------+-----+----+----------+ + +The first non-pointer Int# field is a 32-bit id allocated and +returned by the JSValManager on the JavaScript side. The JSValManager +maintains a Map from ids to actual JavaScript values. This field is +immutable throughout a JSVal# closure's lifetime and is unique for +each JSVal# ever created. + +The Weak# poiner sets the JSVal# closure as key and has a C finalizer +that drops the mapping in JSValManager. When the JSVal# closure is +garbage collected, the finalizer is invoked, but it can also be +eagerly invoked by freeJSVal, that's why we carry the Weak# in JSVal# +as a pointer field. + +Normally, one JSVal# manage one kind of resource: the JavaScript value +retained in JSValManager. However, in case of JSFFI exports where we +convert Haskell functions to JavaScript callbacks, the JSVal# manages +not only the callback on the JavaScript side, but also a stable +pointer that pins the exported function on the Haskell side. That +StablePtr# is recorded in the JSVal# closure. + +Even if the JSVal# closure is garbage collected, we don't know if the +JavaScript side still retains the callback somewhere other than +JSValManager, so the stable pointer will continue to pin the Haskell +function closure. We do a best effort cleanup on the JavaScript side +by using a FinalizationRegistry: if the JSVal# is automatically +collected, the callback is dropped in JSValManager and also not used +elsewhere, the FinalizationRegistry calls into the RTS to drop the +stable pointer as well. + +However, JSVal# can be eagerly freed by freeJSVal. It'll deregister +the callback in the FinalizationRegistry, finalize the Weak# pointer +and also free the stable pointer. In order to make freeJSVal +idempotent, we must not free the stable pointer twice; therefore the +StablePtr# field is mutable and will be overwritten with NULL upon +first freeJSVal invocation; it's also NULL upon creation by +rts_mkJSVal and later overwritten with the StablePtr# upon the +callback creation. + +On top of JSVal#, we have the user-facing lifted JSVal type, which +wraps the JSVal#. The lifted JSVal type is meant to be an abstract +type. Its creation and consumption is mainly handled by the RTS API +functions rts_mkJSVal and rts_getJSVal, which are used in C stub files +generated when desugaring JSFFI foreign imports/exports. -} newtype JSVal# = JSVal# (Any :: UnliftedType) +-- | A 'JSVal' is a first-class Haskell value on the Haskell heap that +-- represents a JavaScript value. You can use 'JSVal' or its @newtype@ +-- as a supported argument or result type in JSFFI import & export +-- declarations, in addition to those lifted FFI types like 'Int' or +-- 'Ptr' that's already supported by C FFI. It is garbage collected by +-- the GHC RTS: +-- +-- * There can be different 'JSVal's that point to the same JavaScript +-- value. As long as there's at least one 'JSVal' still alive on the +-- Haskell heap, that JavaScript value will still be alive on the +-- JavaScript heap. +-- * If there's no longer any live 'JSVal' that points to the +-- JavaScript value, after Haskell garbage collection, the +-- JavaScript runtime will be able to eventually garbage collect +-- that JavaScript value as well. +-- +-- There's a special kind of 'JSVal' that represents a JavaScript +-- callback exported from a Haskell function like this: +-- +-- > foreign import javascript "wrapper" +-- > exportFibAsAsyncJSCallback :: (Int -> Int) -> IO JSVal +-- +-- Such a 'JSVal' manages an additional kind of resource: the exported +-- Haskell function closure. Even if it is automatically garbage +-- collected, the Haskell function closure would still be retained +-- since the JavaScript callback might be retained elsewhere. We do a +-- best-effort collection here using JavaScript +-- [@FinalizationRegistry@](https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/FinalizationRegistry), +-- so the Haskell function closure might be eventually dropped if the +-- JavaScript callback is garbage collected. +-- +-- Note that even the @FinalizationRegistry@ logic can't break cyclic +-- references between the Haskell/JavaScript heap: when an exported +-- Haskell function closure retains a 'JSVal' that represents a +-- JavaScript callback. Though this can be solved by explicit +-- 'freeJSVal' calls. data JSVal - = forall a . JSVal JSVal# (Weak# JSVal) (StablePtr# a) + = JSVal JSVal# +-- | 'freeJSVal' eagerly frees a 'JSVal' in the runtime. It drops the +-- retained JavaScript value on the JavaScript side, and in case of a +-- 'JSVal' that represents a callback, also drops the retained Haskell +-- function closure. Once a 'JSVal' is freed by 'freeJSVal', later +-- attempts to pass it to the JavaScript side would result in runtime +-- crashes, so you should only call 'freeJSVal' when you're confident +-- that 'JSVal' won't be used again (and in case of callbacks, that +-- callback won't be invoked again). +-- +-- 'freeJSVal' is idempotent: it's safe to call it more than once on +-- the same 'JSVal', subsequent invocations are no-ops. You are +-- strongly recommended to call 'freeJSVal' on short-lived +-- intermediate 'JSVal' values for timely release of resources! freeJSVal :: JSVal -> IO () -freeJSVal v@(JSVal _ w sp) = do - case sp `eqStablePtr#` unsafeCoerce# nullAddr# of - 0# -> do - js_callback_unregister v - freeStablePtr $ StablePtr sp - _ -> pure () - IO $ \s0 -> case finalizeWeak# w s0 of +freeJSVal v@(JSVal p) = do + js_callback_unregister v + IO $ \s0 -> case stg_freeJSVal# p s0 of (# s1, _, _ #) -> (# s1, () #) +-- | 'mkWeakJSVal' allows you to create a 'Weak' pointer that observes +-- the liveliness of a 'JSVal' closure on the Haskell heap and +-- optionally attach a finalizer. +-- +-- Note that this liveliness is not affected by 'freeJSVal': even if +-- 'freeJSVal' is called, the 'JSVal' might still be alive on the +-- Haskell heap as a dangling reference and 'deRefWeak' might still be +-- able to retrieve the 'JSVal' before it is garbage collected. mkWeakJSVal :: JSVal -> Maybe (IO ()) -> IO (Weak JSVal) -mkWeakJSVal v@(JSVal k _ _) (Just (IO fin)) = IO $ \s0 -> - case mkWeak# k v fin s0 of +mkWeakJSVal v@(JSVal p) (Just (IO fin)) = IO $ \s0 -> + case mkWeak# p v fin s0 of (# s1, w #) -> (# s1, Weak w #) -mkWeakJSVal (JSVal _ w _) Nothing = pure $ Weak w +mkWeakJSVal v@(JSVal p) Nothing = IO $ \s0 -> + case mkWeakNoFinalizer# p v s0 of + (# s1, w #) -> (# s1, Weak w #) + +foreign import prim "stg_freeJSVAL" + stg_freeJSVal# :: JSVal# -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) -foreign import javascript unsafe "if (!__ghc_wasm_jsffi_finalization_registry.unregister($1)) { throw new WebAssembly.RuntimeError('js_callback_unregister'); }" +foreign import javascript unsafe "try { __ghc_wasm_jsffi_finalization_registry.unregister($1); } catch {}" js_callback_unregister :: JSVal -> IO () +-- | A 'JSString' represents a JavaScript string. newtype JSString = JSString JSVal +-- | Converts a 'JSString' to a Haskell 'String'. Conversion is done +-- eagerly once the resulting 'String' is forced, and the argument +-- 'JSString' may be explicitly freed if no longer used. fromJSString :: JSString -> String fromJSString s = unsafeDupablePerformIO $ do l <- js_stringLength s @@ -122,15 +197,25 @@ foreign import javascript unsafe "$1.length" foreign import javascript unsafe "(new TextEncoder()).encodeInto($1, new Uint8Array(__exports.memory.buffer, $2, $3)).written" js_encodeInto :: JSString -> Ptr a -> Int -> IO Int +-- | Converts a Haskell 'String' to a 'JSString'. toJSString :: String -> JSString toJSString s = unsafeDupablePerformIO $ withCStringLen utf8 s $ \(buf, len) -> js_toJSString buf len foreign import javascript unsafe "(new TextDecoder('utf-8', {fatal: true})).decode(new Uint8Array(__exports.memory.buffer, $1, $2))" js_toJSString :: Ptr a -> Int -> IO JSString +-- | A 'JSException' represents a JavaScript exception. It is likely +-- but not guaranteed to be an instance of the @Error@ class. When you +-- call an async JSFFI import and the result @Promise@ rejected, the +-- rejection value will be wrapped in a 'JSException' and re-thrown in +-- Haskell once you force the result. newtype JSException = JSException JSVal +-- | If the +-- [@error.stack@](https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/Error/stack) +-- property is present, it will be used to render the 'Show' instance +-- output so you can see the JavaScript stack trace. instance Show JSException where showsPrec p e = showParen (p >= 11) $ showString "JSException " . showsPrec 11 (jsErrorString e) @@ -147,6 +232,24 @@ foreign import javascript unsafe "`${$1.stack ? $1.stack : $1}`" instance Exception JSException +-- | An async JSFFI import returns a thunk that represents a pending +-- JavaScript @Promise@: +-- +-- > foreign import javascript "(await fetch($1)).text()" +-- > js_fetch :: JSString -> IO JSString +-- +-- Forcing that thunk blocks the current Haskell thread until the +-- @Promise@ is fulfilled, but that cannot happen if the Haskell +-- thread is a bound thread created by a JSFFI sync export or a C FFI +-- export! Those Haskell computations are meant to return +-- synchronously, but JavaScript asynchronocity is contagious and +-- there's no escape hatch like @unsafeAwaitPromise at . +-- +-- In such cases, a 'WouldBlockException' exception would be thrown. +-- The 'WouldBlockException' is attached with a diagnostic message +-- generated at compile-time (currently just the JSFFI source snippet +-- of the corresponding async import) to help debugging the +-- exception's cause. newtype WouldBlockException = WouldBlockException String deriving (Show) ===================================== rts/wasm/JSFFI.c ===================================== @@ -70,7 +70,7 @@ __attribute__((constructor(102))) static void __ghc_wasm_jsffi_init(void) { } typedef __externref_t HsJSVal; -typedef StgWord JSValKey; +typedef StgInt JSValKey; extern const StgInfoTable stg_JSVAL_info; extern const StgInfoTable ghczminternal_GHCziInternalziWasmziPrimziTypes_JSVal_con_info; @@ -91,9 +91,10 @@ HaskellObj rts_mkJSVal(Capability*, HsJSVal); HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { JSValKey k = __imported_newJSVal(v); - HaskellObj p = (HaskellObj)allocate(cap, CONSTR_sizeW(0, 1)); + HaskellObj p = (HaskellObj)allocate(cap, CONSTR_sizeW(1, 2)); SET_HDR(p, &stg_JSVAL_info, CCS_SYSTEM); - p->payload[0] = (HaskellObj)k; + p->payload[1] = (HaskellObj)k; + p->payload[2] = NULL; StgCFinalizerList *cfin = (StgCFinalizerList *)allocate(cap, sizeofW(StgCFinalizerList)); @@ -107,6 +108,7 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { SET_HDR(w, &stg_WEAK_info, CCS_SYSTEM); w->cfinalizers = (StgClosure *)cfin; w->key = p; + w->value = Unit_closure; w->finalizer = &stg_NO_FINALIZER_closure; w->link = cap->weak_ptr_list_hd; cap->weak_ptr_list_hd = w; @@ -114,14 +116,13 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { cap->weak_ptr_list_tl = w; } - HaskellObj box = (HaskellObj)allocate(cap, CONSTR_sizeW(3, 0)); + p->payload[0] = (HaskellObj)w; + + HaskellObj box = (HaskellObj)allocate(cap, CONSTR_sizeW(1, 0)); SET_HDR(box, &ghczminternal_GHCziInternalziWasmziPrimziTypes_JSVal_con_info, CCS_SYSTEM); box->payload[0] = p; - box->payload[1] = (HaskellObj)w; - box->payload[2] = NULL; - w->value = TAG_CLOSURE(1, box); - return w->value; + return TAG_CLOSURE(1, box); } __attribute__((import_module("ghc_wasm_jsffi"), import_name("getJSVal"))) @@ -129,7 +130,7 @@ HsJSVal __imported_getJSVal(JSValKey); STATIC_INLINE HsJSVal rts_getJSValzh(HaskellObj p) { ASSERT(p->header.info == &stg_JSVAL_info); - return __imported_getJSVal((JSValKey)p->payload[0]); + return __imported_getJSVal((JSValKey)p->payload[1]); } HsJSVal rts_getJSVal(HaskellObj); ===================================== rts/wasm/jsval.cmm ===================================== @@ -1,10 +1,33 @@ #include "Cmm.h" -// This defines the unlifted JSVal# type. See Note [JSVal -// representation for wasm] for detailed explanation. +// This defines the unlifted JSVal# type. See +// Note [JSVal representation for wasm] for +// detailed explanation. -INFO_TABLE(stg_JSVAL, 0, 1, PRIM, "JSVAL", "JSVAL") +INFO_TABLE(stg_JSVAL, 1, 2, PRIM, "JSVAL", "JSVAL") (P_ node) { return (node); } + +stg_setJSVALsp (P_ p, W_ sp) +{ + W_[p + SIZEOF_StgHeader + WDS(2)] = sp; + return (); +} + +stg_freeJSVAL (P_ p) +{ + P_ w; + W_ sp; + + w = P_[p + SIZEOF_StgHeader]; + sp = W_[p + SIZEOF_StgHeader + WDS(2)]; + + if (sp != NULL) { + ccall freeStablePtr(sp); + W_[p + SIZEOF_StgHeader + WDS(2)] = NULL; + } + + jump stg_finalizzeWeakzh (w); +} ===================================== testsuite/tests/jsffi/jsffigc.hs ===================================== @@ -68,7 +68,7 @@ testDynExportGC x y z = do -- Return a continuation to be called after the JavaScript side -- finishes garbage collection. js_mk_cont $ do - -- The JavaScript FinalizerRegistry logic only frees the stable + -- The JavaScript FinalizationRegistry logic only frees the stable -- pointer that pins fn. So we need to invoke Haskell garbage -- collection again. performGC ===================================== utils/jsffi/dyld.mjs ===================================== @@ -231,10 +231,7 @@ class DyLD { // memory access near this address will trap immediately. // // In JS API i32 is signed, hence this layer of redirection. - static #poison = new WebAssembly.Global( - { value: "i32", mutable: false }, - 0xffffffff - DyLD.#pageSize - ).value; + static #poison = (0xffffffff - DyLD.#pageSize) | 0; // When processing exports, skip the following ones since they're // generated by wasm-ld. ===================================== utils/jsffi/prelude.mjs ===================================== @@ -3,29 +3,13 @@ // of one; the post-linker script will copy all contents into a new // ESM module. -// Manage a mapping from unique 32-bit ids to actual JavaScript -// values. +// Manage a mapping from 32-bit ids to actual JavaScript values. export class JSValManager { #lastk = 0; #kv = new Map(); - constructor() {} - - // Maybe just bump this.#lastk? For 64-bit ids that's sufficient, - // but better safe than sorry in the 32-bit case. - #allocKey() { - let k = this.#lastk; - while (true) { - if (!this.#kv.has(k)) { - this.#lastk = k; - return k; - } - k = (k + 1) | 0; - } - } - newJSVal(v) { - const k = this.#allocKey(); + const k = ++this.#lastk; this.#kv.set(k, v); return k; } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cca68421831d0b5aadb82a649921188e343094e0...fd40eaa17c6ce8716ec2eacc95beae194a935352 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cca68421831d0b5aadb82a649921188e343094e0...fd40eaa17c6ce8716ec2eacc95beae194a935352 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250308/438d8993/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 10:32:21 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sun, 09 Mar 2025 06:32:21 -0400 Subject: [Git][ghc/ghc][wip/T25647] Add empty implicit variable bindings to HsOuterExplicit in synifyDataCon Message-ID: <67cd6e354f884_25dc93e38ac14520@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: f66769c6 by Patrick at 2025-03-09T18:32:13+08:00 Add empty implicit variable bindings to HsOuterExplicit in synifyDataCon - - - - - 1 changed file: - utils/haddock/haddock-api/src/Haddock/Convert.hs Changes: ===================================== utils/haddock/haddock-api/src/Haddock/Convert.hs ===================================== @@ -484,6 +484,7 @@ synifyDataCon use_gadt_syntax dc = HsOuterExplicit { hso_xexplicit = noExtField , hso_bndrs = map synifyTyVarBndr user_tvbndrs + , hso_ximplicit = [] } -- skip any EqTheta, use 'orig'inal syntax View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f66769c6325af5fe46d8d0f504b7c38db89da5b2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f66769c6325af5fe46d8d0f504b7c38db89da5b2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/df08d87d/attachment.html> From gitlab at gitlab.haskell.org Sun Mar 9 14:35:47 2025 From: gitlab at gitlab.haskell.org (Ryan Scott (@RyanGlScott)) Date: Sun, 09 Mar 2025 10:35:47 -0400 Subject: [Git][ghc/ghc][wip/make-Wdata-kinds-tc-an-error] 14 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67cda74327ff8_74988c6c14894e@gitlab.mail> Ryan Scott pushed to branch wip/make-Wdata-kinds-tc-an-error at Glasgow Haskell Compiler / GHC Commits: a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - b11744b9 by Ryan Scott at 2025-03-09T10:35:31-04:00 Remove -Wdata-kinds-tc warning, make DataKinds issues in typechecker become errors !11314 introduced the `-Wdata-kinds-tc` warning as part of a fix for #22141. This was a temporary stopgap measure to allow users who were accidentally relying on code which needed the `DataKinds` extension in order to typecheck without having to explicitly enable the extension. Now that some amount of time has passed, this patch removes `-Wdata-kinds-tc` and upgrades any `DataKinds`-related issues in the typechecker (which were previously warnings) into errors. - - - - - 126 changed files: - compiler/GHC.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Unique.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/phases.rst - docs/users_guide/using-warnings.rst - docs/users_guide/wasm.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - − testsuite/tests/typecheck/should_compile/T22141a.stderr - − testsuite/tests/typecheck/should_compile/T22141b.stderr - − testsuite/tests/typecheck/should_compile/T22141c.stderr - − testsuite/tests/typecheck/should_compile/T22141d.stderr - − testsuite/tests/typecheck/should_compile/T22141e.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T20873c.hs - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs - testsuite/tests/typecheck/should_fail/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs - testsuite/tests/typecheck/should_fail/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs - testsuite/tests/typecheck/should_fail/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs - testsuite/tests/typecheck/should_fail/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs - testsuite/tests/typecheck/should_fail/T22141e.stderr - testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs - testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6db8d60540aa68807cf82e7237e425de97ef143f...b11744b98e358fdd7acaf7ba75ce3946c41c836e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6db8d60540aa68807cf82e7237e425de97ef143f...b11744b98e358fdd7acaf7ba75ce3946c41c836e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/9f6fe732/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 15:03:12 2025 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Sun, 09 Mar 2025 11:03:12 -0400 Subject: [Git][ghc/ghc][wip/T24603] 100 commits: interpreter: Fix INTERP_STATS profiling code Message-ID: <67cdadb0c5cba_7498824f1088981@gitlab.mail> Serge S. Gulin pushed to branch wip/T24603 at Glasgow Haskell Compiler / GHC Commits: 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 5c4d297b by Serge S. Gulin at 2025-03-09T18:15:34+04:00 Support for ARM64 Windows (LLVM-enabled) (fixes #24603) submodule Co-authored-by: Cheng Shao <terrorjack at type.dance> Co-authored-by: Dmitrii Egorov <egorov.d.i at icloud.com> Co-authored-by: Andrei Borzenkov <root at sandwitch.dev> - - - - - ed3b0ec4 by Serge S. Gulin at 2025-03-09T18:22:01+04:00 Basic NCG support for HelloWorld - - - - - 3d4f0dd9 by Serge S. Gulin at 2025-03-09T18:22:02+04:00 Remove trailing whtespace to make CI greener - - - - - 447 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Parser.hs - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/System/CPUTime/Windows.hsc - libraries/base/src/System/Timeout.hs - libraries/base/tests/perf/encodingAllocations.hs - libraries/directory - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/haskeline - libraries/process - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/unix - llvm-targets - m4/fp_settings.m4 - m4/ghc_tables_next_to_code.m4 - rts/Interpreter.c - rts/Interpreter.h - rts/RtsMain.c - rts/StgCRun.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - rts/win32/veh_excn.c - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod185.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/all.T - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T21003.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/exe/Main.hs - utils/haddock/doc/conf.py - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - utils/hsc2hs - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - utils/llvm-targets/gen-data-layout.sh - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/50b2fab5c020419acfc7c9a7d4af81044a10e7ce...3d4f0dd9f6e6e8f0fd0fe64db86a5432a2517aad -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/50b2fab5c020419acfc7c9a7d4af81044a10e7ce...3d4f0dd9f6e6e8f0fd0fe64db86a5432a2517aad You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/be5ed9b5/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 15:44:21 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sun, 09 Mar 2025 11:44:21 -0400 Subject: [Git][ghc/ghc][wip/T25647] Add missing implicit variable bindings to HsOuterExplicit in ExactPrint instance Message-ID: <67cdb755a06e5_7498882caa893014@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: cdd9232c by Patrick at 2025-03-09T23:43:03+08:00 Add missing implicit variable bindings to HsOuterExplicit in ExactPrint instance - - - - - 1 changed file: - utils/check-exact/ExactPrint.hs Changes: ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -4373,17 +4373,17 @@ instance ExactPrint Void where instance ExactPrintTVFlag flag => ExactPrint (HsOuterTyVarBndrs flag GhcPs) where getAnnotationEntry (HsOuterImplicit _) = NoEntryVal - getAnnotationEntry (HsOuterExplicit an _) = fromAnn an + getAnnotationEntry (HsOuterExplicit an _ _) = fromAnn an setAnnotationAnchor (HsOuterImplicit a) _ _ _ = HsOuterImplicit a - setAnnotationAnchor (HsOuterExplicit an a) anc ts cs = HsOuterExplicit (setAnchorEpa an anc ts cs) a + setAnnotationAnchor (HsOuterExplicit an a b) anc ts cs = HsOuterExplicit (setAnchorEpa an anc ts cs) a b exact b@(HsOuterImplicit _) = pure b - exact (HsOuterExplicit (EpAnn l (f,d) cs) bndrs) = do + exact (HsOuterExplicit (EpAnn l (f,d) cs) bndrs imps) = do f' <- markEpUniToken f bndrs' <- markAnnotated bndrs d' <- markEpToken d - return (HsOuterExplicit (EpAnn l (f',d') cs) bndrs') + return (HsOuterExplicit (EpAnn l (f',d') cs) bndrs' imps) -- --------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cdd9232c1cfc4f7db894de0b17d3ce808c5147c4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cdd9232c1cfc4f7db894de0b17d3ce808c5147c4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/bb9c6009/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 16:08:19 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sun, 09 Mar 2025 12:08:19 -0400 Subject: [Git][ghc/ghc][wip/T25647] Add implicit variable bindings to HsOuterExplicit in various instances Message-ID: <67cdbcf330f60_74988bd6c30937cb@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 67ed0e7c by Patrick at 2025-03-10T00:08:08+08:00 Add implicit variable bindings to HsOuterExplicit in various instances - - - - - 4 changed files: - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs Changes: ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -1212,9 +1212,10 @@ addHsOuterFamEqnTyVarBinds outer_bndrs thing_inside = do HsOuterImplicit{hso_ximplicit = imp_tvs} -> addSimpleTyVarBinds ReuseBoundNames imp_tvs $ thing_inside $ coreNothingList elt_ty - HsOuterExplicit{hso_bndrs = exp_bndrs} -> + HsOuterExplicit{hso_bndrs = exp_bndrs,hso_ximplicit = imp_tvs} -> addHsTyVarBinds FreshNamesOnly exp_bndrs $ \th_exp_bndrs -> - thing_inside $ coreJustList elt_ty th_exp_bndrs + addSimpleTyVarBinds ReuseBoundNames imp_tvs $ + thing_inside $ coreJustList elt_ty th_exp_bndrs addHsOuterSigTyVarBinds :: HsOuterSigTyVarBndrs GhcRn ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1753,8 +1753,11 @@ instance ToHie (LocatedA (ConDecl GhcRn)) where HsOuterImplicit{hso_ximplicit = imp_vars} -> bindingsOnly $ map (C $ TyVarBind (mkScope outer_bndrs_loc) resScope) imp_vars - HsOuterExplicit{hso_bndrs = exp_bndrs} -> - toHie $ tvScopes resScope NoScope exp_bndrs + HsOuterExplicit{hso_bndrs = exp_bndrs,hso_ximplicit = imp_vars} -> do + exps <- toHie $ tvScopes resScope NoScope exp_bndrs + imps <- bindingsOnly $ map (C $ TyVarBind (mkScope outer_bndrs_loc) resScope) + imp_vars + pure $ exps ++ imps , toHie ctx , toHie args , toHie typ ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -3403,13 +3403,13 @@ tcOuterTKBndrsX skol_mode skol_info outer_bndrs thing_inside do { (imp_tvs', thing) <- tcImplicitTKBndrsX skol_mode skol_info imp_tvs thing_inside ; return ( HsOuterImplicit{hso_ximplicit = imp_tvs'} , thing) } - HsOuterExplicit{hso_bndrs = exp_bndrs} -> - do { (exp_tvs', thing) <- tcExplicitTKBndrsX skol_mode exp_bndrs thing_inside + HsOuterExplicit{hso_bndrs = exp_bndrs,hso_ximplicit = imp_tvs} -> + do { (exp_tvs', (imp_tvs', thing)) <- tcExplicitTKBndrsX skol_mode exp_bndrs $ tcImplicitTKBndrsX skol_mode skol_info imp_tvs thing_inside ; return ( HsOuterExplicit { hso_xexplicit = exp_tvs' , hso_bndrs = exp_bndrs -- note nothing should be here since -- sig - , hso_ximplicit = [] } + , hso_ximplicit = imp_tvs' } , thing) } ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -401,7 +401,7 @@ tcPatSynSig name sig_ty@(L _ (HsSig{sig_bndrs = hs_outer_bndrs, sig_body = hs_ty univ_bndrs :: [TcInvisTVBinder] (implicit_tvs, univ_bndrs) = case outer_bndrs of HsOuterImplicit{hso_ximplicit = implicit_tvs} -> (implicit_tvs, []) - HsOuterExplicit{hso_xexplicit = univ_bndrs} -> ([], univ_bndrs) + HsOuterExplicit{hso_xexplicit = univ_bndrs,hso_ximplicit = implicit_tvs} -> (implicit_tvs, univ_bndrs) ; implicit_tvs <- zonkAndScopedSort implicit_tvs ; let implicit_bndrs = mkTyVarBinders SpecifiedSpec implicit_tvs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67ed0e7c39d8ed80ea8c81ffe26ea6251e07bad2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67ed0e7c39d8ed80ea8c81ffe26ea6251e07bad2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/b650f6d3/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 16:19:50 2025 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Sun, 09 Mar 2025 12:19:50 -0400 Subject: [Git][ghc/ghc][wip/llvm-debug-info] 172 commits: user_guide: Note -pgmP/-optP are for /Haskell/-CPP Message-ID: <67cdbfa6c7496_7498884f76094671@gitlab.mail> Serge S. Gulin pushed to branch wip/llvm-debug-info at Glasgow Haskell Compiler / GHC Commits: 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz Goślinowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 889ad9e7 by Ben Gamari at 2025-03-09T20:19:19+04:00 [WIP] llvmGen: Produce debug information metadata for functions Summary: It turns out that providing debug information in LLVM is relatively straightforward. At this moment this only provides debug information with procedure-level granularity. Test Plan: Validate, look at DWARF output, try poking around in GDB Reviewers: scpmw, simonmar, austin Subscribers: spacekitteh, cocreature, thomie Differential Revision: https://phabricator.haskell.org/D2343 - - - - - 072bc953 by Ben Gamari at 2025-03-09T20:19:20+04:00 Fix distinction - - - - - a920dc04 by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Code cleanup after rebase - - - - - a40871b8 by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Fix store comma - - - - - a4926aee by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Subprograms is not a field of `DICompileUnit` in modern LLVM IR - - - - - dc1b5495 by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Passing location file metaId down - - - - - d444a98d by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Remove empty meta of subprograms `!XX = !{}` - - - - - 8d12b779 by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Use root level fileMetaId instead of generation each record for subprograms - - - - - fff8d21d by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Render debug header and pass location-based file metaId to subprograms - - - - - 44561488 by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Use compilation unit metaId to connect subprograms - - - - - 48111c42 by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Add MetaDISubprogram unit to ppr - - - - - 97d44a2d by Serge S. Gulin at 2025-03-09T20:19:20+04:00 Limit LLVM `Opt` optimization level to `0` when debug metadata is required - - - - - 1333 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/CmmToLlvm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Llvm.hs - compiler/GHC/Llvm/MetaData.hs - compiler/GHC/Llvm/Ppr.hs - compiler/GHC/Llvm/Syntax.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/cbits/genSym.c - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/diagnostics-as-json-schema-1_0.json - docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/expected-undocumented-flags.txt - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/wasm.rst - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/bindist/Makefile - hadrian/cabal.project - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Warnings.hs - libffi-tarballs - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/Data/Semigroup.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Exts.hs - libraries/base/src/System/Timeout.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-experimental/src/Data/Sum/Experimental.hs - libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/tests/stack_big_ret.hs - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - libraries/ghc-internal/src/GHC/Internal/Char.hs - libraries/ghc-prim/GHC/Classes.hs → libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - libraries/ghc-internal/src/GHC/Internal/Err.hs - libraries/ghc-internal/src/GHC/Internal/Event.hs - libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - libraries/ghc-internal/src/GHC/Internal/Generics.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Int.hs - libraries/ghc-internal/src/GHC/Internal/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - libraries/ghc-internal/src/GHC/Internal/Ix.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - libraries/ghc-internal/src/GHC/Internal/Maybe.hs - libraries/ghc-internal/src/GHC/Internal/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-prim/GHC/Prim/Exception.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Read.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - libraries/ghc-internal/src/GHC/Internal/Records.hs - libraries/ghc-internal/src/GHC/Internal/Show.hs - libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - libraries/ghc-prim/GHC/Tuple.hs → libraries/ghc-internal/src/GHC/Internal/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - libraries/ghc-prim/GHC/Types.hs → libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghc-internal/src/GHC/Internal/Word.hs - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - linters/lint-codes/LintCodes/Static.hs - linters/lint-codes/Main.hs - m4/fp_settings.m4 - rts/Exception.cmm - rts/Interpreter.c - rts/Interpreter.h - rts/Prelude.h - rts/PrimOps.cmm - rts/RtsMain.c - rts/RtsSymbols.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStdThunks.cmm - rts/configure.ac - rts/external-symbols.list.in - rts/include/RtsAPI.h - rts/include/Stg.h - rts/include/stg/Prim.h - rts/js/environment.js - rts/js/mem.js - rts/js/verify.js - rts/linker/MachO.c - rts/rts.cabal - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - rts/wasm/scheduler.cmm - rts/win32/libHSghc-prim.def - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - testsuite/tests/bytecode/T24634/Makefile - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - testsuite/tests/codeGen/should_compile/T25166.stdout - testsuite/tests/codeGen/should_run/T23146/all.T - testsuite/tests/codeGen/should_run/T25364.hs - testsuite/tests/codeGen/should_run/T25364.stdout - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail07.stderr - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/driver/T20604/T20604.stdout - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/recomp24656/recomp24656.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - testsuite/tests/ghc-e/should_fail/T23663.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T23686.stderr - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/T11361a.stderr - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs → testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/javascript/Makefile - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLet10.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19892.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/perf/compiler/T11068.stdout - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/all.T - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TTH_top_splice.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/T12686a.stderr - testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23740i.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/T23153.stderr - testsuite/tests/rep-poly/T23154.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T1791/Makefile - testsuite/tests/rts/all.T - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/ipe/T24005/t24005.hs - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/Orphans.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - testsuite/tests/simd/should_run/all.T - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T21851_2.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23927.stdout - testsuite/tests/th/T24111.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.stderr - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_fail/T23734.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T23778.stderr - testsuite/tests/typecheck/should_fail/T24298.stderr - testsuite/tests/typecheck/should_fail/T24553.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T22510.stdout - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/T24396.stderr - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/Instances.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07c249c3a4e838ce3c99d0da6cb538301dd9b592...97d44a2d27ed068be2b27d201629b9d7543ad919 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07c249c3a4e838ce3c99d0da6cb538301dd9b592...97d44a2d27ed068be2b27d201629b9d7543ad919 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/111227a7/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 16:29:24 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sun, 09 Mar 2025 12:29:24 -0400 Subject: [Git][ghc/ghc][wip/T25647] Add forall quantifier to D Int newtype instance Message-ID: <67cdc1e474b76_74988e58b34988b8@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: b55940ba by Patrick at 2025-03-10T00:29:15+08:00 Add forall quantifier to D Int newtype instance - - - - - 1 changed file: - testsuite/tests/indexed-types/should_compile/T25611d.hs Changes: ===================================== testsuite/tests/indexed-types/should_compile/T25611d.hs ===================================== @@ -29,7 +29,7 @@ g :: Int -> N Int g x = MkN x data family D :: Type -> k -> k -newtype instance D Int (a::TYPE r) = MkD a +newtype instance forall r. D Int (a::TYPE r) = MkD a f1 :: Int# -> D Int Int# f1 x = MkD x View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b55940ba693bacee96da0a8f481697a599e79097 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b55940ba693bacee96da0a8f481697a599e79097 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/e43c50a8/attachment.html> From gitlab at gitlab.haskell.org Sun Mar 9 16:45:26 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 09 Mar 2025 12:45:26 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] 228 commits: Bump base, ghc-prim and template-haskell versions for 9.12 Message-ID: <67cdc5a6ceca_7498811d1b9410111d@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: 7f79257a by Zubin Duggal at 2024-12-29T13:04:35+00:00 Bump base, ghc-prim and template-haskell versions for 9.12 Also bump various submodules. (cherry picked from commit 6fc1fa3bdc8f53acdb19e47145789274060e498f) Bump base bound to 4.21 for GHC 9.12 (cherry picked from commit 473a201c6b55aea5bf9c9db0836a66ea1b657e04) Bump binary submodule to 0.8.9.2 (cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20) (cherry picked from commit ec2f40b45c1a3d82d17a2fc07e9ddb9218bc3940) Bump exceptions submodule to 0.10.9 (cherry picked from commit f5b5d1dc2d326368e5b173d622630d77f019b629) Bump file-io submodule to 0.1.4 (cherry picked from commit ba786681de6ac5fa49938e2cd71a5988f0f40d1f) bump os-string submodule to 2.0.6 (cherry picked from commit 3a7ffdbb832c045a55fd1ef24f546abdd9d9e30f) bump transformers submodule to 0.6.1.2 (cherry picked from commit 53b46fd437421b9e5a001edc6d1c427439d7714f) Bump directory submodule to v1.3.9.0 (cherry picked from commit 27dc2664c5404bb462092bb216c2c37b418fd1f8) Bump Win32 submodule to v2.14.1.0 (cherry picked from commit 80df88086180f5e39212b2feacf70a9d2b263c6c) Bump filepath submodule to 1.5.3.0 (cherry picked from commit 29bfae2c58a7303a081a6e7956b9f55e5faf3eeb) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 97b0dff223a6c4cc003adec448104c277f214645) Bump unix submodule to 2.8.6.0 (cherry picked from commit a1f56d6d6a99c100f88ef0a8b4d51298cf24a42d) Bump os-string submodule to 2.0.8 (cherry picked from commit 0121b76fd52ea0c0ce5d07085bc195666b63c625) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 962ceb50c8a6fc370e1c0a267f5cd5562a8cf759) Bump filepath submodule to 1.5.4.0 (cherry picked from commit 7bc6877fd5d41c6d5900678ad5e73ed30f366569) Bump file-io submodule to 0.1.5 (cherry picked from commit 9478b5aefe2877d58baf527edcf936dddbb955b7) Bump Cabal submodule to 3.14.1.0 (cherry picked from commit 5c9c3e3f79a79bb6d9a77a17c716dc3a0bcbd2aa) Bump directory submodule to 0.12.2.0 (cherry picked from commit 897906265db37af34ae2aaa016cec417f263407b) Bump array submodule for base bump Bump stm submodule for base bump Bump process submodule for base bump - - - - - f6079408 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix ghc-e005 after HasCallstack changes (cherry picked from commit 77f340a24561cea8a6f2ada296b3ea356ab1823c) - - - - - 3e10fa75 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Add haskeline to stage0Packages Otherwise we link against boot inplace and boot unix as boot haskeline depends on boot unix. (cherry picked from commit 90b493769ebdf3cd7be404d18462dc20ac1044df) - - - - - 4ad6aec4 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix TH changelog - - - - - ea3f7fd5 by Zubin Duggal at 2024-12-29T13:04:35+00:00 release: copy index.html from correct directory (cherry picked from commit cbfd0829cd61928976c9eb17ba4af18272466063) - - - - - fafb70db by Zubin Duggal at 2024-12-29T13:04:35+00:00 hadrian-multi: warn on unused imports os-string has redundant imports (cherry picked from commit dde3796be689ea57543936e22aa5ea4ef7ed995e) - - - - - c02b1e46 by Simon Peyton Jones at 2024-12-29T17:04:30-05:00 Fix in-scope set for CSE Ticket #25468 showed an assertion failure in CSE because a top-level Id was being used before it was defined. Reason: Note [Glomming] in GHC.Core.Opt.OccurAnal. Solution (used in many places): just put all the top-level bindings in scope at the beginning of CSE. Compile-time allocation wobbles up and down a tiny bit; geo mean is zero. But MultiLayerModulesTH_OneShot and hard_hole_fits increase (on some architectures only) by a bit oever 2% . I think these are just a random fluctuations. Metric Increase: MultiLayerModulesTH_OneShot hard_hole_fits - - - - - 559d4f84 by Krzysztof Gogolewski at 2024-12-30T11:53:19-05:00 Add tests for #23883 The issue has been fixed by commit f5d3e03c56ffc63. Only T23883a is the actual regression test, the remaining ones are tricky cases found during development of an independent fix !11313. - - - - - 278a53ee by Sergey Vinokurov at 2024-12-30T11:53:59-05:00 Update changelog for CLC proposal #107 (NonEmpty laziness) - - - - - f56558be by Matthew Pickering at 2025-01-07T13:53:03-05:00 warnings: Find out if a qualified name is in the interactive scope directly There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600 - - - - - 84155cdb by Simon Peyton Jones at 2025-01-07T13:53:40-05:00 Tidy up kcConDecls Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types - - - - - 6c12b6cf by Bryan Richter at 2025-01-07T18:15:02-05:00 Remove tmp files after toolchain check Fixes #25620 - - - - - 42826a89 by Cheng Shao at 2025-01-07T18:15:39-05:00 xxhash: bump to v0.8.3 - - - - - 185f17e4 by sheaf at 2025-01-07T18:16:15-05:00 Fix typo in GHC.Tc.Solver.Solve.runTcPluginsWanted - - - - - 23099752 by Luite Stegeman at 2025-01-08T00:33:33+01:00 Add flags for switching off speculative evaluation. We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284 - - - - - 0161badc by Ben Gamari at 2025-01-09T17:30:05-05:00 rts/printClosure: Print IPE information for thunks and functions This makes it considerably easier to grok the structure of the heap when IPE information is available. - - - - - 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz Goślinowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - a1523659 by Sven Tennie at 2025-03-09T11:27:00+01:00 WIP: Trying to get simd000 test green - - - - - 3686284e by Sven Tennie at 2025-03-09T11:27:00+01:00 WIP: simd000 - hacked further - - - - - 819c6a97 by Sven Tennie at 2025-03-09T11:27:00+01:00 WIP - - - - - 7aeaf265 by Sven Tennie at 2025-03-09T11:27:00+01:00 simd000 green - - - - - 79f3ad57 by Sven Tennie at 2025-03-09T11:27:00+01:00 simd001 green - - - - - 2a86757d by Sven Tennie at 2025-03-09T11:27:00+01:00 simd003 green - - - - - b5a8c135 by Sven Tennie at 2025-03-09T11:27:00+01:00 simd006 green - - - - - 42a65fd0 by Sven Tennie at 2025-03-09T11:27:01+01:00 simd007 green - - - - - 69c870c8 by Sven Tennie at 2025-03-09T11:27:01+01:00 simd008 && simd009 green - - - - - 08fb4763 by Sven Tennie at 2025-03-09T11:27:01+01:00 Fix int expr cases - - - - - 492bbb47 by Sven Tennie at 2025-03-09T11:27:01+01:00 Vector FMA - - - - - a149cc36 by Sven Tennie at 2025-03-09T11:27:01+01:00 Add TAB char operator - - - - - 1eaf5ac8 by Sven Tennie at 2025-03-09T11:27:01+01:00 Fix vector ccalls - - - - - c39210ca by Sven Tennie at 2025-03-09T11:27:01+01:00 Define YMM* and ZMM* - - - - - 98b31d69 by Sven Tennie at 2025-03-09T11:27:01+01:00 Add TODO - - - - - 7edec53e by Sven Tennie at 2025-03-09T11:27:01+01:00 Define registers for TrivColorable - - - - - b3509691 by Sven Tennie at 2025-03-09T11:27:01+01:00 Add TODOs - - - - - 0422c799 by Sven Tennie at 2025-03-09T11:27:01+01:00 Configure vector register width - - - - - e5577e02 by Sven Tennie at 2025-03-09T11:27:01+01:00 Configure vector register width - - - - - 56bc113c by Sven Tennie at 2025-03-09T11:27:01+01:00 Add documentation - - - - - 47982003 by Sven Tennie at 2025-03-09T11:27:01+01:00 Cleanup CodeGen - - - - - a10e72e4 by Sven Tennie at 2025-03-09T11:27:01+01:00 Add TODOs - - - - - c8e29ae2 by Sven Tennie at 2025-03-09T11:27:01+01:00 Add comment about freeReg for [X,Y,Z]MM - - - - - bde76118 by Sven Tennie at 2025-03-09T11:27:01+01:00 Define MAX_REAL_YMM_REG and MAX_REAL_ZMM_REG - - - - - f917497c by Sven Tennie at 2025-03-09T11:27:01+01:00 VID needs only one register; fix MO_V_Broadcast; refactor MO_V_Insert and MO_V_Insert - - - - - d6b62dbc by Sven Tennie at 2025-03-09T11:27:01+01:00 Add comment about vector registers in allocatableRegs - - - - - 6ec2e5d7 by Sven Tennie at 2025-03-09T11:27:01+01:00 Formatting - - - - - 3ebc18b5 by Sven Tennie at 2025-03-09T11:27:01+01:00 Adjust TODO - - - - - cabb4293 by Sven Tennie at 2025-03-09T11:27:01+01:00 Delete unused function - - - - - d8519beb by Sven Tennie at 2025-03-09T11:27:01+01:00 WIP: Use Format instead of Width in OpReg Operand Ints, floats and vectors are very different things. So, it is very helpful to know to which of this three an OpReg Operand relates. - - - - - 2314efa7 by Sven Tennie at 2025-03-09T11:27:01+01:00 Simplify VID - - - - - 0286eab9 by Sven Tennie at 2025-03-09T11:27:01+01:00 Simplify VMV - - - - - 25fa12db by Sven Tennie at 2025-03-09T11:27:01+01:00 Simplify VMERGE - - - - - 700031c2 by Sven Tennie at 2025-03-09T11:27:01+01:00 Simplify VSLIDEDOWN - - - - - 33a9eae6 by Sven Tennie at 2025-03-09T11:27:01+01:00 Simplify other vector instructions - - - - - 3a8d1b17 by Sven Tennie at 2025-03-09T11:27:01+01:00 Simplify VFMA - - - - - e8b09d33 by Sven Tennie at 2025-03-09T11:27:01+01:00 regUsageOfInstr with correct format - - - - - b7a17108 by Sven Tennie at 2025-03-09T11:27:01+01:00 Assert vector register width - - - - - 52f2cb77 by Sven Tennie at 2025-03-09T11:27:01+01:00 Combine float lit cases - - - - - 89bd07e1 by Sven Tennie at 2025-03-09T11:27:01+01:00 Tighten Vector Ppr constraints - - - - - 6f985d76 by Sven Tennie at 2025-03-09T11:27:01+01:00 Compile vector helper files with vector support - - - - - ee75f1c2 by Sven Tennie at 2025-03-09T11:27:01+01:00 -mriscv-vlen makes more sense to RISC-V people VLEN is a well defined term. - - - - - ff664b96 by Sven Tennie at 2025-03-09T11:27:01+01:00 Simplify expressions - - - - - 26caa069 by Sven Tennie at 2025-03-09T11:27:01+01:00 Fix MO_V_Extract and MO_VF_Extract - - - - - fc0309c7 by Sven Tennie at 2025-03-09T11:27:01+01:00 Assert register format in more places Also, fix it. - - - - - e6970a68 by Sven Tennie at 2025-03-09T11:27:02+01:00 mkSpillInstr: Refactor assertion - - - - - ab10ebcc by Sven Tennie at 2025-03-09T11:27:02+01:00 Better algorithm to inject vector config - - - - - 5f93bfa7 by Sven Tennie at 2025-03-09T11:27:02+01:00 cpuinfo.py: Provide RISC-V features - - - - - a4eff39f by Sven Tennie at 2025-03-09T11:27:02+01:00 Add TODOs - - - - - c3919932 by Sven Tennie at 2025-03-09T11:27:02+01:00 Set and check vector support in Haskell entry code We have to check this on the executing CPU (target) with access to DynFlags. - - - - - 84dfdba9 by Sven Tennie at 2025-03-09T15:42:35+01:00 Allow cpu_features for CROSS_EMULATR to be set - - - - - 17f38ba0 by Sven Tennie at 2025-03-09T15:44:21+01:00 Configure simd tests for RISC-V - - - - - 1403 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/upload_ghc_libs.py - compiler/CodeGen.Platform.h - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/RV64.hs - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToAsm/RV64/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Linear/RV64.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Config/CoreToStg/Prep.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Platform/Reg/Class.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Outputable.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/cbits/genSym.c - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/diagnostics-as-json-schema-1_0.json - docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/expected-undocumented-flags.txt - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using.rst - docs/users_guide/wasm.rst - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/bindist/Makefile - hadrian/cabal.project - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Warnings.hs - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/array - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/Data/Semigroup.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Exts.hs - libraries/base/src/System/Timeout.hs - libraries/binary - libraries/bytestring - libraries/deepseq - libraries/directory - libraries/exceptions - libraries/file-io - libraries/filepath - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-experimental/src/Data/Sum/Experimental.hs - libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/stack_big_ret.hs - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - libraries/ghc-internal/src/GHC/Internal/Char.hs - libraries/ghc-prim/GHC/Classes.hs → libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - libraries/ghc-internal/src/GHC/Internal/Err.hs - libraries/ghc-internal/src/GHC/Internal/Event.hs - libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - libraries/ghc-internal/src/GHC/Internal/Generics.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Int.hs - libraries/ghc-internal/src/GHC/Internal/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - libraries/ghc-internal/src/GHC/Internal/Ix.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - libraries/ghc-internal/src/GHC/Internal/Maybe.hs - libraries/ghc-internal/src/GHC/Internal/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-prim/GHC/Prim/Exception.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Read.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - libraries/ghc-internal/src/GHC/Internal/Records.hs - libraries/ghc-internal/src/GHC/Internal/Show.hs - libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - libraries/ghc-prim/GHC/Tuple.hs → libraries/ghc-internal/src/GHC/Internal/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - libraries/ghc-prim/GHC/Types.hs → libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghc-internal/src/GHC/Internal/Word.hs - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - libraries/terminfo - libraries/text - libraries/transformers - libraries/unix - linters/lint-codes/LintCodes/Static.hs - linters/lint-codes/Main.hs - m4/fp_settings.m4 - m4/ghc_toolchain.m4 - rts/CheckVectorSupport.c - rts/Exception.cmm - rts/Interpreter.c - rts/Interpreter.h - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/RtsMain.c - rts/RtsStartup.c - rts/RtsSymbols.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStdThunks.cmm - rts/configure.ac - rts/external-symbols.list.in - rts/include/RtsAPI.h - rts/include/Stg.h - rts/include/stg/MachRegs.h - rts/include/stg/MachRegs/riscv64.h - rts/include/stg/Prim.h - rts/js/environment.js - rts/js/mem.js - rts/js/verify.js - rts/linker/MachO.c - rts/rts.cabal - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - rts/wasm/scheduler.cmm - rts/win32/libHSghc-prim.def - rts/xxhash.h - testsuite/driver/cpu_features.py - testsuite/driver/cpuinfo.py - testsuite/driver/perf_notes.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - testsuite/tests/bytecode/T24634/Makefile - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - testsuite/tests/codeGen/should_compile/T25166.stdout - testsuite/tests/codeGen/should_run/T23146/all.T - testsuite/tests/codeGen/should_run/T25364.hs - testsuite/tests/codeGen/should_run/T25364.stdout - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - + testsuite/tests/core-to-stg/T25284/A.hs - + testsuite/tests/core-to-stg/T25284/B.hs - + testsuite/tests/core-to-stg/T25284/Cls.hs - + testsuite/tests/core-to-stg/T25284/Main.hs - + testsuite/tests/core-to-stg/T25284/T25284.stdout - + testsuite/tests/core-to-stg/T25284/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail07.stderr - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/driver/T20604/T20604.stdout - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/recomp24656/recomp24656.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - testsuite/tests/ghc-e/should_fail/T23663.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghc-e/should_run/ghc-e005.stderr - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T23686.stderr - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/T11361a.stderr - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs → testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/javascript/Makefile - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLet10.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19892.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/perf/compiler/T11068.stdout - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/all.T - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TTH_top_splice.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/T12686a.stderr - testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23740i.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/T23153.stderr - + testsuite/tests/rep-poly/T23153b.hs - testsuite/tests/rep-poly/T23154.stderr - + testsuite/tests/rep-poly/T23883a.hs - + testsuite/tests/rep-poly/T23883a.stderr - + testsuite/tests/rep-poly/T23883b.hs - + testsuite/tests/rep-poly/T23883b.stderr - + testsuite/tests/rep-poly/T23883c.hs - + testsuite/tests/rep-poly/T23883c.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rep-poly/all.T - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T1791/Makefile - testsuite/tests/rts/all.T - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/ipe/T24005/t24005.hs - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/Orphans.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - testsuite/tests/simd/should_run/all.T - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T21851_2.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23927.stdout - testsuite/tests/th/T24111.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.stderr - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_fail/T23734.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T23778.stderr - testsuite/tests/typecheck/should_fail/T24298.stderr - testsuite/tests/typecheck/should_fail/T24553.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T22510.stdout - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/T24396.stderr - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/Instances.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - utils/hsc2hs - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9554182bb43848207eaa26cf618c4eccb3a7dff3...17f38ba05f1372a981bd8d0eb6f60aaab879c87d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9554182bb43848207eaa26cf618c4eccb3a7dff3...17f38ba05f1372a981bd8d0eb6f60aaab879c87d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/b866fd4d/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 17:10:35 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 09 Mar 2025 13:10:35 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] simd013 test for RISC-V Message-ID: <67cdcb8bc99c2_74988133a828101523@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: eb03f43d by Sven Tennie at 2025-03-09T18:10:23+01:00 simd013 test for RISC-V - - - - - 2 changed files: - testsuite/tests/simd/should_run/all.T - testsuite/tests/simd/should_run/simd013C.c Changes: ===================================== testsuite/tests/simd/should_run/all.T ===================================== @@ -31,7 +31,8 @@ def riscvVlen(): # produce ABI-incompatible code, e.g. when compiling usage of YMM registers # with or without -mavx2. setTestOpts([ - when(arch('riscv64'), extra_hc_opts('-mriscv-vlen' + str(riscvVlen()) + " -opta=-march=rv64gv")) + # TODO: -optc and -opta should not be required, but provided by the GHC pipeline + when(arch('riscv64'), extra_hc_opts('-mriscv-vlen' + str(riscvVlen()) + " -optc=-march=rv64gv -opta=-march=rv64gv")) ]) test('simd_insert_baseline', [], compile_and_run, ['']) @@ -81,7 +82,9 @@ test('simd011', [ req_fma_cpu test('simd012', [], compile_and_run, ['']) test('simd013', [ req_c - , unless((arch('x86_64') or arch('riscv64')), skip) # because the C file uses architecture-dependent intrinsics + , unless((arch('x86_64') or arch('riscv64')), skip) + # ^ Because the C file uses architecture-dependent intrinsics. + # Requires GCC >= 14 on RISC-V. ], compile_and_run, ['simd013C.c']) test('simd014', ===================================== testsuite/tests/simd/should_run/simd013C.c ===================================== @@ -1,4 +1,4 @@ - +#if defined(__x86_64__) || defined(_M_X64) #include <immintrin.h> __m128d sub(__m128d x, __m128d y) @@ -10,3 +10,22 @@ __m128d add7(__m128d x1, __m128d x2, __m128d x3, __m128d x4, __m128d x5, __m128d { return _mm_add_pd(x1,_mm_add_pd(x2,_mm_add_pd(x3,_mm_add_pd(x4,_mm_add_pd(x5,_mm_add_pd(x6, x7)))))); } +#elif defined(__riscv_v) +#if __riscv_v_intrinsic >= 12000 +#include <riscv_vector.h> + +size_t vl = 2; + +vfloat64m1_t sub(vfloat64m1_t x, vfloat64m1_t y) +{ + return __riscv_vfsub(x,y,vl); +} + +vfloat64m1_t add7(vfloat64m1_t x1, vfloat64m1_t x2, vfloat64m1_t x3, vfloat64m1_t x4, vfloat64m1_t x5, vfloat64m1_t x6, vfloat64m1_t x7) +{ + return __riscv_vfadd(x1,__riscv_vfadd(x2,__riscv_vfadd(x3,__riscv_vfadd(x4,__riscv_vfadd(x5,__riscv_vfadd(x6, x7, vl),vl),vl),vl),vl),vl); +} +#else +#error "RISC-V vector target, but current intrinsics not supported." +#endif +#endif View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb03f43de920c454c4bbb639f1bffc7aa4f7ff47 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb03f43de920c454c4bbb639f1bffc7aa4f7ff47 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/f7f48544/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 19:26:32 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sun, 09 Mar 2025 15:26:32 -0400 Subject: [Git][ghc/ghc][wip/T25647] zonk_quant outer binders for families Message-ID: <67cdeb68404a_c31ec62090819852@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 5a03c614 by Patrick at 2025-03-10T03:26:20+08:00 zonk_quant outer binders for families - - - - - 3 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -3462,8 +3462,8 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty -- check there too! -- See Note [Generalising in tcTyFamInstEqnGuts] - ; dvs <- candidateQTyVarsOfType lhs_ty - ; qtvs <- quantifyTyVars skol_info dvs + ; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty + ; qtvs <- quantifyTyVars' outer_tvs skol_info dvs ; let final_tvs = scopedSort qtvs -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -975,8 +975,8 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity -- check there too! -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; dvs <- candidateQTyVarsOfType lhs_ty - ; qtvs <- quantifyTyVars skol_info dvs + ; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty + ; qtvs <- quantifyTyVars' outer_tvs skol_info dvs -- Have to make a same defaulting choice for reuslt kind here -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -81,6 +81,7 @@ module GHC.Tc.Utils.TcMType ( defaultTyVar, promoteMetaTyVarTo, promoteTyVarSet, quantifyTyVars, doNotQuantifyTyVars, zonkAndSkolemise, skolemiseQuantifiedTyVar, + quantifyTyVars', candidateQTyVarsOfType, candidateQTyVarsOfKind, candidateQTyVarsOfTypes, candidateQTyVarsOfKinds, @@ -1751,6 +1752,14 @@ quantifyTyVars :: SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] -- Already zonked -> TcM [TcTyVar] +quantifyTyVars = quantifyTyVars' [] + +quantifyTyVars' :: + [TcTyVar] + -> SkolemInfo + -> CandidatesQTvs -- See Note [Dependent type variables] + -- Already zonked + -> TcM [TcTyVar] -- See Note [quantifyTyVars] -- Can be given a mixture of TcTyVars and TyVars, in the case of -- associated type declarations. Also accepts covars, but *never* returns any. @@ -1758,9 +1767,9 @@ quantifyTyVars :: SkolemInfo -- invariants on CandidateQTvs, we do not have to filter out variables -- free in the environment here. Just quantify unconditionally, subject -- to the restrictions in Note [quantifyTyVars]. -quantifyTyVars skol_info dvs +quantifyTyVars' cvs skol_info dvs -- short-circuit common case - | isEmptyCandidates dvs + | isEmptyCandidates dvs && null cvs = do { traceTc "quantifyTyVars has nothing to quantify" empty ; return [] } @@ -1769,7 +1778,7 @@ quantifyTyVars skol_info dvs ( vcat [ text "dvs =" <+> ppr dvs ]) ; undefaulted <- defaultTyVars dvs - ; final_qtvs <- liftZonkM $ mapMaybeM zonk_quant undefaulted + ; final_qtvs <- liftZonkM $ mapMaybeM zonk_quant (undefaulted++cvs) ; traceTc "quantifyTyVars }" (vcat [ text "undefaulted:" <+> pprTyVars undefaulted View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5a03c614f5813aad25d8885dde8b43a3939e5cd9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5a03c614f5813aad25d8885dde8b43a3939e5cd9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/01d08e5b/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 9 21:14:46 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sun, 09 Mar 2025 17:14:46 -0400 Subject: [Git][ghc/ghc][wip/T25647] revert to old behaviour Message-ID: <67ce04c68d147_ef3fa311f287313e@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: b791749b by Patrick at 2025-03-10T05:14:36+08:00 revert to old behaviour - - - - - 1 changed file: - compiler/GHC/Rename/HsType.hs Changes: ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -1130,7 +1130,8 @@ bindHsOuterTyVarBndrs' bind_fam doc mb_cls implicit_vars outer_bndrs thing_insid , hso_ximplicit = implicit_vars' } where fam_implicit_vars = case bind_fam of - BindFam -> filterFreeVarsToBind (mapMaybe hsLTyVarLocName exp_bndrs) implicit_vars + -- BindFam -> filterFreeVarsToBind (mapMaybe hsLTyVarLocName exp_bndrs) implicit_vars + BindFam -> [] NotBindFam -> [] -- See Note [Term variable capture and implicit quantification] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b791749b6284f22c85df91bc55ed914d6bd2c00c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b791749b6284f22c85df91bc55ed914d6bd2c00c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/bb96e8ab/attachment.html> From gitlab at gitlab.haskell.org Sun Mar 9 23:08:44 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Sun, 09 Mar 2025 19:08:44 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/az/modifiers Message-ID: <67ce1f7c8c8a0_10bf7666bee449390@gitlab.mail> Alan Zimmerman pushed new branch wip/az/modifiers at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/modifiers You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/87d7e952/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 10 01:53:39 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Sun, 09 Mar 2025 21:53:39 -0400 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] look through XExpr ExpandedThingRn while inferring type of head Message-ID: <67ce46235ee8b_10bf761584f20569ec@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 96d01253 by Apoorv Ingle at 2025-03-09T20:52:24-05:00 look through XExpr ExpandedThingRn while inferring type of head - - - - - 1 changed file: - compiler/GHC/Tc/Gen/Head.hs Changes: ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -296,11 +296,11 @@ splitHsApps e = go e (top_ctxt 0 e) [] -- to initialise the argument splitting in 'go' -- See Note [AppCtxt] - top_ctxt n (HsPar _ fun) = top_lctxt n fun - top_ctxt n (HsPragE _ _ fun) = top_lctxt n fun - top_ctxt n (HsAppType _ fun _) = top_lctxt (n+1) fun - top_ctxt n (HsApp _ fun _) = top_lctxt (n+1) fun - top_ctxt n other_fun = VACall other_fun n noSrcSpan + top_ctxt n (HsPar _ fun) = top_lctxt n fun + top_ctxt n (HsPragE _ _ fun) = top_lctxt n fun + top_ctxt n (HsAppType _ fun _) = top_lctxt (n+1) fun + top_ctxt n (HsApp _ fun _) = top_lctxt (n+1) fun + top_ctxt n other_fun = VACall other_fun n noSrcSpan top_lctxt :: Int -> LHsExpr GhcRn -> AppCtxt top_lctxt n (L _ fun) = top_ctxt n fun @@ -539,16 +539,21 @@ tcInferAppHead_maybe :: HsExpr GhcRn -- Returns Nothing for a complicated head tcInferAppHead_maybe fun = case fun of - HsVar _ nm -> Just <$> tcInferId nm - XExpr (HsRecSelRn f) -> Just <$> tcInferRecSelId f - ExprWithTySig _ e hs_ty -> Just <$> tcExprWithSig e hs_ty - HsOverLit _ lit -> Just <$> tcInferOverLit lit - _ -> return Nothing + HsVar _ nm -> Just <$> tcInferId nm + XExpr (HsRecSelRn f) -> Just <$> tcInferRecSelId f + XExpr (ExpandedThingRn _ e) -> tcInferAppHead_maybe e + XExpr (PopErrCtxt e) -> tcInferAppHead_maybe e + ExprWithTySig _ e hs_ty -> Just <$> tcExprWithSig e hs_ty + HsOverLit _ lit -> Just <$> tcInferOverLit lit + _ -> return Nothing addHeadCtxt :: AppCtxt -> TcM a -> TcM a -addHeadCtxt fun_ctxt thing_inside = setSrcSpan fun_loc thing_inside - where - fun_loc = appCtxtLoc fun_ctxt +addHeadCtxt fun_ctxt thing_inside + | not (isGoodSrcSpan fun_loc) -- noSrcSpan => no arguments + = thing_inside -- => context is already set + | otherwise + = setSrcSpan fun_loc thing_inside + where fun_loc = appCtxtLoc fun_ctxt {- ********************************************************************* @@ -1246,4 +1251,5 @@ addExprCtxt e thing_inside -- when we don't want to say "In the expression: _", -- because it is mentioned in the error message itself HsUnboundVar {} -> thing_inside + XExpr (ExpandedThingRn {}) -> thing_inside _ -> addErrCtxt (ExprCtxt e) thing_inside View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/96d01253fe0189af54aa2082e94362ea4c437013 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/96d01253fe0189af54aa2082e94362ea4c437013 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/aa9ce510/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 02:13:50 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Sun, 09 Mar 2025 22:13:50 -0400 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] 43 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67ce4ade94246_10bf7618bc8b457478@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 9089a740 by Apoorv Ingle at 2025-03-09T21:13:30-05:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail - - - - - a86f1d51 by Apoorv Ingle at 2025-03-09T21:13:31-05:00 simplify data structures. remove doTcApp and applicative stmt fail blocks do not refer stmts - - - - - a0ecfa03 by Simon Peyton Jones at 2025-03-09T21:13:31-05:00 - Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed. - Make `tcExpr` take a `Maybe HsThingRn` which will be passed on to tcApp and used by splitHsApps to determine a more accurate `AppCtx` - `tcXExpr` is less hacky now This reverts commit 9648167a936a329d3876de71235f476e5836ddf8. - - - - - 81d3c685 by Apoorv Ingle at 2025-03-09T21:13:32-05:00 do not look through HsExpansion applications - - - - - b7d71f12 by Apoorv Ingle at 2025-03-09T21:13:32-05:00 kill OrigPat and remove HsThingRn From VAExpansion - - - - - 7988e43b by Apoorv Ingle at 2025-03-09T21:13:32-05:00 look through XExpr ExpandedThingRn while inferring type of head - - - - - 61752a8c by Apoorv Ingle at 2025-03-09T21:13:32-05:00 always set in generated code after stepping inside a ExpandedThingRn - - - - - 207 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Unique.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/include/RtsAPI.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/T16135.hs - − testsuite/tests/ado/T16135.stderr - + testsuite/tests/ado/T24406.hs - testsuite/tests/ado/ado002.stderr - testsuite/tests/ado/ado003.stderr - testsuite/tests/ado/ado004.stderr - testsuite/tests/ado/all.T - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/determinism/determ021/determ021.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci.debugger/scripts/break029.script - testsuite/tests/ghci.debugger/scripts/break029.stdout - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/hiefile/should_run/T23540.stdout - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96d01253fe0189af54aa2082e94362ea4c437013...61752a8cdeeab4ff6166c8c8f38de204782b2cf4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96d01253fe0189af54aa2082e94362ea4c437013...61752a8cdeeab4ff6166c8c8f38de204782b2cf4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250309/07fb6dbe/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 07:36:16 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 10 Mar 2025 03:36:16 -0400 Subject: [Git][ghc/ghc] Deleted branch wip/wasm-jsffi-revamp Message-ID: <67ce9670b0079_1c0f38c5d50835de@gitlab.mail> Cheng Shao deleted branch wip/wasm-jsffi-revamp at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/532536cc/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 10 07:36:42 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 10 Mar 2025 03:36:42 -0400 Subject: [Git][ghc/ghc] Deleted branch wip/wasm-dyld-no-type-reflection Message-ID: <67ce968a3d58b_1c0f38c5fd0837eb@gitlab.mail> Cheng Shao deleted branch wip/wasm-dyld-no-type-reflection at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/5134ac21/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 10 08:48:04 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 10 Mar 2025 04:48:04 -0400 Subject: [Git][ghc/ghc][wip/nfdata-forcing] 11 commits: iface: Store flags in interface files Message-ID: <67cea744885a8_1d1ef536b780624ec@gitlab.mail> Matthew Pickering pushed to branch wip/nfdata-forcing at Glasgow Haskell Compiler / GHC Commits: 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 759aa06c by Matthew Pickering at 2025-03-10T08:47:56+00:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - efdf5e79 by Matthew Pickering at 2025-03-10T08:47:56+00:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - d26a9ab1 by Matthew Pickering at 2025-03-10T08:47:57+00:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time on disk. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory usages too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface. This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 108 changed files: - compiler/GHC.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - libraries/ghc-boot/GHC/Serialized.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c84e65f4b0b4c70fb822ced556089711a3eaceec...d26a9ab17c42d72c71e864948ec9c6a8e012e59d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c84e65f4b0b4c70fb822ced556089711a3eaceec...d26a9ab17c42d72c71e864948ec9c6a8e012e59d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/bcd664a9/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 10:04:08 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Mar 2025 06:04:08 -0400 Subject: [Git][ghc/ghc][wip/romes/better-main] driver: Move DynFlags consistency fixes off Main Message-ID: <67ceb9181801b_1eb37c16e78424635@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/better-main at Glasgow Haskell Compiler / GHC Commits: 7c6595fb by Rodrigo Mesquita at 2025-03-10T10:03:45+00:00 driver: Move DynFlags consistency fixes off Main These consistency fixes found in Main.hs are required for the proper functioning of the compiler and should live together with all remaining fixes in `makeDynFlagsConsistent`. This is especially relevant to GHC applications that shouldn't have to copy/fix themselves possibly inconsistent DynFlags. - - - - - 2 changed files: - compiler/GHC/Driver/Session.hs - ghc/Main.hs Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3587,7 +3587,38 @@ makeDynFlagsConsistent dflags | LinkMergedObj <- ghcLink dflags , Nothing <- outputFile dflags - = pgmError "--output must be specified when using --merge-objs" + = pgmError "--output must be specified when using --merge-objs" + +#if MIN_VERSION_GLASGOW_HASKELL(9,13,0,0) + -- When we do ghci, force using dyn ways if the target RTS linker + -- only supports dynamic code + | LinkInMemory <- ghcLink dflags + , sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags + , not (dynamicNow dflags) || not (gopt Opt_ExternalInterpreter dflags) + = flip loop "Forcing dyn ways, because doing GHCi and target RTS linker only supports dynamic code" $ + setDynamicNow $ + -- See checkOptions below, -fexternal-interpreter is + -- required when using --interactive with a non-standard + -- way (-prof, -static, or -dynamic). + setGeneralFlag' Opt_ExternalInterpreter $ + -- Use .o for dynamic object, otherwise it gets dropped + -- with "Warning: ignoring unrecognised input", see + -- objish_suffixes + dflags { dynObjectSuf_ = objectSuf dflags } +#endif + + | backendNeedsFullWays (backend dflags) + , not (gopt Opt_ExternalInterpreter dflags) + , targetWays_ dflags /= hostFullWays + = flip loop "Enabling options for all ways, required by the backend" $ + let dflags_a = dflags { targetWays_ = hostFullWays } + dflags_b = foldl gopt_set dflags_a + $ concatMap (wayGeneralFlags platform) + hostFullWays + dflags_c = foldl gopt_unset dflags_b + $ concatMap (wayUnsetGeneralFlags platform) + hostFullWays + in dflags_c | otherwise = (dflags, mempty) where loc = mkGeneralSrcSpan (fsLit "when making flags consistent") ===================================== ghc/Main.hs ===================================== @@ -224,41 +224,9 @@ main' postLoadMode units dflags0 args flagWarnings = do -- The rest of the arguments are "dynamic" -- Leftover ones are presumably files - (dflags3', fileish_args, dynamicFlagWarnings) <- + (dflags4, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags logger2 dflags2 args' - -- When we do ghci, force using dyn ways if the target RTS linker - -- only supports dynamic code - let dflags3 - | LinkInMemory <- link, - sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags3' - = setDynamicNow $ - -- See checkOptions below, -fexternal-interpreter is - -- required when using --interactive with a non-standard - -- way (-prof, -static, or -dynamic). - setGeneralFlag' Opt_ExternalInterpreter $ - -- Use .o for dynamic object, otherwise it gets dropped - -- with "Warning: ignoring unrecognised input", see - -- objish_suffixes - dflags3' { dynObjectSuf_ = objectSuf dflags3' } - | otherwise - = dflags3' - - let dflags4 = if backendNeedsFullWays bcknd && - not (gopt Opt_ExternalInterpreter dflags3) - then - let platform = targetPlatform dflags3 - dflags3a = dflags3 { targetWays_ = hostFullWays } - dflags3b = foldl gopt_set dflags3a - $ concatMap (wayGeneralFlags platform) - hostFullWays - dflags3c = foldl gopt_unset dflags3b - $ concatMap (wayUnsetGeneralFlags platform) - hostFullWays - in dflags3c - else - dflags3 - let logger4 = setLogFlags logger2 (initLogFlags dflags4) GHC.prettyPrintGhcErrors logger4 $ do View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c6595fbb2b897ef698fa140566bb73e2e091db4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c6595fbb2b897ef698fa140566bb73e2e091db4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/145be931/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 10:15:54 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 10 Mar 2025 06:15:54 -0400 Subject: [Git][ghc/ghc][wip/nfdata-forcing] interfaces: Ensure that forceModIface deeply forces a ModIface Message-ID: <67cebbda15af1_1eb37c471698251f2@gitlab.mail> Matthew Pickering pushed to branch wip/nfdata-forcing at Glasgow Haskell Compiler / GHC Commits: 4dae0101 by Matthew Pickering at 2025-03-10T10:15:35+00:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time on disk. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory usages too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface. This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - libraries/ghc-boot/GHC/Serialized.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Core.hs ===================================== @@ -120,6 +120,8 @@ import Data.List.NonEmpty (nonEmpty) import qualified Data.List.NonEmpty as NE import Data.Word +import Control.DeepSeq + infixl 4 `mkApps`, `mkTyApps`, `mkVarApps`, `App`, `mkCoApps` -- Left associative, so that we can say (f `mkTyApps` xs `mkVarApps` ys) @@ -1185,6 +1187,10 @@ instance Binary IsOrphan where n <- get bh return $ NotOrphan n +instance NFData IsOrphan where + rnf IsOrphan = () + rnf (NotOrphan n) = rnf n + {- Note [Orphans] ~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Coercion/Axiom.hs ===================================== @@ -58,6 +58,7 @@ import GHC.Types.SrcLoc import qualified Data.Data as Data import Data.Array import Data.List ( mapAccumL ) +import Control.DeepSeq {- Note [Coercion axiom branches] @@ -559,6 +560,11 @@ instance Binary Role where 3 -> return Phantom _ -> panic ("get Role " ++ show tag) +instance NFData Role where + rnf Nominal = () + rnf Representational = () + rnf Phantom = () + {- ************************************************************************ * * ===================================== compiler/GHC/Core/DataCon.hs ===================================== @@ -112,6 +112,7 @@ import qualified Data.ByteString.Lazy as LBS import qualified Data.Data as Data import Data.Char import Data.List( find ) +import Control.DeepSeq {- Note [Data constructor representation] @@ -1075,6 +1076,16 @@ instance Binary SrcUnpackedness where 1 -> return SrcUnpack _ -> return NoSrcUnpack +instance NFData SrcStrictness where + rnf SrcLazy = () + rnf SrcStrict = () + rnf NoSrcStrict = () + +instance NFData SrcUnpackedness where + rnf SrcNoUnpack = () + rnf SrcUnpack = () + rnf NoSrcUnpack = () + -- | Compare strictness annotations eqHsBang :: HsImplBang -> HsImplBang -> Bool eqHsBang HsLazy HsLazy = True ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -181,6 +181,7 @@ import GHC.Settings.Constants import GHC.Utils.Misc import GHC.Types.Unique.Set import GHC.Unit.Module +import Control.DeepSeq import Language.Haskell.Syntax.Basic (FieldLabelString(..)) @@ -2916,6 +2917,10 @@ instance Binary Injectivity where _ -> do { xs <- get bh ; return (Injective xs) } } +instance NFData Injectivity where + rnf NotInjective = () + rnf (Injective xs) = rnf xs + -- | Returns whether or not this 'TyCon' is definite, or a hole -- that may be filled in at some later point. See Note [Skolem abstract data] tyConSkolem :: TyCon -> Bool ===================================== compiler/GHC/Data/Strict.hs ===================================== @@ -22,10 +22,15 @@ import GHC.Prelude hiding (Maybe(..), Either(..)) import Control.Applicative import Data.Semigroup import Data.Data +import Control.DeepSeq data Maybe a = Nothing | Just !a deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data) +instance NFData a => NFData (Maybe a) where + rnf Nothing = () + rnf (Just x) = rnf x + fromMaybe :: a -> Maybe a -> a fromMaybe d Nothing = d fromMaybe _ (Just x) = x ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -111,7 +111,5 @@ instance Outputable ModIfaceSelfRecomp where ])] instance NFData ModIfaceSelfRecomp where - -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so - -- I left it as a shallow force. rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -539,6 +539,14 @@ instance Binary IfaceLFInfo where 4 -> pure IfLFUnlifted _ -> panic "Invalid byte" +instance NFData IfaceLFInfo where + rnf = \case + IfLFReEntrant arity -> rnf arity + IfLFThunk updatable mb_fun -> rnf updatable `seq` rnf mb_fun + IfLFCon con -> rnf con + IfLFUnknown fun_flag -> rnf fun_flag + IfLFUnlifted -> () + {- Note [Versioning of instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2767,6 +2775,10 @@ getUnfoldingCache bh = do return (UnfoldingCache { uf_is_value = hnf, uf_is_conlike = conlike , uf_is_work_free = wf, uf_expandable = exp }) +seqUnfoldingCache :: IfUnfoldingCache -> () +seqUnfoldingCache (UnfoldingCache hnf conlike wf exp) = + rnf hnf `seq` rnf conlike `seq` rnf wf `seq` rnf exp `seq` () + infixl 9 .<<|. (.<<|.) :: (Num a, Bits a) => a -> Bool -> a x .<<|. b = (if b then (`setBit` 0) else id) (x `shiftL` 1) @@ -2837,12 +2849,10 @@ instance Binary IfaceExpr where putByte bh 13 put_ bh a put_ bh b - put_ bh (IfaceLitRubbish TypeLike r) = do + put_ bh (IfaceLitRubbish torc r) = do putByte bh 14 put_ bh r - put_ bh (IfaceLitRubbish ConstraintLike r) = do - putByte bh 15 - put_ bh r + put_ bh torc get bh = do h <- getByte bh case h of @@ -2886,9 +2896,8 @@ instance Binary IfaceExpr where b <- get bh return (IfaceECase a b) 14 -> do r <- get bh - return (IfaceLitRubbish TypeLike r) - 15 -> do r <- get bh - return (IfaceLitRubbish ConstraintLike r) + torc <- get bh + return (IfaceLitRubbish torc r) _ -> panic ("get IfaceExpr " ++ show h) instance Binary IfaceTickish where @@ -3047,31 +3056,31 @@ instance NFData IfaceDecl where rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 IfaceData f1 f2 f3 f4 f5 f6 f7 f8 f9 -> - f1 `seq` seqList f2 `seq` f3 `seq` f4 `seq` f5 `seq` + rnf f1 `seq` seqList f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` rnf f9 IfaceSynonym f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 IfaceFamily f1 f2 f3 f4 f5 f6 -> - rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 `seq` f6 `seq` () + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` () IfaceClass f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 IfaceAxiom nm tycon role ax -> rnf nm `seq` rnf tycon `seq` - role `seq` + rnf role `seq` rnf ax IfacePatSyn f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 -> - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` f6 `seq` - rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` f11 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 `seq` () instance NFData IfaceAxBranch where rnf (IfaceAxBranch f1 f2 f3 f4 f5 f6 f7) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` rnf f7 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 instance NFData IfaceClassBody where rnf = \case @@ -3089,7 +3098,7 @@ instance NFData IfaceAT where rnf (IfaceAT f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceClassOp where - rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` f3 `seq` () + rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` () instance NFData IfaceTyConParent where rnf = \case @@ -3104,14 +3113,17 @@ instance NFData IfaceConDecls where instance NFData IfaceConDecl where rnf (IfCon f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` - rnf f7 `seq` rnf f8 `seq` f9 `seq` rnf f10 `seq` rnf f11 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 instance NFData IfaceSrcBang where - rnf (IfSrcBang f1 f2) = f1 `seq` f2 `seq` () + rnf (IfSrcBang f1 f2) = rnf f1 `seq` rnf f2 `seq` () instance NFData IfaceBang where - rnf x = x `seq` () + rnf IfNoBang = () + rnf IfStrict = () + rnf IfUnpack = () + rnf (IfUnpackCo co) = rnf co instance NFData IfaceIdDetails where rnf = \case @@ -3125,23 +3137,22 @@ instance NFData IfaceInfoItem where rnf = \case HsArity a -> rnf a HsDmdSig str -> seqDmdSig str - HsInline p -> p `seq` () -- TODO: seq further? + HsInline p -> rnf p `seq` () HsUnfold b unf -> rnf b `seq` rnf unf HsNoCafRefs -> () - HsCprSig cpr -> cpr `seq` () - HsLFInfo lf_info -> lf_info `seq` () -- TODO: seq further? - HsTagSig sig -> sig `seq` () + HsCprSig cpr -> seqCprSig cpr `seq` () + HsLFInfo lf_info -> rnf lf_info `seq` () + HsTagSig sig -> seqTagSig sig `seq` () instance NFData IfGuidance where rnf = \case IfNoGuidance -> () - IfWhen a b c -> a `seq` b `seq` c `seq` () + IfWhen a b c -> rnf a `seq` rnf b `seq` rnf c `seq` () instance NFData IfaceUnfolding where rnf = \case - IfCoreUnfold src cache guidance expr -> src `seq` cache `seq` rnf guidance `seq` rnf expr + IfCoreUnfold src cache guidance expr -> rnf src `seq` seqUnfoldingCache cache `seq` rnf guidance `seq` rnf expr IfDFunUnfold bndrs exprs -> rnf bndrs `seq` rnf exprs - -- See Note [UnfoldingCache] in GHC.Core for why it suffices to merely `seq` on cache instance NFData IfaceExpr where rnf = \case @@ -3152,13 +3163,13 @@ instance NFData IfaceExpr where IfaceTuple sort exprs -> sort `seq` rnf exprs IfaceLam bndr expr -> rnf bndr `seq` rnf expr IfaceApp e1 e2 -> rnf e1 `seq` rnf e2 - IfaceCase e nm alts -> rnf e `seq` nm `seq` rnf alts + IfaceCase e nm alts -> rnf e `seq` rnf nm `seq` rnf alts IfaceECase e ty -> rnf e `seq` rnf ty IfaceLet bind e -> rnf bind `seq` rnf e IfaceCast e co -> rnf e `seq` rnf co - IfaceLit l -> l `seq` () -- FIXME - IfaceLitRubbish tc r -> tc `seq` rnf r `seq` () - IfaceFCall fc ty -> fc `seq` rnf ty + IfaceLit l -> rnf l `seq` () + IfaceLitRubbish tc r -> rnf tc `seq` rnf r `seq` () + IfaceFCall fc ty -> rnf fc `seq` rnf ty IfaceTick tick e -> rnf tick `seq` rnf e instance NFData IfaceAlt where @@ -3192,22 +3203,22 @@ instance NFData IfaceFamTyConFlav where instance NFData IfaceTickish where rnf = \case IfaceHpcTick m i -> rnf m `seq` rnf i - IfaceSCC cc b1 b2 -> cc `seq` rnf b1 `seq` rnf b2 - IfaceSource src str -> src `seq` rnf str + IfaceSCC cc b1 b2 -> rnf cc `seq` rnf b1 `seq` rnf b2 + IfaceSource src str -> rnf src `seq` rnf str IfaceBreakpoint m i fvs -> rnf m `seq` rnf i `seq` rnf fvs instance NFData IfaceConAlt where rnf = \case IfaceDefaultAlt -> () IfaceDataAlt nm -> rnf nm - IfaceLitAlt lit -> lit `seq` () + IfaceLitAlt lit -> rnf lit `seq` () instance NFData IfaceCompleteMatch where rnf (IfaceCompleteMatch f1 mtc) = rnf f1 `seq` rnf mtc instance NFData IfaceRule where rnf (IfaceRule f1 f2 f3 f4 f5 f6 f7 f8) = - rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` f8 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` () instance NFData IfaceDefault where rnf (IfaceDefault f1 f2 f3) = @@ -3215,11 +3226,11 @@ instance NFData IfaceDefault where instance NFData IfaceFamInst where rnf (IfaceFamInst f1 f2 f3 f4) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` () instance NFData IfaceClsInst where rnf (IfaceClsInst f1 f2 f3 f4 f5 f6) = - f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` f5 `seq` rnf f6 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 instance NFData IfaceWarnings where rnf = \case @@ -3227,12 +3238,12 @@ instance NFData IfaceWarnings where IfWarnSome vs ds -> rnf vs `seq` rnf ds instance NFData IfaceWarningTxt where - rnf = \case - IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 - IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 + rnf = \case + IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 + IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 instance NFData IfaceStringLiteral where - rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 + rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceAnnotation where - rnf (IfaceAnnotation f1 f2) = f1 `seq` f2 `seq` () + rnf (IfaceAnnotation f1 f2) = rnf f1 `seq` rnf f2 `seq` () ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -2577,6 +2577,11 @@ instance Binary (DefMethSpec IfaceType) where 0 -> return VanillaDM _ -> do { t <- get bh; return (GenericDM t) } +instance NFData (DefMethSpec IfaceType) where + rnf = \case + VanillaDM -> () + GenericDM t -> rnf t + instance NFData IfaceType where rnf = \case IfaceFreeTyVar f1 -> f1 `seq` () ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -148,6 +148,7 @@ import qualified GHC.Boot.TH.Ppr as TH #if defined(HAVE_INTERNAL_INTERPRETER) import Unsafe.Coerce ( unsafeCoerce ) import GHC.Desugar ( AnnotationWrapper(..) ) +import Control.DeepSeq #endif import Control.Monad @@ -1039,11 +1040,7 @@ convertAnnotationWrapper fhv = do -- annotation are exposed at this point. This is also why we are -- doing all this stuff inside the context of runMeta: it has the -- facilities to deal with user error in a meta-level expression - seqSerialized serialized `seq` serialized - --- | Force the contents of the Serialized value so weknow it doesn't contain any bottoms -seqSerialized :: Serialized -> () -seqSerialized (Serialized the_type bytes) = the_type `seq` bytes `seqList` () + rnf serialized `seq` serialized #endif ===================================== compiler/GHC/Types/Annotations.hs ===================================== @@ -31,7 +31,7 @@ import Control.Monad import Data.Maybe import Data.Typeable import Data.Word ( Word8 ) - +import Control.DeepSeq -- | Represents an annotation after it has been sufficiently desugared from -- it's initial form of 'GHC.Hs.Decls.AnnDecl' @@ -71,6 +71,10 @@ instance Binary name => Binary (AnnTarget name) where 0 -> liftM NamedTarget $ get bh _ -> liftM ModuleTarget $ get bh +instance NFData name => NFData (AnnTarget name) where + rnf (NamedTarget n) = rnf n + rnf (ModuleTarget m) = rnf m + instance Outputable Annotation where ppr ann = ppr (ann_target ann) ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -529,6 +529,10 @@ instance Binary FunctionOrData where 1 -> return IsData _ -> panic "Binary FunctionOrData" +instance NFData FunctionOrData where + rnf IsFunction = () + rnf IsData = () + {- ************************************************************************ * * @@ -871,6 +875,9 @@ data OverlapMode -- See Note [Rules for instance lookup] in GHC.Core.InstEnv instance Outputable OverlapFlag where ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag) +instance NFData OverlapFlag where + rnf (OverlapFlag mode safe) = rnf mode `seq` rnf safe + instance Outputable OverlapMode where ppr (NoOverlap _) = empty ppr (Overlappable _) = text "[overlappable]" @@ -879,6 +886,14 @@ instance Outputable OverlapMode where ppr (Incoherent _) = text "[incoherent]" ppr (NonCanonical _) = text "[noncanonical]" +instance NFData OverlapMode where + rnf (NoOverlap s) = rnf s + rnf (Overlappable s) = rnf s + rnf (Overlapping s) = rnf s + rnf (Overlaps s) = rnf s + rnf (Incoherent s) = rnf s + rnf (NonCanonical s) = rnf s + instance Binary OverlapMode where put_ bh (NoOverlap s) = putByte bh 0 >> put_ bh s put_ bh (Overlaps s) = putByte bh 1 >> put_ bh s @@ -1860,6 +1875,14 @@ instance Binary Activation where ab <- get bh return (ActiveAfter src ab) +instance NFData Activation where + rnf = \case + AlwaysActive -> () + NeverActive -> () + ActiveBefore src aa -> rnf src `seq` rnf aa + ActiveAfter src ab -> rnf src `seq` rnf ab + FinalActive -> () + instance Outputable RuleMatchInfo where ppr ConLike = text "CONLIKE" ppr FunLike = text "FUNLIKE" @@ -1872,6 +1895,11 @@ instance Binary RuleMatchInfo where if h == 1 then return ConLike else return FunLike +instance NFData RuleMatchInfo where + rnf = \case + ConLike -> () + FunLike -> () + instance Outputable InlineSpec where ppr (Inline src) = text "INLINE" <+> pprWithSourceText src empty ppr (NoInline src) = text "NOINLINE" <+> pprWithSourceText src empty @@ -1906,6 +1934,14 @@ instance Binary InlineSpec where s <- get bh return (Opaque s) +instance NFData InlineSpec where + rnf = \case + Inline s -> rnf s + NoInline s -> rnf s + Inlinable s -> rnf s + Opaque s -> rnf s + NoUserInlinePrag -> () + instance Outputable InlinePragma where ppr = pprInline @@ -1925,6 +1961,9 @@ instance Binary InlinePragma where d <- get bh return (InlinePragma s a b c d) +instance NFData InlinePragma where + rnf (InlinePragma s a b c d) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c `seq` rnf d + -- | Outputs string for pragma name for any of INLINE/INLINABLE/NOINLINE. This -- differs from the Outputable instance for the InlineSpec type where the pragma -- name string as well as the accompanying SourceText (if any) is printed. @@ -2017,6 +2056,13 @@ instance Binary UnfoldingSource where 2 -> return StableSystemSrc _ -> return VanillaSrc +instance NFData UnfoldingSource where + rnf = \case + CompulsorySrc -> () + StableUserSrc -> () + StableSystemSrc -> () + VanillaSrc -> () + instance Outputable UnfoldingSource where ppr CompulsorySrc = text "Compulsory" ppr StableUserSrc = text "StableUser" @@ -2161,6 +2207,19 @@ data TypeOrConstraint = TypeLike | ConstraintLike deriving( Eq, Ord, Data ) +instance Binary TypeOrConstraint where + put_ bh = \case + TypeLike -> putByte bh 0 + ConstraintLike -> putByte bh 1 + get bh = getByte bh >>= \case + 0 -> pure TypeLike + 1 -> pure ConstraintLike + _ -> panic "TypeOrConstraint.get: invalid value" + +instance NFData TypeOrConstraint where + rnf = \case + TypeLike -> () + ConstraintLike -> () {- ********************************************************************* * * ===================================== compiler/GHC/Types/CostCentre.hs ===================================== @@ -36,6 +36,7 @@ import GHC.Utils.Outputable import GHC.Types.SrcLoc import GHC.Data.FastString import GHC.Types.CostCentre.State +import Control.DeepSeq import Data.Data @@ -395,6 +396,21 @@ instance Binary CostCentre where -- CostCentre in the original module, it is not used by importing -- modules. +instance NFData CostCentre where + rnf (NormalCC aa ab ac ad) = rnf aa `seq` rnf ab `seq` rnf ac `seq` rnf ad + rnf (AllCafsCC ae ad) = rnf ae `seq` rnf ad + +instance NFData CCFlavour where + rnf CafCC = () + rnf (IndexedCC flav i) = rnf flav `seq` rnf i + +instance NFData IndexedCCFlavour where + rnf ExprCC = () + rnf DeclCC = () + rnf HpcCC = () + rnf LateCC = () + rnf CallerCC = () + getAllCAFsCC :: Module -> (CostCentre, CostCentreStack) getAllCAFsCC this_mod = let ===================================== compiler/GHC/Types/CostCentre/State.hs ===================================== @@ -15,6 +15,7 @@ import GHC.Data.FastString.Env import Data.Data import GHC.Utils.Binary +import Control.DeepSeq -- | Per-module state for tracking cost centre indices. -- @@ -29,6 +30,9 @@ newCostCentreState = CostCentreState emptyFsEnv newtype CostCentreIndex = CostCentreIndex { unCostCentreIndex :: Int } deriving (Eq, Ord, Data, Binary) +instance NFData CostCentreIndex where + rnf (CostCentreIndex i) = rnf i + -- | Get a new index for a given cost centre name. getCCIndex :: FastString -> CostCentreState ===================================== compiler/GHC/Types/ForeignCall.hs ===================================== @@ -30,6 +30,8 @@ import GHC.Types.SourceText ( SourceText, pprWithSourceText ) import Data.Char import Data.Data +import Control.DeepSeq (NFData(..)) + {- ************************************************************************ * * @@ -344,3 +346,31 @@ instance Binary Header where get bh = do s <- get bh h <- get bh return (Header s h) + +instance NFData ForeignCall where + rnf (CCall c) = rnf c + +instance NFData Safety where + rnf PlaySafe = () + rnf PlayInterruptible = () + rnf PlayRisky = () + +instance NFData CCallSpec where + rnf (CCallSpec t c s) = rnf t `seq` rnf c `seq` rnf s + +instance NFData CCallTarget where + rnf (StaticTarget s a b c) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c + rnf DynamicTarget = () + +instance NFData CCallConv where + rnf CCallConv = () + rnf StdCallConv = () + rnf PrimCallConv = () + rnf CApiConv = () + rnf JavaScriptCallConv = () + +instance NFData CType where + rnf (CType s mh fs) = rnf s `seq` rnf mh `seq` rnf fs + +instance NFData Header where + rnf (Header s h) = rnf s `seq` rnf h ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -84,6 +84,7 @@ import Data.Char import Data.Data ( Data ) import GHC.Exts( isTrue#, dataToTag#, (<#) ) import Numeric ( fromRat ) +import Control.DeepSeq {- ************************************************************************ @@ -204,6 +205,20 @@ instance Binary LitNumType where h <- getByte bh return (toEnum (fromIntegral h)) +instance NFData LitNumType where + rnf (LitNumBigNat) = () + rnf (LitNumInt) = () + rnf (LitNumInt8) = () + rnf (LitNumInt16) = () + rnf (LitNumInt32) = () + rnf (LitNumInt64) = () + rnf (LitNumWord) = () + rnf (LitNumWord8) = () + rnf (LitNumWord16) = () + rnf (LitNumWord32) = () + rnf (LitNumWord64) = () + + {- Note [BigNum literals] ~~~~~~~~~~~~~~~~~~~~~~ @@ -288,6 +303,16 @@ instance Binary Literal where return (LitNumber nt i) _ -> pprPanic "Binary:Literal" (int (fromIntegral h)) +instance NFData Literal where + rnf (LitChar c) = rnf c + rnf (LitNumber nt i) = rnf nt `seq` rnf i + rnf (LitString s) = rnf s + rnf LitNullAddr = () + rnf (LitFloat r) = rnf r + rnf (LitDouble r) = rnf r + rnf (LitLabel l1 k2) = rnf l1 `seq` rnf k2 + rnf (LitRubbish {}) = () -- LitRubbish is not contained within interface files. + -- See Note [Rubbish literals]. instance Outputable Literal where ppr = pprLiteral id ===================================== compiler/GHC/Types/SourceFile.hs ===================================== @@ -13,6 +13,7 @@ where import GHC.Prelude import GHC.Utils.Binary import GHC.Unit.Types +import Control.DeepSeq {- Note [HscSource types] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -53,6 +54,10 @@ data HsBootOrSig | Hsig -- ^ .hsig file deriving (Eq, Ord, Show) +instance NFData HsBootOrSig where + rnf HsBoot = () + rnf Hsig = () + data HscSource -- | .hs file = HsSrcFile @@ -73,6 +78,10 @@ hscSourceToIsBoot :: HscSource -> IsBootInterface hscSourceToIsBoot HsBootFile = IsBoot hscSourceToIsBoot _ = NotBoot +instance NFData HscSource where + rnf HsSrcFile = () + rnf (HsBootOrSig h) = rnf h + instance Binary HscSource where put_ bh HsSrcFile = putByte bh 0 put_ bh HsBootFile = putByte bh 1 ===================================== compiler/GHC/Types/SrcLoc.hs ===================================== @@ -223,7 +223,8 @@ data RealSrcLoc -- We use 'BufPos' in in GHC.Parser.PostProcess.Haddock to associate Haddock -- comments with parts of the AST using location information (#17544). newtype BufPos = BufPos { bufPos :: Int } - deriving (Eq, Ord, Show, Data) + deriving (Eq, Ord, Show, Data, NFData) + -- | Source Location data SrcLoc @@ -373,11 +374,13 @@ data RealSrcSpan } deriving Eq --- | StringBuffer Source Span data BufSpan = BufSpan { bufSpanStart, bufSpanEnd :: {-# UNPACK #-} !BufPos } deriving (Eq, Ord, Show, Data) +instance NFData BufSpan where + rnf (BufSpan a1 a2) = rnf a1 `seq` rnf a2 + instance Semigroup BufSpan where BufSpan start1 end1 <> BufSpan start2 end2 = BufSpan (min start1 start2) (max end1 end2) @@ -439,8 +442,18 @@ instance ToJson RealSrcSpan where end = JSObject [ ("line", JSInt srcSpanELine), ("column", JSInt srcSpanECol) ] +instance NFData RealSrcSpan where + rnf (RealSrcSpan' file line col endLine endCol) = rnf file `seq` rnf line `seq` rnf col `seq` rnf endLine `seq` rnf endCol instance NFData SrcSpan where - rnf x = x `seq` () + rnf (RealSrcSpan a1 a2) = rnf a1 `seq` rnf a2 + rnf (UnhelpfulSpan a1) = rnf a1 + +instance NFData UnhelpfulSpanReason where + rnf (UnhelpfulNoLocationInfo) = () + rnf (UnhelpfulWiredIn) = () + rnf (UnhelpfulInteractive) = () + rnf (UnhelpfulGenerated) = () + rnf (UnhelpfulOther a1) = rnf a1 getBufSpan :: SrcSpan -> Strict.Maybe BufSpan getBufSpan (RealSrcSpan _ mbspan) = mbspan ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -132,6 +132,7 @@ import GHC.Utils.Panic import GHC.Hs.Specificity () import Language.Haskell.Syntax.Specificity +import Control.DeepSeq import Data.Data @@ -734,6 +735,9 @@ instance (Binary tv, Binary vis) => Binary (VarBndr tv vis) where get bh = do { tv <- get bh; vis <- get bh; return (Bndr tv vis) } +instance (NFData tv, NFData vis) => NFData (VarBndr tv vis) where + rnf (Bndr tv vis) = rnf tv `seq` rnf vis + instance NamedThing tv => NamedThing (VarBndr tv flag) where getName (Bndr tv _) = getName tv ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -39,6 +39,7 @@ import Data.List (sortBy, sort, partition) import Data.Set (Set) import qualified Data.Set as Set import Data.Bifunctor +import Control.DeepSeq -- | Dependency information about ALL modules and packages below this one -- in the import hierarchy. This is the serialisable version of `ImportAvails`. @@ -104,6 +105,18 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +instance NFData Dependencies where + rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) + = rnf dmods + `seq` rnf dpkgs + `seq` rnf ppkgs + `seq` rnf hsigms + `seq` rnf tps + `seq` rnf bmods + `seq` rnf orphs + `seq` rnf finsts + `seq` () + -- | Extract information from the rename and typecheck phases to produce -- a dependencies information for the module being compiled. @@ -326,6 +339,13 @@ data Usage -- And of course, for modules that aren't imported directly we don't -- depend on their export lists +instance NFData Usage where + rnf (UsagePackageModule mod hash safe) = rnf mod `seq` rnf hash `seq` rnf safe `seq` () + rnf (UsageHomeModule mod uid hash entities exports safe) = rnf mod `seq` rnf uid `seq` rnf hash `seq` rnf entities `seq` rnf exports `seq` rnf safe `seq` () + rnf (UsageFile file hash label) = rnf file `seq` rnf hash `seq` rnf label `seq` () + rnf (UsageMergedRequirement mod hash) = rnf mod `seq` rnf hash `seq` () + rnf (UsageHomeModuleInterface mod uid hash) = rnf mod `seq` rnf uid `seq` rnf hash `seq` () + instance Binary Usage where put_ bh usg at UsagePackageModule{} = do putByte bh 0 ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -660,52 +660,46 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ - , mi_exports_, mi_fixities_, mi_warns_, mi_anns_ - , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ - , mi_fam_insts_, mi_rules_, mi_trust_, mi_trust_pkg_ - , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_ }) - = rnf mi_module_ - `seq` rnf mi_sig_of_ - `seq` mi_hsc_src_ - `seq` mi_hi_bytes_ - `seq` mi_deps_ - `seq` mi_exports_ - `seq` mi_fixities_ - `seq` rnf mi_warns_ - `seq` rnf mi_anns_ - `seq` rnf mi_decls_ - `seq` rnf mi_defaults_ - `seq` rnf mi_extra_decls_ - `seq` rnf mi_foreign_ - `seq` rnf mi_top_env_ - `seq` rnf mi_insts_ - `seq` rnf mi_fam_insts_ - `seq` rnf mi_rules_ - `seq` mi_trust_ - `seq` rnf mi_trust_pkg_ - `seq` rnf mi_complete_matches_ - `seq` rnf mi_docs_ - `seq` mi_final_exts_ - `seq` mi_ext_fields_ - `seq` () - -instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_mod_hash - , mi_orphan, mi_finsts, mi_exp_hash - , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn - , mi_hash_fn}) - = rnf mi_mod_hash - `seq` rnf mi_orphan - `seq` rnf mi_finsts - `seq` rnf mi_exp_hash - `seq` rnf mi_orphan_hash - `seq` rnf mi_decl_warn_fn - `seq` rnf mi_export_warn_fn - `seq` rnf mi_fix_fn - `seq` rnf mi_hash_fn + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + `seq` rnf a15 + `seq` rnf a16 + `seq` rnf a17 + `seq` rnf a18 + `seq` rnf a19 + `seq` rnf a20 + `seq` rnf a21 + `seq` rnf a22 + -- IfaceBinHandle + `seq` a23 + `seq` rnf a24 + + +instance NFData ModIfaceBackend where + rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 forceModIface :: ModIface -> IO () ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -517,6 +517,9 @@ newtype UnitId = UnitId } deriving (Data) +instance NFData UnitId where + rnf (UnitId fs) = rnf fs `seq` () + instance Binary UnitId where put_ bh (UnitId fs) = put_ bh fs get bh = do fs <- get bh; return (UnitId fs) @@ -704,6 +707,9 @@ data GenWithIsBoot mod = GWIB -- IsBootInterface: this is assumed to perform filtering of non-boot modules, -- e.g. in GHC.Driver.Env.hptModulesBelow +instance NFData mod => NFData (GenWithIsBoot mod) where + rnf (GWIB mod isBoot) = rnf mod `seq` rnf isBoot `seq` () + type ModuleNameWithIsBoot = GenWithIsBoot ModuleName type ModuleWithIsBoot = GenWithIsBoot Module ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,11 +2,11 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where -import Data.Data +import Data.Data (Data) import Data.Eq import Data.Ord import Data.Bool -import Data.Int (Int) +import Prelude import GHC.Data.FastString (FastString) import Control.DeepSeq @@ -134,5 +134,13 @@ data FixityDirection | InfixN deriving (Eq, Data) +instance NFData FixityDirection where + rnf InfixL = () + rnf InfixR = () + rnf InfixN = () + data Fixity = Fixity Int FixityDirection deriving (Eq, Data) + +instance NFData Fixity where + rnf (Fixity i d) = rnf i `seq` rnf d `seq` () ===================================== libraries/ghc-boot/GHC/Serialized.hs ===================================== @@ -22,11 +22,15 @@ import Prelude -- See note [Why do we import Prelude here?] import Data.Bits import Data.Word ( Word8 ) import Data.Data +import Control.DeepSeq -- | Represents a serialized value of a particular type. Attempts can be made to deserialize it at certain types data Serialized = Serialized TypeRep [Word8] +instance NFData Serialized where + rnf (Serialized tr ws) = rnf tr `seq` rnf ws + -- | Put a Typeable value that we are able to actually turn into bytes into a 'Serialized' value ready for deserialization later toSerialized :: forall a. Typeable a => (a -> [Word8]) -> a -> Serialized toSerialized serialize what = Serialized (typeOf what) (serialize what) ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -52,7 +52,6 @@ import Data.Map (Map) import qualified Data.Map as Map import qualified Data.Set as Set import GHC -import qualified GHC.Data.Strict as Strict import GHC.Data.BooleanFormula (BooleanFormula) import GHC.Driver.Session (Language) import qualified GHC.LanguageExtensions as LangExt @@ -61,7 +60,7 @@ import GHC.Types.Fixity (Fixity (..)) import GHC.Types.Name (stableNameCmp) import GHC.Types.Name.Occurrence import GHC.Types.Name.Reader (RdrName (..)) -import GHC.Types.SrcLoc (BufPos (..), BufSpan (..), srcSpanToRealSrcSpan) +import GHC.Types.SrcLoc (srcSpanToRealSrcSpan) import GHC.Types.Var (Specificity) import GHC.Utils.Outputable @@ -987,15 +986,6 @@ instance NFData RdrName where rnf (Orig m on) = m `deepseq` on `deepseq` () rnf (Exact n) = rnf n -instance NFData FixityDirection where - rnf InfixL = () - rnf InfixR = () - rnf InfixN = () - -instance NFData Fixity where - rnf (Fixity n dir) = - n `deepseq` dir `deepseq` () - instance NFData (EpAnn NameAnn) where rnf (EpAnn en ann cs) = en `deepseq` ann `deepseq` cs `deepseq` () @@ -1065,15 +1055,6 @@ instance NFData EpaCommentTok where rnf (EpaLineComment s) = rnf s rnf (EpaBlockComment s) = rnf s -instance NFData a => NFData (Strict.Maybe a) where - rnf Strict.Nothing = () - rnf (Strict.Just x) = rnf x - -instance NFData BufSpan where - rnf (BufSpan p1 p2) = p1 `deepseq` p2 `deepseq` () - -instance NFData BufPos where - rnf (BufPos n) = rnf n instance NFData DeltaPos where rnf (SameLine n) = rnf n View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4dae0101f987c498046307b390c23ece18606b19 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4dae0101f987c498046307b390c23ece18606b19 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/d2ad7759/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 12:38:13 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 10 Mar 2025 08:38:13 -0400 Subject: [Git][ghc/ghc][wip/buildplan] 386 commits: Refactored BooleanFormula to be in line with TTG (#21592) Message-ID: <67cedd35641e0_22530614f50099146@gitlab.mail> Cheng Shao pushed to branch wip/buildplan at Glasgow Haskell Compiler / GHC Commits: 97f600c6 by Hassan Al-Awwadi at 2024-11-04T15:52:12+00:00 Refactored BooleanFormula to be in line with TTG (#21592) There are two parts to this commit. * We moved the definition of BooleanFormula over to L.H.S.BooleanFormula * We parameterized the BooleanFormula over the pass The GHC specific details of BooleanFormula remain in Ghc.Data.BooleanFormula. Because its parameterized over the pass its no longer a functor or traversable, but we defined bfMap and bfTraverse for the cases where we needed fmap and traverse originally. Most other changes are just churn. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - d4fd3580 by Andreas Klebinger at 2024-11-05T07:36:16-05:00 ghc-heap: Fix incomplete selector warnings. Use utility functions instead of selectors to read partial attributes. Part of fixing #25380. - - - - - fdd9f62a by Peter Trommler at 2024-11-05T07:36:51-05:00 PPC NCG: Implement fmin and fmax - - - - - 8e217256 by Mike Pilgrem at 2024-11-07T04:34:20-05:00 Re CLC #293 - Don't specify Data.List.NonEmpty in terms of partial See https://github.com/haskell/core-libraries-committee/issues/293 `List.init` had already been driven out of `tails1` by 21fc180bec93d964a7f4ffdf2429ef6f74b49ab6 but this specification also avoided partial `fromList`, so I preferred it. The `changelog.md` for `base` is updated, with an entry added under `base-4.22.0.0`. - - - - - 346e4cd1 by Zubin Duggal at 2024-11-07T04:34:57-05:00 release: copy zip files into the correct directory Fixes #25446 - - - - - bbdbe225 by Zubin Duggal at 2024-11-07T04:34:57-05:00 release: Sign .gz bindists too Fixes #25447 - - - - - 0c722e14 by Hécate Kleidukos at 2024-11-07T04:35:37-05:00 hadrian: Enforce the usage of GHC >=9.8.1 for ghci-multi GHC 9.6 no good when it comes to multi-repl stuff, despite being well within the range of n-2 releases for bootstrapping, when the script was adapted to load haddock, in !12851 - - - - - d8f8a1c3 by Sylvain Henry at 2024-11-07T19:27:46-05:00 Handle the special ghc-prim:GHC.Prim module in the compiler Before this patch, some custom hacks were necessary in ghc-prim's Setup.hs to register the GHC.Prim (virtual) module and in Hadrian to generate haddocks properly. In this patch we special-case this module in the compiler itself instead (which it already is, see ghcPrimIface in GHC.Iface.Load). From Cabal/Hadrian's perspective GHC.Prim is now just a normal autogenerated module. This simplification is worthwhile on its own. It was found while looking into the work needed for #24453 which aims to merge ghc-prim, ghc-bignum, and ghc-internal. It's also one step closer to remove ghc-prim's custom setup. - - - - - a55adc8e by Cheng Shao at 2024-11-07T19:28:22-05:00 Clean up obsolete CPP guarded code paths from the tree This patch cleans up obsolete CPP guarded code paths from the tree. The minimum supported boot GHC version is 9.6, and all the pre-9.6 era code paths can be removed. - - - - - 9ede97f3 by Cheng Shao at 2024-11-07T19:28:58-05:00 Remove obsolete executable wrappers from the tree The executable wrappers are handled by hadrian and bindist Makefile. The various .wrapper scripts in the tree are unused since removal of Make build system, so this patch removes them all. - - - - - 7d42b2df by tristian at 2024-11-07T19:29:40-05:00 TcRnDuplicateDecls now suggests to use the DuplicateRecordFields extension. Fixes: !24627 - - - - - e56ed179 by Zubin Duggal at 2024-11-11T15:16:35+05:30 testsuite: normalise some versions in callstacks (cherry picked from commit f230e29f30d0c1c566d4dd251807fcab76a2710e) - - - - - a28fc903 by Zubin Duggal at 2024-11-11T15:16:35+05:30 testsuite: use -fhide-source-paths to normalise some backpack tests (cherry picked from commit b19de476bc5ce5c7792e8af1354b94a4286a1a13) - - - - - ed16d303 by Zubin Duggal at 2024-11-11T15:16:36+05:30 testsuite/haddock: strip version identifiers and unit hashes from html tests (cherry picked from commit fbf0889eadc410d43dd5c1657e320634b6738fa5) - - - - - e45e5836 by Zubin Duggal at 2024-11-11T15:16:36+05:30 haddock: oneshot tests can drop files if they share modtimes. Stop this by including the filename in the key. Ideally we would use `ghc -M` output to do a proper toposort Partially addresses #25372 (cherry picked from commit e78c7ef96e395f1ef41f04790aebecd0409b92b9) - - - - - 9104e6eb by Zubin Duggal at 2024-11-11T15:16:36+05:30 testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences (cherry picked from commit a79a587e025d42d34bb30e115fc5c7cab6c1e030) - - - - - 2c31264a by Zubin Duggal at 2024-11-11T15:16:36+05:30 testsuite: normalise windows file seperators (cherry picked from commit f858875e03b9609656b542aaaaff85ad0a83878a) - - - - - 2807f91b by Zubin Duggal at 2024-11-11T15:21:30+05:30 testsuite: Also match <VERSION> placeholders when normalising callsites - - - - - c02add17 by Ben Gamari at 2024-11-12T01:22:11-05:00 configure: Check version number validity Here we verify the previously informal invariant that stable release version numbers must have three components, preventing costly failed releases. Specifically, the check fails in the following scenarios: * `version=9.13` while `RELEASE=YES` since this would imply a release made from an unstable branch * `version=9.13.0` since unstable versions should only have two components * `version=9.12` since this has the wrong number of version components for a stable branch Fixes #25390. - - - - - 747fd322 by Teo Camarasu at 2024-11-12T01:22:49-05:00 docs: link to #14474 in the template-haskell docs - - - - - 6d96bb62 by Zubin Duggal at 2024-11-12T01:23:25-05:00 testsuite: normalise execvp vs exec differences in process tests Fixes #25431 - - - - - 502e6711 by Torsten Schmits at 2024-11-12T01:24:01-05:00 fix test lint that accumulated while the checks were broken I didn't fix the issues flagged by the #ifdef linter because it were so many that it seemed like the rule has become obsolete. - - - - - 223a4cb5 by Torsten Schmits at 2024-11-12T01:24:02-05:00 test driver: fix file collection for regex linters When a testsuite linter is executed with the `tracked` strategy, the driver runs `git ls-tree` to collect eligible files. This appears to have ceased producing any paths – `ls-tree` restricts its results to the current working directory, which is `testsuite/tests/linters` in this case. As a quick fix, this patch changes the working directory to match expectations. - - - - - 9ad9ac63 by Alan Zimmerman at 2024-11-12T01:24:39-05:00 EPA: Capture location of '_' for wild card type binder And keep track of promotion status in HsExplicitTupleTy, so the round-trip ppr test works for it. Updates Haddock output too, using the PromotionFlag in HsExplicitTupleTy. Closes #25454 - - - - - c37b96fa by Cheng Shao at 2024-11-12T01:25:15-05:00 wasm: fix setImmediate() implementation for Cloudflare Workers This patch fixes setImmediate() implementation for Cloudflare Workers in the wasm backend's js prelude script. Cloudflare Workers doesn't support the MessageChannel API, and we use a setTimeout() based fallback implementation in this case. - - - - - bea8ea4c by Cheng Shao at 2024-11-12T01:25:15-05:00 wasm: fix FinalizationRegistry logic for Cloudflare Workers This patch fixes FinalizationRegistry related logic for Cloudflare Workers in wasm backend js post linker. Cloudflare Workers doesn't support FinalizationRegistry, in this case we use a dummy implementation that doesn't do anything. - - - - - 00d551bf by Cheng Shao at 2024-11-13T08:48:21-05:00 Remove obsolete cross-port script This patch removes the obsolete cross-port script in the tree. The script was based on the legacy Make build system which has been pruned from the tree long ago. For hadrian, proper support for two-stage bootstrapping onto a new unsupported platform is a work in progress in !11444. - - - - - 75a2eae4 by Cheng Shao at 2024-11-13T08:48:58-05:00 hadrian: fix bindist makefile for wasm32-wasi target This patch fixes one incoherent place between bindist makefile and hadrian logic: I forgot to include wasi/wasm32 in OsSupportsGHCi/ArchSupportsGHCi as well. And this results in incorrect settings file generated after installing the bindist, and "Use interpreter"/"Have interpreter" fields incorrectly have "NO" values where they should be "YES" like --info output of in-tree version. - - - - - 0614abef by Alan Zimmerman at 2024-11-13T08:49:34-05:00 EPA: Correctly capture leading semis in decl list Closes #25467 - - - - - 00d58ae1 by Sebastian Graf at 2024-11-13T15:21:23-05:00 DmdAnal: Make `prompt#` lazy (#25439) This applies the same treatment to `prompt#` as for `catch#`. See `Note [Strictness for mask/unmask/catch/prompt]`. Fixes #25439. - - - - - 93233a66 by Ben Gamari at 2024-11-13T15:21:59-05:00 boot: Do not attempt to update config.sub While Apple ARM hardware was new we found that the autoconf scripts included in some boot packages were too old. As a mitigation for this, we introduced logic in the `boot` script to update the `config.sub` with that from the GHC tree. However, this causes submodules which have `config.sub` committted to appear to be dirty. This is a considerable headache. Now since `config.sub` with full platform support is more common we can remove `boot`'s `config.sub` logic. Fixes #19574. - - - - - fa66fa64 by Ryan Scott at 2024-11-14T19:05:00-05:00 Add regression test for #16234 Issue #16234 was likely fixed by !9765. This adds a regression test to ensure that it remains fixed. Fixes #16234. - - - - - bfe64df8 by Matthew Pickering at 2024-11-14T19:05:36-05:00 ghc-internal: Update to Unicode 16 This patch updates the automatically generated code for querying unicode properties to unicode 16. Fixes #25402 - - - - - 1fd83f86 by Ben Gamari at 2024-11-14T19:06:13-05:00 configure: Accept happy-2.1.2 happy-2.1 was released in late Oct 2024. I have confirmed that master bootstraps with it. Here we teach configure to accept this tool. Fixes #25438. - - - - - aa58fc5b by Ben Gamari at 2024-11-14T19:06:49-05:00 rts: Tighten up invariants of PACK - - - - - 8aa4c10a by Ben Gamari at 2024-11-14T19:06:49-05:00 testsuite: Fix badly escaped literals Use raw string literals to ensure that `\s` is correctly interpreted as a character class. - - - - - 0e084029 by Ben Gamari at 2024-11-14T19:06:49-05:00 rts: Improve documentation of SLIDE bytecode instruction - - - - - 9bf3663b by Ben Gamari at 2024-11-14T19:06:49-05:00 rts/Interpreter: Assert that TEST*_P discriminators are valid - - - - - 1f668511 by Ben Gamari at 2024-11-14T19:06:49-05:00 rts/Interpreter: Improve documentation of TEST*_P instructions - - - - - 59e0a770 by Cheng Shao at 2024-11-14T19:07:25-05:00 misc: improve clangd compile_flags.txt flags This patch improves the compile_flags.txt config used to power clangd for the rts C codebase. The flags in the file are sampled & deduped from a real stage1 build with clang-19 and vastly improves the IDE accuracy when hacking the rts. For maximum code coverage under the default settings, compile_flags.txt defaults to threaded+profiled+dynamic+debug way. This does not mean profdyn needs to be actually built in _build/stage1 for IDE to work. To activate IDE for other RTS ways, simply remove one of the -D flags at the end of compile_flags.txt and restart clangd. - - - - - c2c562e0 by Ben Gamari at 2024-11-14T19:08:01-05:00 testsuite: Don't consider untracked files in dirtiness check Considering trees containing untracked files as dirty is a bridge too far. The chance of an untracked file significantly affecting measured performanced metrics is quite small whereas not collecting measurements is quite inconvenient for some workflows. We now ignore untracked files in the dirtiness check. Fixes #25471. - - - - - ed2ed6c5 by Cheng Shao at 2024-11-14T19:08:37-05:00 testsuite: add regression test T25473 This commit adds regression test T25473 marked as broken due to #25473. It will be fixed in the subsequent commit. - - - - - bd0a8b7e by Cheng Shao at 2024-11-14T19:08:37-05:00 wasm: fix foreign import javascript "wrapper" in TH/ghci This patch fixes foreign import javascript "wrapper" in wasm backend's TH/ghci by fixing the handling of dyld/finalization_registry magic variables. Fixes T25473 and closes #25473. - - - - - f1b0bc32 by Ben Gamari at 2024-11-14T19:09:13-05:00 rts/linker: Make FreeBSD declarations proper prototypes The iconv declarations for FreeBSD were previously not prototypes, leading to warnings. - - - - - 086cbbc1 by Ben Gamari at 2024-11-14T19:09:13-05:00 base: Drop redundant import in FreeBSD ExecutablePath implementation - - - - - 79ecd199 by Ben Gamari at 2024-11-14T19:09:13-05:00 compiler: Fix partial selector warnings in GHC.Runtime.Heap.Inspect - - - - - 1acb73bf by Andrew Lelechenko at 2024-11-15T06:10:47-05:00 gitlab: mention CLC in MR template - - - - - 8f2e0832 by Ben Gamari at 2024-11-15T06:11:24-05:00 rts: Allow use of GNU-stack notes on FreeBSD Previously we gated use of GNU-style non-executable stack notes to only apply on Linux. However, these are also supported by FreeBSD, which also uses ELF. Fix this. Fixes #25475. - - - - - 2c427cb0 by Ben Gamari at 2024-11-16T05:27:40-05:00 rts: Fix EINTR check in timerfd ticker When `poll` failed we previously checked that `errno == -EINTR` to silence the failure warning. However, this is wrong as `errno` values are generally not negated error codes (in contrast to many system call results, which is likely what the original author had in mind). Fixes #25477. - - - - - a0fa4941 by Ben Gamari at 2024-11-16T05:28:16-05:00 rts: Increase gen_workspace alignment to 128 bytes on AArch64 Increase to match the 128-byte cache-line size of Apple's ARMv8 implementation. Closes #25459. - - - - - 142d8afa by Ben Gamari at 2024-11-16T16:20:47-05:00 rts/RtsFlags: Refactor size parsing This makes a number of improvements mentioned in #20201: * fail if the argument cannot be parsed as a number (`-Mturtles`) * fail if an unrecognized unit is given (e.g. `-M1x`) - - - - - b7a146e5 by Ben Gamari at 2024-11-16T16:20:47-05:00 testsuite: Add tests for RTS flag parsing error handling See #20201. - - - - - ddb7afa6 by Ben Gamari at 2024-11-16T16:21:23-05:00 users guide: Mention language extensions in equality constraints discussion As suggested in #24127, mention the language extensions necessary for usage of equality constriants in their documentation. Closes #24127. - - - - - 36133dac by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide/9.14.1-notes: Fix list syntax - - - - - 888de658 by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide/debug-info: Fix duplicate flag descriptions - - - - - f120e427 by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide: Fix reference to 9.14.1 release notes - - - - - 8e975032 by Ben Gamari at 2024-11-16T16:21:59-05:00 Introduce GHC.Tc.Plugin.lookupTHName This makes it significantly more convenient (and less GHC-version-dependent) to resolve a template-haskell name into a GHC Name. As proposed in #24741. - - - - - a0e168ec by ARATA Mizuki at 2024-11-16T16:22:40-05:00 x86 NCG SIMD: Lower packFloatX4#, insertFloatX4# and broadcastFloatX4# to SSE1 instructions Fixes #25441 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 3936bf1b by sheaf at 2024-11-16T16:23:22-05:00 X86 NCG: allow VXOR at scalar floating-point types The NCG can emit VXOR instructions at scalar floating-point types, but the pretty-printer would panic instead of emitting the appropriate VXORPS/VXORPD instructions. This patch rectifies that oversight. Fixes #25455 - - - - - d9dff93a by Ben Gamari at 2024-11-16T16:23:58-05:00 rts: Fix platform-dependent pointer casts Previously we had unnecessary (and incorrect) platform-dependent casts to turn `OSThreadIds`s into a integer. We now just uniformly cast first to a `uintptr_t` (which is always safe, regardless of whether `OSThreadId` is a pointer), and then cast to the desired integral type. This fixes a warning on musl platforms. - - - - - 6d95cdb8 by Ben Gamari at 2024-11-16T16:24:34-05:00 testsuite: Mark encoding004 as broken on FreeBSD Due to #22003, CP936 fails to roundtrip: ```diff == CP936 +Failed to roundtrip given mutant byte at index 891 (251 /= 123 at index 891) +Failed to roundtrip given mutant byte at index 1605 (197 /= 69 at index 1605) +Failed to roundtrip given mutant byte at index 2411 (235 /= 107 at index 2411) +Failed to roundtrip given mutant byte at index 6480 (208 /= 80 at index 6480) +Failed to roundtrip given mutant byte at index 6482 (210 /= 82 at index 6482) +Failed to roundtrip given mutant byte at index 6484 (212 /= 84 at index 6484) +Failed to roundtrip given mutant byte at index 6496 (224 /= 96 at index 6496) +Failed to roundtrip given mutant byte at index 7243 (203 /= 75 at index 7243) +Failed to roundtrip given mutant byte at index 7277 (237 /= 109 at index 7277) +Failed to roundtrip given mutant byte at index 8027 (219 /= 91 at index 8027) +Failed to roundtrip given mutant byte at index 8801 (225 /= 97 at index 8801) ``` - - - - - 26e86984 by Ben Gamari at 2024-11-18T04:05:31-05:00 hadrian: Allow haddock options to be passed via key-value settings - - - - - 6e68b117 by Matthew Pickering at 2024-11-18T04:06:07-05:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - a4e0d235 by Rodrigo Mesquita at 2024-11-18T04:06:07-05:00 exceptions: Improve the message layout as per #285 This commit fixes the layout of the additional information included when displaying an exception, namely the type of the exception. It also fixes the default handler's heading message to work well together with the improved display message of SomeException. CLC proposal#285 - - - - - 284ffab3 by Rodrigo Mesquita at 2024-11-18T04:06:07-05:00 Display type and callstack of exception on handler This commit changes the Exception instance of SomeException to *simply* display the underlying exception in `displayException`. The augmented exception message that included the type and backtrace of the exception are now only printed on a call to `displayExceptionWithInfo`. At a surface level, existing programs should behave the same since the `uncaughtExceptionHandler`, which is responsible for printing out uncaught exceptions to the user, will use `displayExceptionWithInfo` by default. However, unlike the instance's `displayException` method, the `uncaughtExceptionHandler` can be overriden with `setUncaughtExceptionHandler`. This makes the extra information opt-in without fixing it the instance, which can be valuable if your program wants to display uncaught exceptions to users in a user-facing way (ie without backtraces). This is what was originally agreed for CLC#231 or CLC#261 with regard to the type of the exception information. The call stack also becoming part of the default handler rather than the Exception instance is an ammendment to CLC#164. Discussion of the ammendment is part of CLC#285. - - - - - 36cddd2c by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Remove redundant CallStack from exceptions Before the exception backtraces proposal was implemented, ErrorCall accumulated its own callstack via HasCallStack constraints, but ExceptionContext is now accumulated automatically. The original ErrorCall mechanism is now redundant and we get a duplicate CallStack Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall CLC proposal#285 Fixes #25283 - - - - - 7a74330b by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Freeze call stack in error throwing functions CLC proposal#285 - - - - - 3abf31a4 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 De-duplicate displayContext and displayExceptionContext The former was unused except for one module where it was essentially re-defining displayExceptionContext. Moreover, this commit extends the fix from bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too, which was missing. - - - - - c0d783f8 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Re-export NoBacktrace from Control.Exception This was originally proposed and accepted in section "2.7 Capturing Backtraces on Exceptions" of the CLC proposal for exception backtraces. However, the implementation missed this re-export, which this commit now fixes. - - - - - 802b5c3e by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Fix exception backtraces from GHCi When running the program with `runhaskell`/`runghc` the backtrace should match the backtrace one would get by compiling and running the program. But currently, an exception thrown in a program interpreted with `runhaskell` will: * Not include the original exception backtrace at all * Include the backtrace from the internal GHCi/ghc rethrowing of the original exception This commit fixes this divergence by not annotating the ghc(i) backtrace (with NoBacktrace) and making sure that the backtrace of the original exception is serialized across the boundary and rethrown with the appropriate context. Fixes #25116 The !13301 MR (not this commit in particular) improves performance of MultiLayerModules. Unfortunately, T3294 regresses on aarch64-linux-deb12 by 1% allocations. Since this patch must be merged for 9.12 ASAP, we will not be able to investigate the slight regression on this platform in time. ------------------------- Metric Decrease: MultiLayerModulesRecomp MultiLayerModulesTH_OneShot Metric Increase: T3294 ------------------------- - - - - - 3e89eb65 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 base: Add to changelog.md CLC #285 - - - - - d9326a48 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Bump array and stm submodules for testsuite The testsuites of array and stm had to be updated according to !13301. Updates submodule array and stm. - - - - - 325fcb5d by Ben Gamari at 2024-11-18T04:06:45-05:00 rts/adjustor: Clean up code style of Nativei386 adjustor - - - - - 39bb6e58 by Ben Gamari at 2024-11-18T04:06:45-05:00 rts/adjustor: Fix stack overrun error in Nativei386 adjustor We were reserving the wrong kind of adjustor context (the generic `AdjustorContext` used by other adjustor implementations, rather than the i386-specific `CCallContext`) to return the adjustor context while freeing, resulting in #25485. Fixes #25485. - - - - - 831aab22 by sheaf at 2024-11-18T21:22:36-05:00 Include diagnostic reason in -fdiagnostics-as-json This commit ensures that the -fdiagnostics-as-json output includes the diagnostic reason. This allows the full error message produced by GHC to be re-constructed from the JSON output. Fixes #25403 - - - - - 3e5bfdd3 by Ben Gamari at 2024-11-18T21:23:12-05:00 rts: Introduce printIPE This is a convenience utility for use in GDB. - - - - - 44d909a3 by Sjoerd Visscher at 2024-11-19T14:38:24-05:00 Don't store boot locations in finder cache Partially reverts commit fff55592a7b Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache. Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for. - - - - - 64c95292 by Sjoerd Visscher at 2024-11-19T14:38:24-05:00 Concentrate boot extension logic in Finder With new mkHomeModLocation that takes an extra HscSource to add boot extensions if required. - - - - - 11bad98d by ARATA Mizuki at 2024-11-19T14:39:08-05:00 Better documentation for floating-point min/max and SIMD primitives See #25350 for floating-point min/max Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 791a47b2 by Arnaud Spiwack at 2024-11-20T14:00:05+00:00 Add test for #25185 - - - - - 374e18e5 by Arnaud Spiwack at 2024-11-20T14:09:30+00:00 Quick look: emit the multiplicity of app heads in tcValArgs Otherwise it's not scaled properly by the context, allowing unsound expressions. Fixes #25185. - - - - - 1fc02399 by sheaf at 2024-11-20T18:11:03-05:00 x86 NCG: fix regUsageOfInstr for VMOVU & friends This commit fixes the implementation of 'regUsageOfInstr' for vector operations that take an 'Operand' as the destination, by ensuring that when the destination is an address then the address should be *READ*, and not *WRITTEN*. Getting this wrong is a disaster, as it means the register allocator has incorrect information, which can lead to it discard stores to registers, segfaults ensuing. Fixes #25486 - - - - - 7bd407a6 by Brandon Chinn at 2024-11-21T14:08:15-05:00 Fix CRLF in multiline strings (#25375) - - - - - 7575709b by Rodrigo Mesquita at 2024-11-21T14:08:52-05:00 Improve reachability queries on ModuleGraph Introduces `ReachabilityIndex`, an index constructed from a `GHC.Data.Graph.Directed` `Graph` that supports fast reachability queries (in $O(1)$). This abstract data structure is exposed from `GHC.Data.Graph.Directed.Reachability`. This index is constructed from the module graph nodes and cached in `ModuleGraph`, enabling efficient reachability queries on the module graph. Previously, we'd construct a Map of Set of ModuleGraph nodes which used a lot of memory (`O(n^2)` in the number of nodes) and cache that in the `ModuleGraph`. By using the reachability index we get rid of this space leak in the module graph -- even though the index is still quadratic in the number of modules, it is much, much more space efficient due to its representation using an IntMap of IntSet as opposed to the transitive closure we previously cached. In a memory profile of MultiLayerModules with 100x100 modules, memory usage improved from 6GB residency to 2.8GB, out of which roughly 1.8GB are caused by a second space leak related to ModuleGraph. On the same program, it brings compile time from 7.5s to 5.5s. Note how we simplify `checkHomeUnitsClosed` in terms of `isReachableMany` and by avoiding constructing a second graph with the full transitive closure -- it suffices to answer the reachability query on the full graph without collapsing the transitive closure completely into nodes. Unfortunately, solving this leak means we have to do a little bit more work since we can no longer cache the result of turning vertex indices into nodes. This results in a slight regression in MultiLayerModulesTH_Make, but results in large performance and memory wins when compiling large amounts of modules. ------------------------- Metric Decrease: mhu-perf Metric Increase: MultiLayerModulesTH_Make ------------------------- - - - - - bcbcdaaf by Cheng Shao at 2024-11-21T14:09:28-05:00 driver: fix hpc undefined symbol issue in TH with -fprefer-byte-code This commit fixes an undefined symbol error in RTS linker when attempting to compile home modules with -fhpc and -fbyte-code-and-object-code/-fprefer-byte-code, see #25510 for detailed description and analysis of the bug. Also adds T25510/T25510c regression tests to test make mode/oneshot mode of the bug. - - - - - 970ada5a by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Bump ci-images For introduction of Alpine/i386 image. Thanks to Julian for the base image. Co-Authored-By: Julian Ospald <hasufell at hasufell.de> - - - - - 8115abc2 by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Add release job for i386/Alpine As requested by Mikolaj and started by Julian. Co-Authored-By: Julian Ospald <hasufell at hasufell.de> - - - - - 639f0149 by Ben Gamari at 2024-11-22T23:32:06-05:00 rts/linker/Elf: Resolve _GLOBAL_OFFSET_TABLE_ - - - - - 490d4d0a by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Mark i386 Alpine test breakages Marks the following tests as broken on i386/Alpine: * T22033 due to #25497 * simd009, T25062_V16, T25169, T22187_run due to #25498 - - - - - 536cdf09 by Cheng Shao at 2024-11-22T23:32:42-05:00 compiler: remove unused GHC.Linker.Loader.loadExpr This patch removes the unused `GHC.Linker.Loader.loadExpr` function. It was moved from `GHC.Runtime.Linker.linkExpr` in `ghc-9.0` to `GHC.Linker.Loader.loadExpr` in `ghc-9.2`, and remain completely unused and untested ever since. There's also no third party user of this function to my best knowledge, so let's remove this. Anyone who wants to write their own GHC API function to load bytecode can consult the source code in older release branches. - - - - - 6ee35024 by Drew Fenwick at 2024-11-22T23:33:26-05:00 Fix a non-compiling example in the type abstractions docs This patch adds a missing Show constraint to a code example in the User Guide's type abstractions docs to fix issue #25422. - - - - - d1172e20 by Rodrigo Mesquita at 2024-11-22T23:34:02-05:00 Re-introduce ErrorCallWithLocation with a deprecation pragma With the removal of the duplicate backtrace, part of CLC proposal #285, the constructor `ErrorCallWithLocation` was removed from base. This commit re-introduces it with a deprecation. - - - - - 1187a60a by Ben Gamari at 2024-11-22T23:34:39-05:00 testsuite: Skip tests requiring Hadrian deps in out-of-tree testsuite runs Some testsuite tests require specific tools (e.g. `check-ppr` and `check-exact`) beyond those shipped in the binary distribution. Skip these tests. Fixes #13897. - - - - - c37d7a2e by Ben Gamari at 2024-11-22T23:34:39-05:00 testsuite: Declare exactprint tests' dependency on check-exact - - - - - 454ce957 by Ben Gamari at 2024-11-22T23:35:15-05:00 ghc-internal: Fix a few cases of missing Haddock markup - - - - - a249649b by Ben Gamari at 2024-11-22T23:35:51-05:00 testsuite/GHCiPrimCall : Add missing Makefile includes - - - - - a021a493 by Ben Gamari at 2024-11-22T23:35:51-05:00 testsuite/IpeStats: Use Make rather than shell interpolation - - - - - 6e1fbda7 by Ben Gamari at 2024-11-25T03:55:44-05:00 hadrian-ghci-multi: Pass -this-package-name in unit response files As noted in #25509, the `-this-package-name` must be passed for each package to ensure that GHC can response references to the packages' exposed modules via package-qualified imports. Fix this. Closes #25509. - - - - - a05e4a9b by Simon Hengel at 2024-11-25T03:56:33-05:00 Refactoring: Use `OnOff` more consistently for `Extension` - - - - - 7536181d by Matthew Pickering at 2024-11-25T14:00:07-05:00 driver: Always link against "base" package when one shot linking The default value for base-unit-id is stored in the settings file. At install time, this can be set by using the BASE_UNIT_ID environment variable. At runtime, the value can be set by `-base-unit-id` flag. For whether all this is a good idea, see #25382 Fixes #25382 - - - - - 7f90f319 by Andreas Klebinger at 2024-11-25T14:00:44-05:00 Compacting GC: Handle black holes in large objects. As #14497 showed black holes can appear inside large objects when we capture a computation and later blackhole it like we do for AP_STACK closures. Fixes #24791 - - - - - 291388e1 by Cheng Shao at 2024-11-25T14:01:19-05:00 ci: minor nix-in-docker improvements This patch makes some minor improvements re nix-in-docker logic in the ci configuration: - Update `nixos/nix` to the latest version - Apply $CPUS to `cores`/`max-jobs` to avoid oversubscribing while allowing a reasonable degree of parallelism - Remove redundant `--extra-experimental-features nix-command` in later `nix shell` invocations, it's already configured in `/etc/nix/nix.conf` - - - - - e684c406 by Cheng Shao at 2024-11-25T14:01:57-05:00 ci: avoid depending on stack job for test-bootstrap jobs This patch makes test-bootstrap related ci jobs only depend on hadrian-ghc-in-ghci job to finish, consistent with other jobs in the full-build stage generated by gen_ci.hs. This allows the jobs to be spawned earlier and improve overall pipeline parallelism. - - - - - caaf5388 by Simon Hengel at 2024-11-25T14:02:41-05:00 Refactoring: Remove `pSupportedExts` from `ParserOpts` This is never used for lexing / parsing. It is only used by `GHC.Parser.Header.getOptions`. - - - - - 41f8365c by Arnaud Spiwack at 2024-11-25T14:03:23-05:00 Add test for #25515 - - - - - 9279619f by Arnaud Spiwack at 2024-11-25T14:03:23-05:00 Desugar record notation with correct multiplicities Simply uses the multiplicity as stored in the field. As I'm writing this commit, the only possible multiplicity is 1, but !13525 is changing this. It's actually easier to take !13525 into account. Fixes #25515. - - - - - fcc3ae6e by Andreas Klebinger at 2024-11-26T08:24:58-05:00 Clarify INLINE unfolding optimization docs. Fixes #24660 - - - - - 88c4fe1d by Cheng Shao at 2024-11-26T08:25:34-05:00 rts: remove -Wl,-U,___darwin_check_fd_set_overflow hack This patch bumps macOS minimum SDK version to 11.0 for x86_64-darwin to align it with aarch64-darwin. This allows us to get rid of the horrible -Wl,-U,___darwin_check_fd_set_overflow hack, which is causing linker warnings and testsuite failures on macOS 15. Fixes #25504. - - - - - 53f978c0 by doyougnu at 2024-11-26T16:07:26-05:00 ghc-experimental: expose GHC.RTS.Flags, GHC.Stats See this CLC proposal: - https://github.com/haskell/core-libraries-committee/issues/289 and this CLC proposal for background: - https://github.com/haskell/core-libraries-committee/issues/288 Metric Decrease: MultiLayerModulesTH_OneShot - - - - - e70d4140 by Wang Xin at 2024-11-26T16:08:10-05:00 Add -mcmodel=medium moduleflag to generated LLVM IR on LoongArch platform With the Medium code model, the jump range of the generated jump instruction is larger than that of the Small code model. It's a temporary fix of the problem descriped in https://gitlab.haskell .org/ghc/ghc/-/issues/25495. This commit requires that the LLVM used contains the code of commit 9dd1d451d9719aa91b3bdd59c0c6679 83e1baf05, i.e., version 8.0 and later. Actually we should not rely on LLVM, so the only way to solve this problem is to implement the LoongArch backend. Add new type for codemodel - - - - - df42ba16 by Andreas Klebinger at 2024-11-27T11:40:49-05:00 Cmm constant folding: Narrow results to operations bitwidth. When constant folding ensure the result is still within bounds for the given type by explicitly narrowing the results. Not doing so results in a lot of spurious assembler warnings especially when testing primops. - - - - - bf3db97e by Ben Gamari at 2024-11-27T11:41:26-05:00 ghc-toolchain: Introduce basic flag validation We verify that required flags (currently `--output` and `--triple`) are provided. The implementation is truly awful, but so is getopt. Begins to address #25500. - - - - - a104508d by Ben Gamari at 2024-11-27T11:42:03-05:00 rts: Allow ExecPage to allocate anywhere in address space Currently the ExecPage facility has two users: * GHCi, for constructing info tables, and * the adjustor allocation path Despite neither of these have any spatial locality constraints ExecPage was using the linker's `mmapAnonForLinker`, which tries hard to ensure that mappings end up nearby the executable image. This makes adjustor allocation needlessly subject to fragmentation concerns. We now instead return less constrained mappings, improving the robustness of the mechanism. Addresses #25503. - - - - - c3fc9b86 by Ben Gamari at 2024-11-27T11:42:39-05:00 base: Fix incorrect mentions of GHC.Internal.Numeric These were incorrectly changed by the automated refactoring of the `ghc-internal` migration. Fixes #25521. - - - - - a362b943 by sheaf at 2024-11-27T23:44:28-05:00 Add checkExact to toolTargets This change means that the Hadrian multi target will include exactprint. In particular, this means that HLS will work on exactprint inside the GHC tree. - - - - - e6c957e4 by Arnaud Spiwack at 2024-11-27T23:45:09-05:00 Add test for #25428 - - - - - 52d97f4e by Arnaud Spiwack at 2024-11-27T23:45:09-05:00 Don't bypass MonoLocalBind in empty patterns Fixes #25428 - - - - - 7890f2d8 by Ben Gamari at 2024-11-28T10:26:46-05:00 hadrian: Bump directory bound to >=1.3.9 Earlier versions of `directory` are racy on Windows due to #24382. Also includes necessary Hadrian bootstrap plan bump. Fixes #24382. - - - - - 0fd43ea6 by Adam Sandberg Ericsson at 2024-11-28T10:27:22-05:00 mention -Iw in +RTS -? - - - - - 6cf579b9 by Ben Gamari at 2024-11-28T10:27:59-05:00 gitlab-ci: Set GIT_SUBMODULE_FORCE_HTTPS GitLab recommends using `https://` to clone submodules and provides the `GIT_SUBMODULE_FORCE_HTTPS` variable to force this. Fixes #25528. - - - - - 5b4774f9 by sheaf at 2024-12-03T15:22:07+01:00 Remove TcRnDeprecatedInvisTyArgInConPat mechanism The combination of ScopedTypeVariables + TypeApplications now no longer enables the use of type applications in constructor patterns, as per GHC proposal #448. This completes the deprecation that begun with GHC 9.8. We also remove the -Wdeprecated-type-abstractions flag, which was introduced in GHC 9.10. - - - - - f813c8d7 by sheaf at 2024-12-03T17:10:15-05:00 Hadrian: use / when making filepaths absolute In Hadrian, we are careful to use -/- rather than </>, in order to use / instead of \ in filepaths. However, this gets ruined by the use of makeAbsolute from System.Directory, which, on Windows, changes back forward slashes to backslashes. - - - - - 292ed74e by Ben Gamari at 2024-12-03T17:10:52-05:00 rts/linker: Fix out-of-bounds mapping logic Previously the structure of `mmapInRegion` concealed a subtle bug concerning handling of `mmap` returning mappings below the beginning of the desired region. Specifically, we would reset `p = result + bytes` and then again reset `p = region->start` before looping around for another iteration. This resulted in an infinite loop on FreeBSD. Fixes #25492. - - - - - 20912f5b by Ben Gamari at 2024-12-03T17:10:52-05:00 rts/linker: Clarify debug output - - - - - f98b3ac0 by Simon Hengel at 2024-12-03T17:11:30-05:00 SysTools: Avoid race conditions when processing output (fixes #16450) - - - - - 03851b64 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 mg: Drop unnecessary HasCallStack This HasCallStack was a debugging artifact from a previous commit. - - - - - 01d213b5 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 Improve haddock of graphReachabilityCyclic - - - - - f7cbffe2 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 Refactor ModuleGraph interface The 'ModuleGraph' abstraction represents the relationship and strucutre of the modules being compiled. This structure is meant to be constructed once at the start of compilation, and never changed again. However, it's exposed interface was confusing and exposed too many footguns which led to inneficient usages of the ModuleGraph. This commit improves significantly the exported interface of ModuleGraph, taking into consideration the recent improvements around reachability queries. Since the ModuleGraph graphs and related structures (HPT, EPS) are performance critical in the sense that somewhat simple mistakes can cause bad leaks and non-linear memory usage, we want to have proper APIs that guide efficient usage. This is a good step in that direction. - - - - - b69a7f3c by David Binder at 2024-12-04T18:37:42-05:00 Use consistent capitalization for "GHC Proposal" in user guide - - - - - 18d9500d by David Binder at 2024-12-04T18:37:42-05:00 Fix reference to GHC proposal 193 in user guide - - - - - dd959406 by Ben Gamari at 2024-12-04T18:38:18-05:00 Revert "rts/Interpreter: Assert that TEST*_P discriminators are valid" This assertion was based on the misconception that `GET_TAG` was returning the pointer tag whereas it is actually returning the constructor tag. This reverts commit 9bf3663b9970851e7b5701d68147450272823197. Fixes #25527. - - - - - cad6fede by Ben Gamari at 2024-12-04T18:38:54-05:00 rts/IOManager: Drop dead code This assignment is dead code as it occurs after all branches have returned. Moreover, it can't possibly be relevant since the "available" branch already sets `flag`. Potentially fixes #25542. - - - - - 55d8304e by Ben Gamari at 2024-12-06T16:56:00-05:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - 56b9f484 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 336d392e by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - dd7ca939 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Mention incorrect Data.Enum addition in changelog - - - - - dfd1db48 by Ben Gamari at 2024-12-06T16:56:36-05:00 base: Reintroduce {Show,Enum} IoSubSystem These instances were dropped in !9676 but not approved by the CLC. Addresses #25549. - - - - - 090fc7c1 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements on T25240 T25240 doesn't need RTS linker, GHCi is sufficient and GHCi can also be dynamically linked. - - - - - 3fb5d399 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements for T25155 Loading C objects requires RTS linker. - - - - - 4c58bdf6 by Leary at 2024-12-07T03:42:07-05:00 TH: Add typed variants of dataToExpQ and liftData This commit introduces to template-haskell (via ghc-internal) two functions `dataToCodeQ` and `liftDataTyped`, typed variants of `dataToExpQ` and `liftData` respectively. Tested in: `dataToCodeQUnit`. - - - - - 63027593 by Serge S. Gulin at 2024-12-08T13:52:05+03:00 JS: Basic cleanup for unused stuff to simplify things. 1. Make `staticInitStat`, `staticDeclStat`, `allocUnboxedConStatic`, `allocateStaticList`, `jsStaticArg` local to modules. 2. Remove unused `hdRawStr`, `hdStrStr` from Haskell and JavaScript (`h$pstr`, `h$rstr`, `h$str`). 3. Introduce a special type `StaticAppKind` enumeration and `StaticApp` to represent boxed scalar static applications. Originally, StaticThunk supported to pass Maybe when it became Nothing for initializied thunks in an alternatie way but it is not used anymore. - - - - - a9f8f1fb by Serge S. Gulin at 2024-12-08T14:10:45+03:00 JS: Add trivial optimizations for `unpackCString` and `unpackCStringUtf8`. It became possible due of introduction strings unfloating at Sinker pass (#13185). Earns few more bytes at optimizations. - - - - - b519c06b by Serge S. Gulin at 2024-12-08T15:50:26+03:00 JS: Specialize unpackCString# CAFs (fixes #24744) Code analysis shown that such optimization would be possible out of the box if `cachedIdentForId` allowed to do that for Haskell `Id`s which are represented by few JavaScript `Ident`s. It is a usual for strings which are represented at JavaScript as a pair of 2 values: the string content and the offset where to start reading actual string from the full content. Usually offset is 0 but technically we need to allow such complex structures to be treated as "global". Enabling it there shown that `genToplevelRhs` and `globalOccs` had inaccuracies in their implementations: 1. `globalOccs` operated over JavaScript's `Ident`s but for complex structures it didn't pay attention to the fact that different Idents actually could be pointed to same Id. Now the algo is changed to calculate occurencies for Ids. 2. `genToplevelRhs` didn't assume that different Idents pointed to same Id can have mixed order of occurence. But actually the order is important. Strings are encoded into 2 variables where first is content and second is offset and their order are not interchangeable. It is fixed by regeneration Idents from collected Ids which is fine because all Idents generation is passed through the Cache and they are quasi-stable. - - - - - a8ceccf3 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Fix panic in multiline string with unterminated gap (#25530) - - - - - 9e464ad0 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Add test case for unterminated multiline string - - - - - ed1ed5c6 by Rodrigo Mesquita at 2024-12-09T16:26:19-05:00 Revert mapMG renaming We had previously renamed this function for consistency, but that caused unnecessary breakage - - - - - 158261f7 by Sylvain Henry at 2024-12-09T16:27:01-05:00 RTS: make Cabal flags manual Cabal shouldn't automatically try to set them. We set them explicitly. - - - - - a83b7ed6 by Matthew Stephenson at 2024-12-10T14:01:22-05:00 Add missing @since documentation for (!?) function - - - - - e745e3a3 by Ben Gamari at 2024-12-10T14:01:59-05:00 compiler: Don't attempt to TSAN-instrument SIMD operations TSAN only provides instrumentation for 8, 16, 32, and 64-bit memory loads/stores. Don't attempt to instrument wider operations. Fixes #25563. - - - - - 684c0018 by Ben Gamari at 2024-12-10T14:02:35-05:00 gitlab/ci: Don't clobber RUNTEST_ARGS Previously the logic handling `IGNORE_PERF_FAILURES` clobbered the user's `RUNTEST_ARGS`. Fix this. - - - - - 41dae5b8 by Ben Gamari at 2024-12-10T14:03:11-05:00 hadrian: Mitigate mktexfmt race At least some versions of Texlive's `mktexfmt` utility cannot be invoked concurrently in their initial run since they fail to handle failure of `mkdir` due to racing. Specifically, we see ``` | Run Xelatex: users_guide.tex => /tmp/extra-dir-9616886274866 | Run Xelatex: Haddock.tex => /tmp/extra-dir-9616886274869 This is XeTeX, Version 3.14159265-2.6-0.999992 (TeX Live 2020) (preloaded format=xelatex) restricted \write18 enabled. kpathsea: Running mktexfmt xelatex.fmt mktexfmt: mktexfmt is using the following fmtutil.cnf files (in precedence order): mktexfmt: /usr/share/texlive/texmf-dist/web2c/fmtutil.cnf mktexfmt: mktexfmt is using the following fmtutil.cnf file for writing changes: mktexfmt: /builds/ghc/ghc/tmp-home/.texlive2020/texmf-config/web2c/fmtutil.cnf /usr/bin/mktexfmt: mkdir(/builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c/) failed for tree /builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c: File exists at /usr/share/texlive/tlpkg/TeXLive/TLUtils.pm line 937. I can't find the format file `xelatex.fmt'! ``` That is two `mktexfmt` invocations (for the user's guide and haddock builds) attempted to create `$HOME/texlive2020/texmf-var/web2c` and raced. One of the two `mkdir`'s consequently failed, bringing down the entire build. We avoid this by ensuring that the first `xelatex` invocation is always performed serially. Fixes #25564. - - - - - 9efbc51f by Ben Gamari at 2024-12-10T14:03:48-05:00 rts/CheckUnload: Reset old_objects if unload is skipped Previously `checkUnload` failed to reset `old_objects` when it decided not to unload (e.g. due to heap profiling being enabled). Fixes #24935. - - - - - 5192a75f by Ben Gamari at 2024-12-11T04:28:11-05:00 rts: Annotate BCOs with their Name This introduces a new bytecode instruction, `BCO_NAME`, to aid in debugging bytecode execution. This instruction is injected by `mkProtoBCO` and captures the Haskell name of the BCO. It is then printed by the disassembler, allowing ready correlation with STG dumps. - - - - - 99225996 by Ben Gamari at 2024-12-11T04:28:48-05:00 configure: Implement ld override whitelist Bring `configure` into alignment with `ghc-toolchain`, ensuring that the ld-override logic will only take effect on Linux and Windows. Fixes #25501. - - - - - 4a8fc928 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Unmark T14028 as broken on FreeBSD This now appears to pass on FreeBSD 14. Closes #19723. - - - - - d7c0eb5a by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Migrate FreeBSD runner tag to FreeBSD 14 - - - - - 7246dacc by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Reintroduce FreeBSD 14 job - - - - - 4af936da by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Allow use of newer cabal-install bindists Newer cabal-install bindists have internal directory structure. Here we detect and account for the presence of such structure. - - - - - cbf38c1b by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Enable documentation build on FreeBSD 14 - - - - - d68107fb by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Use system libffi on FreeBSD - - - - - fea3b590 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark linker_unload as broken on FreeeBSD Due to #25491. - - - - - ccf171ee by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Prefer system toolchain on FreeBSD It's not uncommon to find machines with gcc installed via ports. We should be using the system's default clang-based toolchain instead. - - - - - cfb34738 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T21969 as broken on FreeBSD Due to #25512. - - - - - 0b64e37c by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark RestartEventLogging as broken on FreeBSD I am seeing this fail quite reproducibly. Due to #19724. - - - - - 3b412019 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T16180 as "broken" on FreeBSD Sadly we in fact need to skip it as it merely times out during compilation. See #14012. - - - - - 57e3cab5 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Skip T16992 unless in slow speed This test has extraordinary memory requirements and tests a rather niche aspect of the compact region mechanism. It has been suggested multiple times that we shouldn't run it in the default testsuite configuration. Finally implement this. See #21890. See #21892. - - - - - f08a72eb by Ben Gamari at 2024-12-11T19:30:54-05:00 rts(setNumCapabilities): Assert that n_caps < MAX_N_CAPS It was noticed in #25560 that this would previously be allowed, resulting in a segfault. I will add a proper exception in `base` in a future commit. - - - - - e10d31ad by Ben Gamari at 2024-12-11T19:30:55-05:00 ghc-internal: Fix inconsistent FFI import types The foreign imports of `enabled_capabilities` and `getNumberOfProcessors` were declared as `CInt` whereas they are defined as `uint32_t`. - - - - - 06265655 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Mention maximum capability count in users guide Addresses #25560. - - - - - d488470b by Ben Gamari at 2024-12-11T19:30:55-05:00 rts/Capability: Move induction variable declaration into `for`s Just a stylistic change. - - - - - 71f050b7 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Determine max_n_capabilities at RTS startup Previously the maximum number of capabilities supported by the RTS was statically capped at 256. However, this bound is uncomfortably low given the size of today's machine. While supporting unbounded, fully-dynamic adjustment would be nice, it is complex and so instead we do something simpler: Probe the logical core count at RTS startup and use this as the static bound for the rest of our execution. This should avoid users running into the capability limit on large machines while avoiding wasting memory on a large capabilities array for most users and keeping complexity at bay. Addresses #25560. - - - - - 1e84b411 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Introduce req_c_rts As suggested by @hsyl20, this is intended to mark tests that rely on the behavior of the C RTS. - - - - - 683115a4 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Add test for #25560 - - - - - ef2052a8 by Ben Gamari at 2024-12-12T04:42:32-05:00 testsuite: Only run T14497_compact in normal way This test targets the compacting GC so it makes little sense to run it across all ways. Moreover, it outright conflicts with the `nonmoving` way. - - - - - 34d3e8e6 by Ben Gamari at 2024-12-12T04:43:08-05:00 rts/CheckUnload: Don't prepare to unload if we can't unload Previously `prepareUnloadCheck` would move the `objects` list to `old_objects` even when profiling (where we cannot unload). This caused us to vacate the `objects` list during major GCs, losing track of loaded objects. Fix this by ensuring that `prepareUnloadCheck` and `checkUnload` both use the same short-cutting logic. - - - - - 9c53489d by Andrei Borzenkov at 2024-12-12T15:06:42-05:00 Update GHCi :info type declaration printing (#24459) - Do not print result's kind in type families because we have full kind in SAKS and we display invisible arity using @-binders - Do not suppress significant invisible binders An invisible binder is considered significant when it meets at least one of the following two criteria: - It visibly occurs in the declaration's body - It is followed by a significant binder, so it affects positioning For non-generative type declarations (type synonyms and type families) there is one additional criterion: - It is not followed by a visible binder, so it affects the arity of a type synonym See Note [Print invisible binders in interface declarations] for more information about what is "visibly occurs" - - - - - 13fe48d4 by Matthew Pickering at 2024-12-12T15:07:19-05:00 typechecker: Perform type family consistency checks in topological order Consider a module M importing modules A, B and C. We can waste a lot of work depending on the order that the modules are checked for family consistency. Consider that C imports A and B. When compiling C we must have already checked A and B for consistency, therefore if C is processed first then A and B will not need to be checked for consistency again. If A and B are compared first, then the consistency checks will be performed against (wasted as we already performed them for C). At the moment the order which modules are checked is non-deterministic. Clearly we should engineer that C is checked before B and A, but by what scheme? A simple one is to observe that if a module M is in the transitive closure of X then the size of the consistent family set of M is less than or equal to size of the consistent family set of X. Therefore by sorting the imports by the size of the consistent family set and processing the largest first, you make sure to process modules in topological order. In practice we have observed that this strategy has reduced the amount of consistency checks performed. One solution to #25554 - - - - - 62a2b25f by Sylvain Henry at 2024-12-14T04:31:09-05:00 TNTC: set CmmProc entry_label properly (#25565) Before this patch we were renaming the entry label of a CmmProc late in the CmmToAsm pass. It led to inconsistencies and to some labels being used in info tables but not being emitted (#25565). Now we set the CmmProc entry label earlier in the StgToCmm monad and we don't renamed it afterwards. - - - - - b339e7c3 by Simon Hengel at 2024-12-14T04:31:47-05:00 Make filter functionality for system tools line-based This is more efficient as: - All existing filter functions were line-based anyway. They broke up the input into lines and then joined it back together. - We already break up the output from system tools into lines when processing it. Splitting up the output of system tools once and then filtering and processing it reduces both code and runtime complexity. - - - - - 39669077 by Simon Hengel at 2024-12-14T04:31:47-05:00 Refactoring: Don't use a `Chan` when parsing SysTools output - - - - - 64756530 by Simon Peyton Jones at 2024-12-14T22:28:04-05:00 Tidy up the handling of `assert` Fixes #25493 - - - - - 8658fbc1 by Rodrigo Mesquita at 2024-12-14T22:28:41-05:00 base: displayException for SomeAsyncException Provide a better implementation of `SomeException` for `SomeAsyncException`. The previous, implicit, implementation, would not use the `displayException` of the exception wrapped by `SomeAsyncException`. Implements CLC-Proposal#309 Closes #25513 - - - - - 2d3a0a70 by ARATA Mizuki at 2024-12-15T18:35:30-05:00 LLVM: When emitting a vector literal with ppTypeLit, include the type information Fixes #25561 - - - - - bfacc086 by Simon Peyton Jones at 2024-12-15T18:36:05-05:00 Fix signature lookup in instance declarations This fixes a bug introduced by the fix to #16610 - - - - - 80f0e02d by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Improve GHC build times Two small changes * In GHC.Data.Unboxed, never omit interface pragmas. In "fast builds" one might omit them generally, but doing so gives very bad performance for code that imports this module. * In GHC.Hs.Dump don't do type-class specialisation. For some reason it goes mad and generates vast amounts of useless code. See #25463. - - - - - 175a1355 by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Refactor Lint Refactor Lint for two reasons: * To improve performance * To prepare for type-lets The big changes are all in GHC.Core.Lint: * Change the main APIs: * `lintType` returns nothing rather than returning a `LintedType`; * `lintCoercion` return nothing rather than returning a `LintedCoercion` Reason: these functions did a lot of allocation to return a substituted type/coercion that was often discarded, or used only to extract its kind. Instead we now return nothing, and, when needed, extract the kind and substitute. * Applications are treated as a whole, by `lintApp`. By treating multiple arguments all at once we avoid performing multiple substitutions, each substituting a single type variable. This can make an absolutely huge difference. Overall this led to a pretty massive rewrite of Lint, with many smaller changes. Smaller chnages elsewhere * Rename `GHC.Core.TyCo.Subst.getSubstInScope` to `substInScopeSet` for consistency * Define and use `GHC.Core.Type.liftedTypeOrConstraintKind` Performance. This MR someimtes gives gives a very large improvement in compile time, when Lint is on. here is a selection of changes over 5% in perf/compiler (with -dcore-lint) T25196 -97.0% T14766 -89.7% T14683 -74.4% T5631 -60.9% T20261 -56.7% T18923 -17.6% T13035 -15.8% T6048 -15.8% CoOpt_Read -14.4% T9630 -10.9% T5642 -7.3% Eliminating the egregious offenders is a big win. However, in some cases the compiler allocation /increases/. Here ae the changes over 1%: T9961 1.5% T8095 2.8% T14052 3.9% T12545 4.5% T14052Type 5.5% T5030 8.0% T5321Fun 8.3% T3064 12.7% CoOpt_Singletons 15.6% T9198 16.0% LargeRecord 18.1% I looked at the two biggest increases in compile-time bytes allocated. Interestingly, they both show substantial *decreases* in actual compile time, due to much smaller GC times. I'm honestly not sure either why the allocation increases, or why the GC time decreases; but I'm going to take the win! T9198 Baseline With patch No Lint Alloc 44.6M 44.6M Mut time 0.23s 0.22s GC time 0.21s 0.21s With Lint Alloc 309M 360M Mut time 1.51s 0.85s GC time 2.97s 0.25s ------------------- LargeRecord Baseline With patch No Lint Alloc 1.37G 1.37G Mut time 2.33s 2.33s GC time 2.40s 2.42s With Lint Alloc 3.4G 4.0G Mut time 6.02s 5.68s GC time 3.67s 3.03s IMPORTANT NOTE: These changes don't show up in CI because in CI the tests in perf/compiler are all run with -dcore-lint switched off. I gathered this data with some manual runs. - - - - - 8ef2dad6 by Simon Peyton Jones at 2024-12-17T02:48:09-05:00 Add Note [Typechecking overloaded literals] See #25494. - - - - - e86b1b20 by Ben Gamari at 2024-12-17T13:51:39-05:00 testsuite: Use math.inf instead of division-by-zero This both more directly captures the intent and also fixes #25580. - - - - - 430d965a by Ben Gamari at 2024-12-17T13:52:15-05:00 rts: Fix incorrect format specifiers in era profiling Fixes #25581. - - - - - 267098ad by Andreas Klebinger at 2024-12-18T23:43:13-05:00 Document `-prof` and non `-prof` code being incompatible. Fixes #25518. - - - - - 04433916 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: output metadata fragment in CI (cherry picked from commit 52b58a660e735b20961d792d8fa9267f01247a50) - - - - - 7c78804e by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metatdata: use fedora33 for redhat Redhat 9 doesn't have libtinfo.so.5 anymore (cherry picked from commit dc86785eb43afd1bd292287c064fb5ad94fe8c7f) - - - - - 1d72cfb2 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: still use centos for redhat <9 - - - - - 3f7ebc58 by Sylvain Henry at 2024-12-19T20:40:14-05:00 Merge ghc-bignum into ghc-internal (#24453) First step towards merging ghc-bignum and ghc-prim into ghc-internal. After this patch, ghc-bignum is deprecated and is just a shallow package reexporting modules from ghc-internal and base. Use those directly instead. Move `gmp` submodule into ghc-internal directory. - - - - - ee0150c2 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Improve performance of deriving Show Significantly improves performance of deriving Show instances by avoiding using the very polymorphic `.` operator in favour of inlining its definition. We were generating tons of applications of it, each which had 3 type arguments! Improves on #9557 ------------------------- Metric Decrease: InstanceMatching T12707 T3294 ------------------------ - - - - - 8b266671 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Don't eta expand cons when deriving Data This eta expansion was introduced with the initial commit for Linear types. I believe this isn't needed any longer. My guess is it is an artifact from the initial linear types implementation: data constructors are linear, but they shouldn't need to be eta expanded to be used as higher order functions. I suppose in the early days this wasn't true. For instance, this works now: data T x = T x f = \(x :: forall y. y -> T y) -> x True f T -- ok! T is linear, but can be passed where an unrestricted higher order function is expected. I recall there being some magic around to make this work for data constructors... Since this works, there's no need to eta_expand the data constructors in the derived Data instances. - - - - - 1f67ad21 by Andrei Borzenkov at 2024-12-25T01:42:31-05:00 Flip the order of arguments of setField (#24668) GHC Proposal 583 "HasField redesign" specifies the following order of a setField function arguments as this: setField :: forall fld a b. SetField fld a b. b -> a -> a This patch flips the application order to match the spec. - - - - - 3e0c948d by Ben Gamari at 2024-12-25T01:43:08-05:00 rel-eng/upload: Add set_symlink mode This slightly eases updating of the `latest` symlinks. - - - - - 63d63f9d by Simon Peyton Jones at 2024-12-25T01:43:45-05:00 Preserve orientation when unifying kinds This MR fixes yet another manifestation of the trickiness caused by Note [Fundeps with instances, and equality orientation]. I wish there was a more robust way to do this, but this fix is a definite improvement. Fixes #25597 - - - - - 94ba9a6a by ARATA Mizuki at 2024-12-26T10:47:57-05:00 x86 NCG SIMD: Support pack/insert/broadcast/unpack of 128-bit integer vectors - - - - - 6bf0d587 by Andrew Lelechenko at 2024-12-26T10:48:33-05:00 docs: fix haddock formatting in Control.Monad.Fix - - - - - feb14af1 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Remove unnecessary irrefutable patterns from NonEmpty functions Implementation of https://github.com/haskell/core-libraries-committee/issues/107 - - - - - 6a0d91b4 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Make cons, Semigroup, IsList, and Monad instances stricter - - - - - 1249e597 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Restore some laziness in <| and Semigroup instance, improve Monad instance The Monad instance shouldn't produce the outer :| unless f a reduces to WHNF. (Notice that the b :| bs match is implicitly lazy.) - - - - - 8699d826 by Sergey Vinokurov at 2024-12-27T15:12:30+00:00 Add comment outlining Data.List.NonEmpty implementation guiding principles - - - - - 7febe00e by Sergey Vinokurov at 2024-12-27T22:24:43+00:00 Fix tests since location of ‘>>=’ changed - - - - - a928c326 by ARATA Mizuki at 2024-12-28T03:06:14-05:00 Fix LLVM version detection With a recent LLVM, `llc -version` emits the version on the first line if the vendor is set. It emits the version on the second line otherwise. Therefore, we need to check the both lines to detect the version. GHC now emits a warning if it fails to detect the LLVM version, so we can notice if the output of `llc -version` changes in the future. Also, the warning for using LLVM < 10 on s390x is removed, because we assume LLVM >= 13 now. This fixes the definition of __GLASGOW_HASKELL_LLVM__ macro. Fixes #25606 - - - - - 7f79257a by Zubin Duggal at 2024-12-29T13:04:35+00:00 Bump base, ghc-prim and template-haskell versions for 9.12 Also bump various submodules. (cherry picked from commit 6fc1fa3bdc8f53acdb19e47145789274060e498f) Bump base bound to 4.21 for GHC 9.12 (cherry picked from commit 473a201c6b55aea5bf9c9db0836a66ea1b657e04) Bump binary submodule to 0.8.9.2 (cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20) (cherry picked from commit ec2f40b45c1a3d82d17a2fc07e9ddb9218bc3940) Bump exceptions submodule to 0.10.9 (cherry picked from commit f5b5d1dc2d326368e5b173d622630d77f019b629) Bump file-io submodule to 0.1.4 (cherry picked from commit ba786681de6ac5fa49938e2cd71a5988f0f40d1f) bump os-string submodule to 2.0.6 (cherry picked from commit 3a7ffdbb832c045a55fd1ef24f546abdd9d9e30f) bump transformers submodule to 0.6.1.2 (cherry picked from commit 53b46fd437421b9e5a001edc6d1c427439d7714f) Bump directory submodule to v1.3.9.0 (cherry picked from commit 27dc2664c5404bb462092bb216c2c37b418fd1f8) Bump Win32 submodule to v2.14.1.0 (cherry picked from commit 80df88086180f5e39212b2feacf70a9d2b263c6c) Bump filepath submodule to 1.5.3.0 (cherry picked from commit 29bfae2c58a7303a081a6e7956b9f55e5faf3eeb) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 97b0dff223a6c4cc003adec448104c277f214645) Bump unix submodule to 2.8.6.0 (cherry picked from commit a1f56d6d6a99c100f88ef0a8b4d51298cf24a42d) Bump os-string submodule to 2.0.8 (cherry picked from commit 0121b76fd52ea0c0ce5d07085bc195666b63c625) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 962ceb50c8a6fc370e1c0a267f5cd5562a8cf759) Bump filepath submodule to 1.5.4.0 (cherry picked from commit 7bc6877fd5d41c6d5900678ad5e73ed30f366569) Bump file-io submodule to 0.1.5 (cherry picked from commit 9478b5aefe2877d58baf527edcf936dddbb955b7) Bump Cabal submodule to 3.14.1.0 (cherry picked from commit 5c9c3e3f79a79bb6d9a77a17c716dc3a0bcbd2aa) Bump directory submodule to 0.12.2.0 (cherry picked from commit 897906265db37af34ae2aaa016cec417f263407b) Bump array submodule for base bump Bump stm submodule for base bump Bump process submodule for base bump - - - - - f6079408 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix ghc-e005 after HasCallstack changes (cherry picked from commit 77f340a24561cea8a6f2ada296b3ea356ab1823c) - - - - - 3e10fa75 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Add haskeline to stage0Packages Otherwise we link against boot inplace and boot unix as boot haskeline depends on boot unix. (cherry picked from commit 90b493769ebdf3cd7be404d18462dc20ac1044df) - - - - - 4ad6aec4 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix TH changelog - - - - - ea3f7fd5 by Zubin Duggal at 2024-12-29T13:04:35+00:00 release: copy index.html from correct directory (cherry picked from commit cbfd0829cd61928976c9eb17ba4af18272466063) - - - - - fafb70db by Zubin Duggal at 2024-12-29T13:04:35+00:00 hadrian-multi: warn on unused imports os-string has redundant imports (cherry picked from commit dde3796be689ea57543936e22aa5ea4ef7ed995e) - - - - - c02b1e46 by Simon Peyton Jones at 2024-12-29T17:04:30-05:00 Fix in-scope set for CSE Ticket #25468 showed an assertion failure in CSE because a top-level Id was being used before it was defined. Reason: Note [Glomming] in GHC.Core.Opt.OccurAnal. Solution (used in many places): just put all the top-level bindings in scope at the beginning of CSE. Compile-time allocation wobbles up and down a tiny bit; geo mean is zero. But MultiLayerModulesTH_OneShot and hard_hole_fits increase (on some architectures only) by a bit oever 2% . I think these are just a random fluctuations. Metric Increase: MultiLayerModulesTH_OneShot hard_hole_fits - - - - - 559d4f84 by Krzysztof Gogolewski at 2024-12-30T11:53:19-05:00 Add tests for #23883 The issue has been fixed by commit f5d3e03c56ffc63. Only T23883a is the actual regression test, the remaining ones are tricky cases found during development of an independent fix !11313. - - - - - 278a53ee by Sergey Vinokurov at 2024-12-30T11:53:59-05:00 Update changelog for CLC proposal #107 (NonEmpty laziness) - - - - - f56558be by Matthew Pickering at 2025-01-07T13:53:03-05:00 warnings: Find out if a qualified name is in the interactive scope directly There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600 - - - - - 84155cdb by Simon Peyton Jones at 2025-01-07T13:53:40-05:00 Tidy up kcConDecls Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types - - - - - 6c12b6cf by Bryan Richter at 2025-01-07T18:15:02-05:00 Remove tmp files after toolchain check Fixes #25620 - - - - - 42826a89 by Cheng Shao at 2025-01-07T18:15:39-05:00 xxhash: bump to v0.8.3 - - - - - 185f17e4 by sheaf at 2025-01-07T18:16:15-05:00 Fix typo in GHC.Tc.Solver.Solve.runTcPluginsWanted - - - - - 23099752 by Luite Stegeman at 2025-01-08T00:33:33+01:00 Add flags for switching off speculative evaluation. We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284 - - - - - 0161badc by Ben Gamari at 2025-01-09T17:30:05-05:00 rts/printClosure: Print IPE information for thunks and functions This makes it considerably easier to grok the structure of the heap when IPE information is available. - - - - - 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz Goślinowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 8021f6ee by Cheng Shao at 2025-03-10T07:57:32+00:00 driver: make UsageFile distinguish hs/nonhs deps - - - - - 40eea9dd by Cheng Shao at 2025-03-10T12:37:46+00:00 driver: implement --buildplan major mode to extract BuildPlan info from dependency analysis - - - - - 96fdb8a5 by Cheng Shao at 2025-03-10T12:37:50+00:00 track non-hs deps - - - - - 1993 changed files: - .gitattributes - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/hello.hs - .gitlab/jobs.yaml - .gitlab/merge_request_templates/Default.md - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/recompress-all - .gitlab/rel_eng/upload.sh - .gitlab/rel_eng/upload_ghc_libs.py - .gitmodules - boot - compile_flags.txt - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Class.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - + compiler/GHC/Data/Graph/Directed/Internal.hs - + compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Data/Unboxed.hs - compiler/GHC/Data/Word64Map/Internal.hs - compiler/GHC/Data/Word64Map/Lazy.hs - compiler/GHC/Data/Word64Map/Strict.hs - compiler/GHC/Data/Word64Map/Strict/Internal.hs - compiler/GHC/Data/Word64Set.hs - compiler/GHC/Data/Word64Set/Internal.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Config/CoreToStg/Prep.hs - compiler/GHC/Driver/Config/Linker.hs - compiler/GHC/Driver/Config/Parser.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Phases.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Coverage.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Config.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Llvm/Ppr.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Platform/Ways.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Hpc.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/CodeGen.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Monad.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Symbols.hs - compiler/GHC/StgToJS/Types.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Finder/Types.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Info.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/Env.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/Location.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/Module/Warnings.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/GlobalVars.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Panic/Plain.hs - compiler/GHC/Utils/Touch.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Binds.hs - + compiler/Language/Haskell/Syntax/BooleanFormula.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/cbits/genSym.c - compiler/ghc.cabal.in - distrib/configure.ac.in - − distrib/cross-port - docs/users_guide/9.14.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/debug-info.rst - docs/users_guide/debugging.rst - docs/users_guide/diagnostics-as-json-schema-1_0.json - + docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/expected-undocumented-flags.txt - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/equality_constraints.rst - docs/users_guide/exts/multiline_strings.rst - docs/users_guide/exts/overloaded_record_update.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/exts/primitives.rst - docs/users_guide/exts/rewrite_rules.rst - docs/users_guide/exts/stolen_syntax.rst - docs/users_guide/exts/strict.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/exts/type_abstractions.rst - docs/users_guide/ghci.rst - docs/users_guide/packages.rst - docs/users_guide/phases.rst - docs/users_guide/profiling.rst - docs/users_guide/release-notes.rst - docs/users_guide/runtime_control.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using-warnings.rst - docs/users_guide/using.rst - docs/users_guide/wasm.rst - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - − ghc/ghc.wrapper - hadrian/bindist/Makefile - hadrian/bindist/config.mk.in - hadrian/bootstrap/plan-9_10_1.json - hadrian/bootstrap/plan-9_6_1.json - hadrian/bootstrap/plan-9_6_2.json - hadrian/bootstrap/plan-9_6_3.json - hadrian/bootstrap/plan-9_6_4.json - hadrian/bootstrap/plan-9_6_5.json - hadrian/bootstrap/plan-9_6_6.json - hadrian/bootstrap/plan-9_8_1.json - hadrian/bootstrap/plan-9_8_2.json - hadrian/bootstrap/plan-bootstrap-9_10_1.json - hadrian/bootstrap/plan-bootstrap-9_6_1.json - hadrian/bootstrap/plan-bootstrap-9_6_2.json - hadrian/bootstrap/plan-bootstrap-9_6_3.json - hadrian/bootstrap/plan-bootstrap-9_6_4.json - hadrian/bootstrap/plan-bootstrap-9_6_5.json - hadrian/bootstrap/plan-bootstrap-9_6_6.json - hadrian/bootstrap/plan-bootstrap-9_8_1.json - hadrian/bootstrap/plan-bootstrap-9_8_2.json - hadrian/cabal.project - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/doc/user-settings.md - hadrian/ghci-multi-cabal.in - hadrian/hadrian.cabal - hadrian/src/CommandLine.hs - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Haskell/Cabal/Parse.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/src/Rules/ToolArgs.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Warnings.hs - hadrian/stack.yaml - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/array - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Control/Exception.hs - libraries/base/src/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Char.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/Data/Semigroup.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Exception.hs - libraries/base/src/GHC/Exts.hs - + libraries/base/src/GHC/Num/BigNat.hs - + libraries/base/src/GHC/Num/Integer.hs - + libraries/base/src/GHC/Num/Natural.hs - libraries/base/src/Prelude.hs - libraries/base/src/System/Timeout.hs - libraries/base/tests/IO/T21336/T21336a.stderr - libraries/base/tests/IO/T21336/T21336b.stderr - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/all.T - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/openFile002.stderr-mingw32 - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withBinaryFile002.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFile002.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/IO/withFileBlocking002.stderr - libraries/base/tests/T15349.stderr - libraries/base/tests/T16111.stderr - libraries/base/tests/T19288.stderr - libraries/base/tests/T24807.stderr - libraries/base/tests/all.T - libraries/base/tests/assert.stderr - libraries/base/tests/dynamic002.hs - libraries/base/tests/foldableArray.hs - libraries/base/tests/readFloat.stderr - − libraries/base/tests/topHandler04.hs - − libraries/base/tests/topHandler04.stderr - libraries/base/tests/unicode002.stdout - libraries/base/tests/unicode003.hs - libraries/base/tests/unicode003.stdout - libraries/binary - libraries/bytestring - libraries/deepseq - libraries/directory - libraries/exceptions - libraries/file-io - libraries/filepath - − libraries/ghc-bignum/.gitignore - + libraries/ghc-bignum/Dummy.hs - − libraries/ghc-bignum/Setup.hs - − libraries/ghc-bignum/aclocal.m4 - libraries/ghc-bignum/changelog.md - − libraries/ghc-bignum/config.mk.in - − libraries/ghc-bignum/configure.ac - − libraries/ghc-bignum/ghc-bignum.buildinfo.in - libraries/ghc-bignum/ghc-bignum.cabal - − libraries/ghc-bignum/install-sh - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/BaseDir.hs - libraries/ghc-boot/GHC/Data/ShortText.hs - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-boot/GHC/Utils/Encoding/UTF8.hs - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-compact/tests/all.T - libraries/ghc-compact/tests/compact_function.stderr - libraries/ghc-compact/tests/compact_mutable.stderr - libraries/ghc-compact/tests/compact_pinned.stderr - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-experimental/src/Data/Sum/Experimental.hs - libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - + libraries/ghc-experimental/src/GHC/RTS/Flags/Experimental.hs - + libraries/ghc-experimental/src/GHC/Stats/Experimental.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/stack_big_ret.hs - libraries/ghc-internal/.gitignore - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/aclocal.m4 - libraries/ghc-bignum/README.rst → libraries/ghc-internal/bignum-backend.rst - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-bignum/cbits/gmp_wrappers.c → libraries/ghc-internal/cbits/gmp_wrappers.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/ghc-internal/configure.ac - libraries/ghc-internal/ghc-internal.buildinfo.in - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-bignum/GMP.rst → libraries/ghc-internal/gmp-backend.rst - libraries/ghc-bignum/gmp/ghc-gmp.h → libraries/ghc-internal/gmp/ghc-gmp.h - libraries/ghc-bignum/gmp/gmp-tarballs → libraries/ghc-internal/gmp/gmp-tarballs - libraries/ghc-bignum/include/HsIntegerGmp.h.in → libraries/ghc-internal/include/HsIntegerGmp.h.in - libraries/ghc-bignum/include/WordSize.h → libraries/ghc-internal/include/WordSize.h - − libraries/ghc-internal/include/alignment.h - libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-bignum/src/GHC/Num/Backend.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Check.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - libraries/ghc-bignum/src/GHC/Num/Backend/FFI.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Native.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Selected.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Selected.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - libraries/ghc-bignum/src/GHC/Num/Integer.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-bignum/src/GHC/Num/Integer.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - libraries/ghc-bignum/src/GHC/Num/Natural.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-bignum/src/GHC/Num/Natural.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - libraries/ghc-bignum/src/GHC/Num/Primitives.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-bignum/src/GHC/Num/WordArray.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - libraries/ghc-internal/src/GHC/Internal/Char.hs - libraries/ghc-prim/GHC/Classes.hs → libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - libraries/ghc-internal/src/GHC/Internal/Err.hs - libraries/ghc-internal/src/GHC/Internal/Event.hs - libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Float/ConversionUtils.hs - libraries/ghc-internal/src/GHC/Internal/Float/RealFracMethods.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/Types.hs - libraries/ghc-internal/src/GHC/Internal/Generics.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/SubSystem.hs - libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Int.hs - libraries/ghc-internal/src/GHC/Internal/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - libraries/ghc-internal/src/GHC/Internal/IsList.hs - libraries/ghc-internal/src/GHC/Internal/Ix.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - libraries/ghc-internal/src/GHC/Internal/Maybe.hs - libraries/ghc-internal/src/GHC/Internal/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs-boot - libraries/ghc-internal/src/GHC/Internal/Numeric/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-prim/GHC/Prim/Exception.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Read.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - libraries/ghc-internal/src/GHC/Internal/Records.hs - libraries/ghc-internal/src/GHC/Internal/Show.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs-boot - − libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hs-boot - libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - libraries/ghc-prim/GHC/Tuple.hs → libraries/ghc-internal/src/GHC/Internal/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats/Internal.hs - libraries/ghc-prim/GHC/Types.hs → libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghc-internal/src/GHC/Internal/Word.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/unicode_version - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/InfoTable.hsc - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/integer-gmp/integer-gmp.cabal - libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs - libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - libraries/template-haskell/tests/all.T - + libraries/template-haskell/tests/dataToCodeQUnit.hs - + libraries/template-haskell/tests/dataToCodeQUnit.stdout - libraries/template-haskell/vendored-filepath/System/FilePath.hs - libraries/terminfo - libraries/text - libraries/transformers - libraries/unix - linters/lint-codes/LintCodes/Static.hs - linters/lint-codes/Main.hs - m4/find_ld.m4 - m4/fp_settings.m4 - m4/fp_setup_project_version.m4 - m4/fptools_happy.m4 - m4/ghc_toolchain.m4 - rts/Capability.c - rts/Capability.h - rts/CheckUnload.c - rts/Disassembler.c - rts/Exception.cmm - rts/ExecPage.c - rts/IOManager.c - rts/IPE.c - rts/Interpreter.c - rts/Interpreter.h - rts/Linker.c - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/ProfHeap.c - rts/RtsFlags.c - rts/RtsMain.c - rts/RtsSymbols.c - rts/Schedule.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStdThunks.cmm - rts/Task.h - rts/Updates.h - rts/adjustor/NativeAmd64Asm.S - rts/adjustor/NativeAmd64MingwAsm.S - rts/adjustor/Nativei386.c - rts/adjustor/Nativei386Asm.S - rts/configure.ac - rts/external-symbols.list.in - rts/include/RtsAPI.h - rts/include/Stg.h - rts/include/rts/Bytecodes.h - rts/include/rts/Config.h - rts/include/rts/IPE.h - rts/include/rts/Threads.h - rts/include/rts/storage/HeapAlloc.h - rts/include/rts/storage/InfoTables.h - rts/include/stg/Prim.h - rts/js/environment.js - rts/js/mem.js - rts/js/string.js - rts/js/verify.js - rts/linker/MMap.c - rts/linker/MMap.h - rts/linker/MachO.c - rts/posix/ticker/TimerFd.c - rts/rts.cabal - rts/sm/Compact.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GCThread.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - rts/wasm/scheduler.cmm - rts/win32/libHSghc-prim.def - rts/xxhash.h - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/all.T - testsuite/tests/annotations/should_fail/annfail12.stderr - testsuite/tests/arityanal/should_run/T21694a.stderr - testsuite/tests/arityanal/should_run/T24296.stderr - testsuite/tests/array/should_run/arr003.stderr - testsuite/tests/array/should_run/arr004.stderr - testsuite/tests/array/should_run/arr007.stderr - testsuite/tests/array/should_run/arr008.stderr - testsuite/tests/arrows/should_compile/T21301.stderr - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/all.T - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp16.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/all.T - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail17.stderr - testsuite/tests/backpack/should_fail/bkpfail19.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - testsuite/tests/backpack/should_run/bkprun05.stderr - testsuite/tests/bytecode/T24634/Makefile - testsuite/tests/bytecode/T25090/Makefile - + testsuite/tests/bytecode/T25510/Makefile - + testsuite/tests/bytecode/T25510/T25510A.hs - + testsuite/tests/bytecode/T25510/T25510B.hs - + testsuite/tests/bytecode/T25510/all.T - + testsuite/tests/cmm/opt/T24556.cmm - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - testsuite/tests/codeGen/should_compile/T25166.stdout - testsuite/tests/codeGen/should_run/T16846.stderr - testsuite/tests/codeGen/should_run/T23146/all.T - testsuite/tests/codeGen/should_run/T25364.hs - testsuite/tests/codeGen/should_run/T25364.stdout - testsuite/tests/codeGen/should_run/T5626.stderr - testsuite/tests/codeGen/should_run/T7319.stderr - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/codeGen/should_run/cgrun016.stderr - testsuite/tests/codeGen/should_run/cgrun025.stderr - testsuite/tests/codeGen/should_run/cgrun045.stderr - testsuite/tests/codeGen/should_run/cgrun051.stderr - testsuite/tests/codeGen/should_run/cgrun059.stderr - testsuite/tests/concurrent/should_run/T13330.stderr - testsuite/tests/concurrent/should_run/T4030.stderr - testsuite/tests/concurrent/should_run/T5611.stderr - testsuite/tests/concurrent/should_run/T5611a.stderr - testsuite/tests/concurrent/should_run/T5866.stderr - testsuite/tests/concurrent/should_run/all.T - testsuite/tests/concurrent/should_run/allocLimit1.stderr - testsuite/tests/concurrent/should_run/allocLimit3.stderr - testsuite/tests/concurrent/should_run/conc009.stderr - testsuite/tests/concurrent/should_run/conc020.stderr - testsuite/tests/concurrent/should_run/conc021.stderr - testsuite/tests/concurrent/should_run/conc031.stderr - testsuite/tests/concurrent/should_run/conc040.stderr - testsuite/tests/concurrent/should_run/conc058.stderr - testsuite/tests/concurrent/should_run/conc064.stderr - testsuite/tests/concurrent/should_run/conc068.stderr - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - + testsuite/tests/core-to-stg/T25284/A.hs - + testsuite/tests/core-to-stg/T25284/B.hs - + testsuite/tests/core-to-stg/T25284/Cls.hs - + testsuite/tests/core-to-stg/T25284/Main.hs - + testsuite/tests/core-to-stg/T25284/T25284.stdout - + testsuite/tests/core-to-stg/T25284/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/deSugar/should_fail/DsStrictFail.stderr - testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr - testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr - testsuite/tests/deSugar/should_run/Or5.stderr - testsuite/tests/deSugar/should_run/T11193.stderr - testsuite/tests/deSugar/should_run/T11572.stderr - testsuite/tests/deSugar/should_run/T11601.stderr - testsuite/tests/deSugar/should_run/T20024.stderr - testsuite/tests/deSugar/should_run/dsrun005.stderr - testsuite/tests/deSugar/should_run/dsrun007.stderr - testsuite/tests/deSugar/should_run/dsrun008.stderr - testsuite/tests/default/DefaultImportFail01.stderr - testsuite/tests/default/DefaultImportFail02.stderr - testsuite/tests/default/DefaultImportFail03.stderr - testsuite/tests/default/DefaultImportFail04.stderr - testsuite/tests/default/DefaultImportFail05.stderr - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail07.stderr - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/deriving/should_run/T9576.stderr - testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/dmdanal/should_compile/T9208.hs - testsuite/tests/dmdanal/should_run/T12368.stderr - testsuite/tests/dmdanal/should_run/T12368a.stderr - testsuite/tests/dmdanal/should_run/T13380.stderr - testsuite/tests/dmdanal/should_run/T13380d.stderr - testsuite/tests/dmdanal/should_run/T13380e.stderr - testsuite/tests/dmdanal/should_run/T23208.stderr - + testsuite/tests/dmdanal/should_run/T25439.hs - + testsuite/tests/dmdanal/should_run/T25439.stdout - testsuite/tests/dmdanal/should_run/all.T - testsuite/tests/dmdanal/should_run/strun002.stderr - testsuite/tests/driver/Makefile - testsuite/tests/driver/T13914/T13914.stdout - testsuite/tests/driver/T20604/T20604.stdout - + testsuite/tests/driver/T25382.hs - testsuite/tests/driver/all.T - testsuite/tests/driver/boot-target/Makefile - testsuite/tests/driver/fat-iface/Makefile - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/json.stderr - testsuite/tests/driver/json_warn.hs - testsuite/tests/driver/json_warn.stderr - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits_callstack.stderr - testsuite/tests/driver/recomp24656/recomp24656.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/exceptions/T25052.stdout - testsuite/tests/ffi/should_run/T7170.stderr - testsuite/tests/ffi/should_run/ffi008.stderr - testsuite/tests/ffi/should_run/fptrfail01.stderr - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/all.T - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/ghc-api/T10942.hs - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/T20757.stderr - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-api/exactprint/all.T - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail7.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - testsuite/tests/ghc-e/should_fail/T23663.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghc-e/should_fail/T9930fail.stderr - testsuite/tests/ghc-e/should_fail/all.T - testsuite/tests/ghc-e/should_run/ghc-e005.stderr - testsuite/tests/ghci.debugger/scripts/break006.stderr - testsuite/tests/ghci.debugger/scripts/break009.stdout - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break017.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - testsuite/tests/ghci/linking/T25240/all.T - testsuite/tests/ghci/linking/all.T - testsuite/tests/ghci/scripts/Defer02.stderr - testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10501.stderr - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T15325.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T19310.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T21294a.stdout - testsuite/tests/ghci/scripts/T23686.stderr - + testsuite/tests/ghci/scripts/T24459.script - + testsuite/tests/ghci/scripts/T24459.stdout - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T5557.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci055.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_run/GHCiPrimCall/Makefile - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/hpc/function/tough.stdout - testsuite/tests/hpc/function2/tough2.stdout - testsuite/tests/hpc/simple/tixs/T10529a.stderr - testsuite/tests/hpc/simple/tixs/T10529b.stderr - testsuite/tests/hpc/simple/tixs/T10529c.stderr - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/T11361a.stderr - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs → testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12522a.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/javascript/Makefile - testsuite/tests/javascript/T23479_1.hs → testsuite/tests/javascript/T23479.hs - testsuite/tests/javascript/T23479_1.stdout → testsuite/tests/javascript/T23479.stdout - testsuite/tests/javascript/T23479_2.hs → testsuite/tests/javascript/T24744.hs - testsuite/tests/javascript/T23479_2.stdout → testsuite/tests/javascript/T24744.stdout - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/lib/integer/IntegerConversionRules.hs - testsuite/tests/lib/integer/T20066.stderr - + testsuite/tests/linear/should_compile/T25428.hs - + testsuite/tests/linear/should_compile/T25515.hs - testsuite/tests/linear/should_compile/all.T - testsuite/tests/linear/should_fail/LinearConfusedDollar.stderr - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLet10.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/linear/should_fail/T25185.hs - + testsuite/tests/linear/should_fail/T25185.stderr - testsuite/tests/linear/should_fail/all.T - testsuite/tests/linters/Makefile - testsuite/tests/linters/regex-linters/check-cpp.py - testsuite/tests/linters/regex-linters/linter.py - + testsuite/tests/llvm/should_compile/T25606.hs - testsuite/tests/llvm/should_compile/all.T - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/mdo/should_fail/mdofail006.stderr - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19892.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/numeric/should_run/foundation.hs - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr - testsuite/tests/overloadedrecflds/should_fail/NFSDuplicate.stderr - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.hs - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - + testsuite/tests/parser/should_fail/T25530.hs - + testsuite/tests/parser/should_fail/T25530.stderr - testsuite/tests/parser/should_fail/all.T - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - testsuite/tests/parser/should_run/RecordDotSyntax1.hs - + testsuite/tests/parser/should_run/T25375.hs - + testsuite/tests/parser/should_run/T25375.stdout - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/patsyn/should_run/ghci.stderr - testsuite/tests/perf/compiler/Makefile - testsuite/tests/perf/compiler/MultiLayerModulesTH_Make.stderr - testsuite/tests/perf/compiler/MultiLayerModulesTH_OneShot.stderr - testsuite/tests/perf/compiler/T11068.stdout - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/perf/size/all.T - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/all.T - testsuite/tests/primops/should_run/T10481.stderr - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Makefile - testsuite/tests/printer/Ppr010.hs - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/printer/Test25454.hs - + testsuite/tests/printer/Test25467.hs - testsuite/tests/printer/all.T - testsuite/tests/process/all.T - testsuite/tests/profiling/should_compile/T19894/StreamD.hs - testsuite/tests/profiling/should_compile/T19894/StreamK.hs - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/profiling/should_run/ioprof.prof.sample - testsuite/tests/profiling/should_run/toplevel_scc_1.prof.sample - testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quasiquotation/all.T - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/T18263.stderr - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_localname.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TTH_top_splice.stderr - testsuite/tests/rebindable/RebindableFailA.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/Or3.hs - testsuite/tests/rename/should_fail/Or3.stderr - testsuite/tests/rename/should_fail/T12686a.stderr - testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T22478b.hs - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23740i.stderr - + testsuite/tests/rename/should_fail/T25437.hs - + testsuite/tests/rename/should_fail/T25437.stderr - testsuite/tests/rename/should_fail/T5001b.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rename/should_fail/rn_dup.stderr - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyMcGuard.stderr - testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T12709.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/T23153.stderr - + testsuite/tests/rep-poly/T23153b.hs - testsuite/tests/rep-poly/T23154.stderr - + testsuite/tests/rep-poly/T23883a.hs - + testsuite/tests/rep-poly/T23883a.stderr - + testsuite/tests/rep-poly/T23883b.hs - + testsuite/tests/rep-poly/T23883b.stderr - + testsuite/tests/rep-poly/T23883c.hs - + testsuite/tests/rep-poly/T23883c.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rep-poly/all.T - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T13832.stderr - + testsuite/tests/rts/T14497-compact.hs - + testsuite/tests/rts/T14497-compact.stdout - testsuite/tests/rts/T1791/Makefile - + testsuite/tests/rts/T20201a.hs - + testsuite/tests/rts/T20201a.stderr - + testsuite/tests/rts/T20201b.hs - + testsuite/tests/rts/T20201b.stderr - + testsuite/tests/rts/T25560.hs - testsuite/tests/rts/T2783.stderr - testsuite/tests/rts/T7087.stderr - testsuite/tests/rts/T7636.stderr - testsuite/tests/rts/all.T - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/continuations/cont_missing_prompt_err.stderr - testsuite/tests/rts/ipe/IpeStats/Makefile - testsuite/tests/rts/ipe/T24005/t24005.hs - testsuite/tests/rts/linker/all.T - testsuite/tests/runghc/T7859.stderr - testsuite/tests/runghc/T7859.stderr-mingw32 - testsuite/tests/safeHaskell/check/pkg01/all.T - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang09.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang18.hs - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/Orphans.stdout - + testsuite/tests/simd/should_run/T25455.hs - + testsuite/tests/simd/should_run/T25455.stdout - + testsuite/tests/simd/should_run/T25486.hs - + testsuite/tests/simd/should_run/T25486.stdout - + testsuite/tests/simd/should_run/T25561.hs - + testsuite/tests/simd/should_run/T25561.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/int16x8_basic.hs - + testsuite/tests/simd/should_run/int16x8_basic.stdout - + testsuite/tests/simd/should_run/int16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/int16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/int32x4_basic.hs - + testsuite/tests/simd/should_run/int32x4_basic.stdout - + testsuite/tests/simd/should_run/int32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/int32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/int64x2_basic.hs - + testsuite/tests/simd/should_run/int64x2_basic.stdout - + testsuite/tests/simd/should_run/int64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/int64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/int8x16_basic.hs - + testsuite/tests/simd/should_run/int8x16_basic.stdout - + testsuite/tests/simd/should_run/int8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/int8x16_basic_baseline.stdout - testsuite/tests/simd/should_run/simd006.hs - + testsuite/tests/simd/should_run/simd_insert.hs - + testsuite/tests/simd/should_run/simd_insert.stdout - + testsuite/tests/simd/should_run/simd_insert_array.hs - + testsuite/tests/simd/should_run/simd_insert_array.stdout - + testsuite/tests/simd/should_run/simd_insert_array_baseline.hs - + testsuite/tests/simd/should_run/simd_insert_array_baseline.stdout - + testsuite/tests/simd/should_run/simd_insert_baseline.hs - + testsuite/tests/simd/should_run/simd_insert_baseline.stdout - + testsuite/tests/simd/should_run/word16x8_basic.hs - + testsuite/tests/simd/should_run/word16x8_basic.stdout - + testsuite/tests/simd/should_run/word16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/word16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/word32x4_basic.hs - + testsuite/tests/simd/should_run/word32x4_basic.stdout - + testsuite/tests/simd/should_run/word32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/word32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/word64x2_basic.hs - + testsuite/tests/simd/should_run/word64x2_basic.stdout - + testsuite/tests/simd/should_run/word64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/word64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/word8x16_basic.hs - + testsuite/tests/simd/should_run/word8x16_basic.stdout - + testsuite/tests/simd/should_run/word8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/word8x16_basic_baseline.stdout - testsuite/tests/simplCore/T9646/Main.hs - testsuite/tests/simplCore/T9646/StrictPrim.hs - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T21286.stderr - testsuite/tests/simplCore/should_compile/T21694.hs - testsuite/tests/simplCore/should_compile/T21851_2.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T22428.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplCore/should_fail/T7411.stderr - testsuite/tests/simplCore/should_run/T16066.stderr - testsuite/tests/simplCore/should_run/T16893/T16893.stderr - testsuite/tests/simplCore/should_run/T457.stderr - testsuite/tests/simplCore/should_run/T5587.stderr - testsuite/tests/simplCore/should_run/T5625.stderr - testsuite/tests/simplCore/should_run/T7924.stderr - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10279.hs - testsuite/tests/th/T10279.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10796b.stderr - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15360b.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T16980.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23927.stdout - testsuite/tests/th/T24111.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T5976.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T8987.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_exn2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - + testsuite/tests/th/wasm/T25473A.hs - + testsuite/tests/th/wasm/T25473B.hs - + testsuite/tests/th/wasm/all.T - testsuite/tests/type-data/should_run/T22332a.stderr - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/should_compile/FloatFDs.hs - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClasses.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesCore.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesEffects.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesReader.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesState.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadPrimitive.hs - + testsuite/tests/typecheck/should_compile/T16234/DataPeano.hs - + testsuite/tests/typecheck/should_compile/T16234/Main.hs - + testsuite/tests/typecheck/should_compile/T16234/Makefile - + testsuite/tests/typecheck/should_compile/T16234/all.T - testsuite/tests/typecheck/should_compile/T17343.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.stderr - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25597.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T15883d.stderr - testsuite/tests/typecheck/should_fail/T15883e.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20443b.hs - testsuite/tests/typecheck/should_fail/T20443b.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - testsuite/tests/typecheck/should_fail/T22478c.hs - testsuite/tests/typecheck/should_fail/T22478c.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_fail/T23734.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T23778.stderr - testsuite/tests/typecheck/should_fail/T24298.stderr - testsuite/tests/typecheck/should_fail/T24553.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T7279.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_ExistentialEscape.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearMultiAppPat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearMultiPat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearSinglePat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearSinglePat.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_Nonmatching.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBinding.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.hs - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail1.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_run/T10284.stderr - testsuite/tests/typecheck/should_run/T11049.stderr - testsuite/tests/typecheck/should_run/T11715.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T21973a.stderr - testsuite/tests/typecheck/should_run/T22510.stdout - testsuite/tests/typecheck/should_run/T9497a-run.stderr - testsuite/tests/typecheck/should_run/T9497b-run.stderr - testsuite/tests/typecheck/should_run/T9497c-run.stderr - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/UnlGadt1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - testsuite/tests/unsatisfiable/T23816.stderr - testsuite/tests/unsatisfiable/UnsatDefer.stderr - testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - testsuite/tests/vdq-rta/should_compile/T23739_th_pprint1.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/T24396.stderr - testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - testsuite/tests/wcompat-warnings/Template.hs - testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Parsers.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - − utils/ghc-pkg/ghc-pkg.wrapper - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock-test/src/Test/Haddock.hs - utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs - utils/haddock/haddock.cabal - − utils/haddock/haddock.wrapper - utils/haddock/html-test/Main.hs - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug548.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/Instances.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/hp2ps/hp2ps.wrapper - utils/hsc2hs - − utils/iserv/Makefile - utils/iserv/cbits/iservmain.c - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/runghc/runghc.wrapper - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cdd379fb5c93740ed91727b7fc0890dd26a769ea...96fdb8a59aa502380a1a764508ebe502c66db90d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cdd379fb5c93740ed91727b7fc0890dd26a769ea...96fdb8a59aa502380a1a764508ebe502c66db90d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/ec7cbde2/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 13:01:50 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 10 Mar 2025 09:01:50 -0400 Subject: [Git][ghc/ghc][wip/T23109] 85 commits: Deal correctly with Given CallStack constraints Message-ID: <67cee2be4bfab_22530656dccc1052b1@gitlab.mail> Simon Peyton Jones pushed to branch wip/T23109 at Glasgow Haskell Compiler / GHC Commits: e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - f8d1c581 by Simon Peyton Jones at 2025-03-10T10:22:52+00:00 Make newtype instances opaque I think this will help with #23109 Wibbles Allow SelCo for newtype classes Experimental change Wibble Furher wibbles Further improvments Further wibbles esp exprIsConLike Run classop rule first Newtype classops are small needs comments Wibble imports Wibbles Notably: define and use mkNewTypeDictApp Make newtype-class data constructors not inline This variant tries * Making the data constructor for a newtype class not inline * exprIsConApp_maybe treats it like a normal data constructor * CoreToStg discards it (perhaps CorePrep should do that instead) * Some as-it-turns-out unforced changes to corePrepPgm that makes it pass all TyCons, not just the data tycons * Significantly simpler story in mkNewTypeDictApp Wibble Get rid of newtype classes in CorePrep not CoreToStg Comment out bits that I think are no longer necessary * Extra field in ClassOpId, and classOpDictApp_maybe in Simplify.Iteration * Newtype classes being injective * Don't preInlineUnconditionally Dfuns * mkNewTypeDictApp * Zonking of unfoldings (only necessary for those local dfuns) Wibble Allow pushDataCon on ClassTyCon newtypes The fact that there is no *actual* data constructor in the end i kind-of-irrelevant, and we turn out to get quite a lot of class-op (d |> co) where co : C t1 ~R C t2 Wibbles to merge Make newtype classes pretend to be injective Make class datacons be have-no-unfolding Fixes the problem reported in #20689 @Mikolaj wibble Don't make a closure table for type data decls Make UanaryClass a new AlgTyConRhs work in progress, won't compile More wibbles More wibbbles More wibbles Unused bindings Unused import Wibbles Wibbles Wibble Wibbles Remove tyConAlgDataCons_maybe, and tyConSingleAlgDataCon_maybe Rename dontUnbox to canUnboxType (flippping sign) Rebase wibbles More rebase wibbles Yet more rebase wibbles Wibble imports Import wibble Adjust type of evCast ..to avoid gratuitous breakage Re-add mkEvCast, but DEPRECATED - - - - - 0b77b97b by Simon Peyton Jones at 2025-03-10T13:01:32+00:00 Wibbles - - - - - 415 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - − compiler/GHC/Tc/Types/EvTerm.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/RepType.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/TyThing.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/dmdanal/sigs/T21888.stderr - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/numeric/should_compile/T15547.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T17366.stderr - testsuite/tests/simplCore/should_compile/T17966.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/tcplugins/CtIdPlugin.hs - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T21003.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/660c4b1d5aaa730a7b54bf3ad443ab0b7829b33b...0b77b97b6df4553dbc98ae8bfceed0994aa97f56 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/660c4b1d5aaa730a7b54bf3ad443ab0b7829b33b...0b77b97b6df4553dbc98ae8bfceed0994aa97f56 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/1b02f75e/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 13:15:51 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 10 Mar 2025 09:15:51 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/iface-hash-fix Message-ID: <67cee607668ca_2253064d6c2810633d@gitlab.mail> Matthew Pickering pushed new branch wip/iface-hash-fix at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/iface-hash-fix You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/01fc4a8f/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 10 13:17:06 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 10 Mar 2025 09:17:06 -0400 Subject: [Git][ghc/ghc][wip/remove-unused-fields] 12 commits: iface: Store flags in interface files Message-ID: <67cee6522b662_2253066f966810799b@gitlab.mail> Matthew Pickering pushed to branch wip/remove-unused-fields at Glasgow Haskell Compiler / GHC Commits: 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 9baaabb9 by Matthew Pickering at 2025-03-10T13:05:18+00:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - bb2dfa55 by Matthew Pickering at 2025-03-10T13:15:24+00:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 5a2404b8 by Matthew Pickering at 2025-03-10T13:15:24+00:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 90d69296 by Matthew Pickering at 2025-03-10T13:15:24+00:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 91 changed files: - compiler/GHC.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Unique.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ad1f029e3fcc7c5a493cbb5273d86d3b1d1c362...90d69296c0cf9ffeac6c0dadef287aa75c6119ce -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ad1f029e3fcc7c5a493cbb5273d86d3b1d1c362...90d69296c0cf9ffeac6c0dadef287aa75c6119ce You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/909565ed/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 13:17:10 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Mon, 10 Mar 2025 09:17:10 -0400 Subject: [Git][ghc/ghc][wip/T24359] 9 commits: Specialising expressions -- at last Message-ID: <67cee656ad18_22530676fd18108146@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 567556d5 by Simon Peyton Jones at 2025-03-10T14:13:44+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - f3c2eab2 by Simon Peyton Jones at 2025-03-10T14:13:44+01:00 Warn about rules that previously quantified over equalities - - - - - 00c6a218 by sheaf at 2025-03-10T14:13:44+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning flag, -Wrule-lhs-equalities, which controls the warning message that is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 5813bbbf by sheaf at 2025-03-10T14:13:44+01:00 New plan from Feb 10 - - - - - b2990749 by sheaf at 2025-03-10T14:13:44+01:00 move updInertDicts, updInertIrreds - - - - - 8f4eead6 by sheaf at 2025-03-10T14:13:44+01:00 fix isEmptyWorkList - - - - - a1ccfc75 by sheaf at 2025-03-10T14:13:44+01:00 Add mapMaybeTM to TrieMap - - - - - dd144789 by sheaf at 2025-03-10T14:13:44+01:00 remove unionEvBindMap, squash into mapMaybeTM - - - - - 3b419045 by sheaf at 2025-03-10T14:13:44+01:00 new plan from March 7 - - - - - 163 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30049b74c302270ca4e0dfd18ef7eeaee815bd65...3b41904511e9fa60fd4436b8f17f4f23c3681998 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30049b74c302270ca4e0dfd18ef7eeaee815bd65...3b41904511e9fa60fd4436b8f17f4f23c3681998 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/6cc1f77a/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 13:21:22 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 10 Mar 2025 09:21:22 -0400 Subject: [Git][ghc/ghc][wip/remove-unused-fields] Remove mi_hpc field from interface files Message-ID: <67cee752b8745_225306748c40112342@gitlab.mail> Matthew Pickering pushed to branch wip/remove-unused-fields at Glasgow Haskell Compiler / GHC Commits: 80367b42 by Matthew Pickering at 2025-03-10T13:21:02+00:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 12 changed files: - compiler/GHC.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Unit/Module/ModIface.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout Changes: ===================================== compiler/GHC.hs ===================================== @@ -116,7 +116,6 @@ module GHC ( mi_decls, mi_extra_decls, mi_top_env, - mi_hpc, mi_trust, mi_trust_pkg, mi_complete_matches, ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -138,7 +138,6 @@ deSugar hsc_env tcg_default_exports = defaults, tcg_insts = insts, tcg_fam_insts = fam_insts, - tcg_hpc = other_hpc_info, tcg_complete_matches = complete_matches, tcg_self_boot = self_boot }) @@ -179,7 +178,7 @@ deSugar hsc_env then writeMixEntries (hpcDir dflags) mod ticks orig_file2 else return 0 -- dummy hash when none are written pure $ HpcInfo (fromIntegral $ sizeSS ticks) hashNo - _ -> pure $ emptyHpcInfo other_hpc_info + _ -> pure $ emptyHpcInfo ; (msgs, mb_res) <- initDs hsc_env tcg_env $ do { dsEvBinds ev_binds $ \ ds_ev_binds -> do ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1265,7 +1265,6 @@ pprModIface unit_state iface <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) - <+> (if mi_hpc iface then text "[hpc]" else Outputable.empty) <+> integer hiVersion , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -66,7 +66,6 @@ import GHC.Types.Unique.DSet import GHC.Types.TypeEnv import GHC.Types.SourceFile import GHC.Types.TyThing -import GHC.Types.HpcInfo import GHC.Types.CompleteMatch import GHC.Types.Name.Cache @@ -120,14 +119,13 @@ mkPartialIface hsc_env core_prog mod_details mod_summary import_decls , mg_rdr_env = rdr_env , mg_fix_env = fix_env , mg_warns = warns - , mg_hpc_info = hpc_info , mg_safe_haskell = safe_mode , mg_trust_pkg = self_trust , mg_docs = docs } = do self_recomp <- traverse (mkSelfRecomp hsc_env this_mod (ms_hs_hash mod_summary)) usages - return $ mkIface_ hsc_env this_mod core_prog hsc_src deps rdr_env import_decls fix_env warns hpc_info self_trust + return $ mkIface_ hsc_env this_mod core_prog hsc_src deps rdr_env import_decls fix_env warns self_trust safe_mode self_recomp docs mod_details -- | Fully instantiate an interface. Adds fingerprints and potentially code @@ -237,8 +235,7 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program tcg_import_decls = import_decls, tcg_rdr_env = rdr_env, tcg_fix_env = fix_env, - tcg_warns = warns, - tcg_hpc = other_hpc_info + tcg_warns = warns } = do let pluginModules = map lpModule (loadedPlugins (hsc_plugins hsc_env)) @@ -247,7 +244,6 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program (tcg_mod tc_result) (tcg_imports tc_result) (map mi_module pluginModules) - let hpc_info = emptyHpcInfo other_hpc_info usage <- mkRecompUsageInfo hsc_env tc_result docs <- extractDocs (ms_hspp_opts mod_summary) tc_result @@ -256,7 +252,7 @@ mkIfaceTc hsc_env safe_mode mod_details mod_summary mb_program let partial_iface = mkIface_ hsc_env this_mod (fromMaybe [] mb_program) hsc_src deps rdr_env import_decls - fix_env warns hpc_info + fix_env warns (imp_trust_own_pkg imports) safe_mode self_recomp docs mod_details @@ -290,7 +286,7 @@ mkRecompUsageInfo hsc_env tc_result = do mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> Dependencies -> GlobalRdrEnv -> [ImportUserSpec] - -> NameEnv FixItem -> Warnings GhcRn -> HpcInfo + -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode -> Maybe ModIfaceSelfRecomp @@ -299,7 +295,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> PartialModIface mkIface_ hsc_env this_mod core_prog hsc_src deps rdr_env import_decls fix_env src_warns - hpc_info pkg_trust_req safe_mode self_recomp + pkg_trust_req safe_mode self_recomp docs ModDetails{ md_defaults = defaults, md_insts = insts, @@ -375,7 +371,6 @@ mkIface_ hsc_env & set_mi_top_env rdrs & set_mi_decls decls & set_mi_extra_decls extra_decls - & set_mi_hpc (isHpcUsed hpc_info) & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -77,7 +77,6 @@ import GHC.Types.SrcLoc as SrcLoc import GHC.Types.Basic ( TopLevelFlag(..) ) import GHC.Types.SourceText import GHC.Types.Id -import GHC.Types.HpcInfo import GHC.Types.PkgQual import GHC.Types.GREInfo (ConInfo(..), ConFieldInfo (..), ConLikeInfo (ConIsData)) @@ -201,7 +200,7 @@ with yes we have gone with no for now. -- Note: Do the non SOURCE ones first, so that we get a helpful warning -- for SOURCE ones that are unnecessary rnImports :: [(LImportDecl GhcPs, SDoc)] - -> RnM ([LImportDecl GhcRn], [ImportUserSpec], GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)], AnyHpcUsage) + -> RnM ([LImportDecl GhcRn], [ImportUserSpec], GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)]) rnImports imports = do tcg_env <- getGblEnv -- NB: want an identity module here, because it's OK for a signature @@ -212,10 +211,10 @@ rnImports imports = do stuff1 <- mapAndReportM (rnImportDecl this_mod) ordinary stuff2 <- mapAndReportM (rnImportDecl this_mod) source -- Safe Haskell: See Note [Tracking Trust Transitively] - let (decls, imp_user_spec, rdr_env, imp_avails, defaults, hpc_usage) = combine (stuff1 ++ stuff2) + let (decls, imp_user_spec, rdr_env, imp_avails, defaults) = combine (stuff1 ++ stuff2) -- Update imp_boot_mods if imp_direct_mods mentions any of them let merged_import_avail = clobberSourceImports imp_avails - return (decls, imp_user_spec, rdr_env, merged_import_avail, defaults, hpc_usage) + return (decls, imp_user_spec, rdr_env, merged_import_avail, defaults) where clobberSourceImports imp_avails = @@ -228,24 +227,23 @@ rnImports imports = do combJ (GWIB _ IsBoot) x = Just x combJ r _ = Just r -- See Note [Combining ImportAvails] - combine :: [(LImportDecl GhcRn, ImportUserSpec, GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)], AnyHpcUsage)] - -> ([LImportDecl GhcRn], [ImportUserSpec], GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)], AnyHpcUsage) + combine :: [(LImportDecl GhcRn, ImportUserSpec, GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)])] + -> ([LImportDecl GhcRn], [ImportUserSpec], GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)]) combine ss = - let (decls, imp_user_spec, rdr_env, imp_avails, defaults, hpc_usage, finsts) = foldr + let (decls, imp_user_spec, rdr_env, imp_avails, defaults, finsts) = foldr plus - ([], [], emptyGlobalRdrEnv, emptyImportAvails, [], False, emptyModuleSet) + ([], [], emptyGlobalRdrEnv, emptyImportAvails, [], emptyModuleSet) ss in (decls, imp_user_spec, rdr_env, imp_avails { imp_finsts = moduleSetElts finsts }, - defaults, hpc_usage) + defaults) - plus (decl, us, gbl_env1, imp_avails1, defaults1, hpc_usage1) - (decls, uss, gbl_env2, imp_avails2, defaults2, hpc_usage2, finsts_set) + plus (decl, us, gbl_env1, imp_avails1, defaults1) + (decls, uss, gbl_env2, imp_avails2, defaults2, finsts_set) = ( decl:decls, us:uss, gbl_env1 `plusGlobalRdrEnv` gbl_env2, imp_avails1' `plusImportAvails` imp_avails2, defaults1 ++ defaults2, - hpc_usage1 || hpc_usage2, extendModuleSetList finsts_set new_finsts ) where imp_avails1' = imp_avails1 { imp_finsts = [] } @@ -309,7 +307,7 @@ Running generateModules from #14693 with DEPTH=16, WIDTH=30 finishes in -- 4. A boolean 'AnyHpcUsage' which is true if the imported module -- used HPC. rnImportDecl :: Module -> (LImportDecl GhcPs, SDoc) - -> RnM (LImportDecl GhcRn, ImportUserSpec , GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)], AnyHpcUsage) + -> RnM (LImportDecl GhcRn, ImportUserSpec , GlobalRdrEnv, ImportAvails, [(Module, IfaceDefault)]) rnImportDecl this_mod (L loc decl@(ImportDecl { ideclName = loc_imp_mod_name , ideclPkgQual = raw_pkg_qual @@ -438,7 +436,7 @@ rnImportDecl this_mod } return (L loc new_imp_decl, ImpUserSpec imp_spec imp_user_list, gbl_env, - imports, (,) (mi_module iface) <$> mi_defaults iface, mi_hpc iface) + imports, (,) (mi_module iface) <$> mi_defaults iface) -- | Rename raw package imports ===================================== compiler/GHC/Tc/Module.hs ===================================== @@ -459,7 +459,7 @@ isTypeSubsequenceOf (t1:t1s) (t2:t2s) tcRnImports :: HscEnv -> [(LImportDecl GhcPs, SDoc)] -> TcM ([NonEmpty ClassDefaults], TcGblEnv) tcRnImports hsc_env import_decls - = do { (rn_imports, imp_user_spec, rdr_env, imports, defaults, hpc_info) <- rnImports import_decls ; + = do { (rn_imports, imp_user_spec, rdr_env, imports, defaults) <- rnImports import_decls ; ; this_mod <- getModule ; gbl_env <- getGblEnv @@ -494,8 +494,7 @@ tcRnImports hsc_env import_decls tcg_default = foldMap subsume tc_defaults, tcg_inst_env = tcg_inst_env gbl `unionInstEnv` home_insts, tcg_fam_inst_env = extendFamInstEnvList (tcg_fam_inst_env gbl) - home_fam_insts, - tcg_hpc = hpc_info + home_fam_insts }) $ do { ; traceRn "rn1" (ppr (imp_direct_dep_mods imports)) ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -154,7 +154,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique.FM import GHC.Types.Basic import GHC.Types.CostCentre.State -import GHC.Types.HpcInfo import GHC.Data.IOEnv import GHC.Data.Bag @@ -641,10 +640,6 @@ data TcGblEnv tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName)), -- ^ Maybe Haddock header docs and Maybe located module name - tcg_hpc :: !AnyHpcUsage, -- ^ @True@ if any part of the - -- prog uses hpc instrumentation. - -- NB. BangPattern is to fix a leak, see #15111 - tcg_self_boot :: SelfBootInfo, -- ^ Whether this module has a -- corresponding hi-boot file ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -358,7 +358,6 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this tcg_zany_n = zany_n_var, tcg_keep = keep_var, tcg_hdr_info = (Nothing,Nothing), - tcg_hpc = False, tcg_main = Nothing, tcg_self_boot = NoSelfBoot, tcg_safe_infer = infer_var, ===================================== compiler/GHC/Types/HpcInfo.hs ===================================== @@ -1,9 +1,7 @@ -- | Haskell Program Coverage (HPC) support module GHC.Types.HpcInfo ( HpcInfo (..) - , AnyHpcUsage , emptyHpcInfo - , isHpcUsed ) where @@ -16,19 +14,8 @@ data HpcInfo , hpcInfoHash :: Int } | NoHpcInfo - { hpcUsed :: AnyHpcUsage -- ^ Is hpc used anywhere on the module \*tree\*? - } --- | This is used to signal if one of my imports used HPC instrumentation --- even if there is no module-local HPC usage -type AnyHpcUsage = Bool -emptyHpcInfo :: AnyHpcUsage -> HpcInfo +emptyHpcInfo :: HpcInfo emptyHpcInfo = NoHpcInfo --- | Find out if HPC is used by this module or any of the modules --- it depends upon -isHpcUsed :: HpcInfo -> AnyHpcUsage -isHpcUsed (HpcInfo {}) = True -isHpcUsed (NoHpcInfo { hpcUsed = used }) = used - ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -27,7 +27,6 @@ module GHC.Unit.Module.ModIface , mi_insts , mi_fam_insts , mi_rules - , mi_hpc , mi_trust , mi_trust_pkg , mi_complete_matches @@ -56,7 +55,6 @@ module GHC.Unit.Module.ModIface , set_mi_extra_decls , set_mi_foreign , set_mi_top_env - , set_mi_hpc , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches @@ -114,7 +112,6 @@ import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env -import GHC.Types.HpcInfo import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Types.SourceFile @@ -301,8 +298,6 @@ data ModIface_ (phase :: ModIfacePhase) mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc_ :: !AnyHpcUsage, - -- ^ True if this program uses Hpc at any point in the program. mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. @@ -482,7 +477,6 @@ instance Binary ModIface where mi_insts_ = insts, mi_fam_insts_ = fam_insts, mi_rules_ = rules, - mi_hpc_ = hpc_info, mi_trust_ = trust, mi_trust_pkg_ = trust_pkg, mi_complete_matches_ = complete_matches, @@ -522,7 +516,6 @@ instance Binary ModIface where put_ bh fam_insts lazyPut bh rules put_ bh orphan_hash - put_ bh hpc_info put_ bh trust put_ bh trust_pkg put_ bh complete_matches @@ -552,7 +545,6 @@ instance Binary ModIface where fam_insts <- {-# SCC "bin_fam_insts" #-} get bh rules <- {-# SCC "bin_rules" #-} lazyGet bh orphan_hash <- get bh - hpc_info <- get bh trust <- get bh trust_pkg <- get bh complete_matches <- get bh @@ -579,7 +571,6 @@ instance Binary ModIface where mi_insts_ = insts, mi_fam_insts_ = fam_insts, mi_rules_ = rules, - mi_hpc_ = hpc_info, mi_trust_ = trust, mi_trust_pkg_ = trust_pkg, -- And build the cached values @@ -623,7 +614,6 @@ emptyPartialModIface mod mi_extra_decls_ = Nothing, mi_foreign_ = emptyIfaceForeign, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_hpc_ = False, mi_trust_ = noIfaceTrustInfo, mi_trust_pkg_ = False, mi_complete_matches_ = [], @@ -674,7 +664,7 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ , mi_exports_, mi_fixities_, mi_warns_, mi_anns_ , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ - , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_fam_insts_, mi_rules_, mi_trust_, mi_trust_pkg_ , mi_complete_matches_, mi_docs_, mi_final_exts_ , mi_ext_fields_ }) = rnf mi_module_ @@ -694,7 +684,6 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf mi_insts_ `seq` rnf mi_fam_insts_ `seq` rnf mi_rules_ - `seq` rnf mi_hpc_ `seq` mi_trust_ `seq` rnf mi_trust_pkg_ `seq` rnf mi_complete_matches_ @@ -828,9 +817,6 @@ set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreig set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } -set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase -set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } - set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } @@ -924,7 +910,6 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} {-# INLINE mi_rules #-} -{-# INLINE mi_hpc #-} {-# INLINE mi_trust #-} {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} @@ -940,7 +925,7 @@ pattern ModIface :: [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> ModIface_ phase pattern ModIface @@ -960,7 +945,6 @@ pattern ModIface , mi_insts , mi_fam_insts , mi_rules - , mi_hpc , mi_trust , mi_trust_pkg , mi_complete_matches @@ -986,7 +970,6 @@ pattern ModIface , mi_insts_ = mi_insts , mi_fam_insts_ = mi_fam_insts , mi_rules_ = mi_rules - , mi_hpc_ = mi_hpc , mi_trust_ = mi_trust , mi_trust_pkg_ = mi_trust_pkg , mi_complete_matches_ = mi_complete_matches ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -164,7 +164,6 @@ GHC.Types.ForeignStubs GHC.Types.GREInfo GHC.Types.Hint GHC.Types.Hint.Ppr -GHC.Types.HpcInfo GHC.Types.Id GHC.Types.Id.Info GHC.Types.Id.Make ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -187,7 +187,6 @@ GHC.Types.ForeignStubs GHC.Types.GREInfo GHC.Types.Hint GHC.Types.Hint.Ppr -GHC.Types.HpcInfo GHC.Types.Id GHC.Types.Id.Info GHC.Types.Id.Make View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/80367b42993ebb65b3b957cf993f0c444504122e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/80367b42993ebb65b3b957cf993f0c444504122e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/d0a9e768/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 13:21:40 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 10 Mar 2025 09:21:40 -0400 Subject: [Git][ghc/ghc][wip/nfdata-forcing] 5 commits: Take into account all flags when computing iface_hash Message-ID: <67cee76429678_225306748c401127e6@gitlab.mail> Matthew Pickering pushed to branch wip/nfdata-forcing at Glasgow Haskell Compiler / GHC Commits: 9baaabb9 by Matthew Pickering at 2025-03-10T13:05:18+00:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - bb2dfa55 by Matthew Pickering at 2025-03-10T13:15:24+00:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 5a2404b8 by Matthew Pickering at 2025-03-10T13:15:24+00:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 80367b42 by Matthew Pickering at 2025-03-10T13:21:02+00:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - ba407615 by Matthew Pickering at 2025-03-10T13:21:02+00:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 46 changed files: - compiler/GHC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - libraries/ghc-boot/GHC/Serialized.hs - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - utils/haddock/haddock-api/src/Haddock/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4dae0101f987c498046307b390c23ece18606b19...ba4076150ba65a0401b3f80428bd2f30c22ad342 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4dae0101f987c498046307b390c23ece18606b19...ba4076150ba65a0401b3f80428bd2f30c22ad342 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/3f14543b/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 10 15:05:35 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 10 Mar 2025 11:05:35 -0400 Subject: [Git][ghc/ghc][wip/buildplan] 2 commits: driver: implement --buildplan major mode to extract BuildPlan info from dependency analysis Message-ID: <67ceffbf7737_25aa2f16e70c1447a@gitlab.mail> Cheng Shao pushed to branch wip/buildplan at Glasgow Haskell Compiler / GHC Commits: f7eed8ac by Cheng Shao at 2025-03-10T15:05:17+00:00 driver: implement --buildplan major mode to extract BuildPlan info from dependency analysis - - - - - 267e74e1 by Cheng Shao at 2025-03-10T15:05:22+00:00 track non-hs deps - - - - - 4 changed files: - compiler/GHC/Driver/Make.hs - compiler/GHC/Unit/Module/Graph.hs - docs/users_guide/expected-undocumented-flags.txt - ghc/Main.hs Changes: ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -8,6 +8,7 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- ----------------------------------------------------------------------------- -- @@ -20,6 +21,10 @@ module GHC.Driver.Make ( depanal, depanalE, depanalPartial, checkHomeUnitsClosed, load, loadWithCache, load', AnyGhcDiagnostic, LoadHowMuch(..), ModIfaceCache(..), noIfaceCache, newIfaceCache, + ModuleGraphNodeWithBootFile(..), + BuildPlan(..), + computeBuildPlan, + speculateIface, instantiationNodes, downsweep, @@ -73,6 +78,7 @@ import GHC.Driver.MakeSem import GHC.Parser.Header import GHC.ByteCode.Types +import GHC.Iface.Binary import GHC.Iface.Load ( cannotFindModule ) import GHC.IfaceToCore ( typecheckIface ) import GHC.Iface.Recomp ( RecompileRequired(..), CompileReason(..) ) @@ -92,6 +98,7 @@ import GHC.Utils.Misc import GHC.Utils.Error import GHC.Utils.Logger import GHC.Utils.Fingerprint +import GHC.Utils.Json import GHC.Utils.TmpFs import GHC.Types.Basic @@ -119,6 +126,7 @@ import qualified Data.Set as Set import Control.Concurrent ( newQSem, waitQSem, signalQSem, ThreadId, killThread, forkIOWithUnmask ) import qualified GHC.Conc as CC import Control.Concurrent.MVar +import Control.Exception (evaluate) import Control.Monad import Control.Monad.Trans.Except ( ExceptT(..), runExceptT, throwE ) import qualified Control.Monad.Catch as MC @@ -482,6 +490,29 @@ newIfaceCache = do load :: GhcMonad f => LoadHowMuch -> f SuccessFlag load how_much = loadWithCache noIfaceCache mkUnknownDiagnostic how_much +computeBuildPlan :: GhcMonad m => m [BuildPlan] +computeBuildPlan = do + msg <- mkBatchMsg <$> getSession + (errs, mod_graph) <- depanalE mkUnknownDiagnostic (Just msg) [] False + unless (isEmptyMessages errs) $ throwErrors (fmap GhcDriverMessage errs) + modifySession $ \hsc_env -> hsc_env { hsc_mod_graph = mod_graph } + guessOutputFile + + liftIO $ evaluate $ createBuildPlan mod_graph Nothing + +speculateIface :: GhcMonad m => ModSummary -> m (Maybe ModIface) +speculateIface ms = withSession $ \hsc_env -> liftIO $ do + let dflags = hsc_dflags hsc_env + profile = targetProfile dflags + name_cache = hsc_NC hsc_env + file_path + | ways dflags `hasWay` WayDyn = msDynHiFilePath ms + | otherwise = msHiFilePath ms + res <- tryMost $ readBinIface profile name_cache CheckHiWay QuietBinIFace file_path + pure $ case res of + Right iface -> Just iface + _ -> Nothing + mkBatchMsg :: HscEnv -> Messager mkBatchMsg hsc_env = if length (hsc_all_home_unit_ids hsc_env) > 1 @@ -571,6 +602,19 @@ instance Outputable BuildPlan where ppr (ResolvedCycle mgn) = text "ResolvedCycle:" <+> ppr mgn ppr (UnresolvedCycle mgn) = text "UnresolvedCycle:" <+> ppr mgn +instance ToJson BuildPlan where + json (SingleModule mgn) = JSObject [ + ("type", json "single-module"), + ("node", json mgn) + ] + json (ResolvedCycle mgn) = JSObject [ + ("type", json "resolved-cycle"), + ("nodes", JSArray $ map (either json (\(ModuleGraphNodeWithBootFile mgn _) -> json mgn)) mgn) + ] + json (UnresolvedCycle mgn) = JSObject [ + ("type", json "unresolved-cycle"), + ("nodes", JSArray $ map json mgn) + ] -- Just used for an assertion countMods :: BuildPlan -> Int ===================================== compiler/GHC/Unit/Module/Graph.hs ===================================== @@ -117,9 +117,11 @@ import GHC.Types.SourceFile ( hscSourceString, isHsigFile ) import GHC.Unit.Module.ModSummary import GHC.Unit.Types +import GHC.Utils.Json import GHC.Utils.Outputable import GHC.Unit.Module.ModIface import GHC.Utils.Misc ( partitionWith ) +import GHC.Utils.Panic import System.FilePath import qualified Data.Map as Map @@ -248,6 +250,29 @@ instance Outputable ModuleGraphNode where LinkNode uid _ -> text "LN:" <+> ppr uid UnitNode _ uid -> text "P:" <+> ppr uid +instance ToJson ModuleGraphNode where + json (InstantiationNode {}) = panic "--buildplan: backpack not supported" + json (ModuleNode nks ms) = JSObject [ + ("node-kind", json "compile"), + ("dependencies", JSArray $ map json nks), + ("unit_id", JSString $ unitIdString $ ms_unitid ms), + ("module_name", JSString $ moduleNameString $ moduleName $ ms_mod ms), + ("is_boot", JSBool $ isBootSummary ms == IsBoot), + ("hs_path", JSString $ normalise $ msHsFilePath ms), + ("uses_th", JSBool $ isTemplateHaskellOrQQNonBoot ms) + ] + json (LinkNode nks uid) = JSObject [ + ("node-kind", json "link"), + ("dependencies", JSArray $ map json nks), + ("unit_id", JSString $ unitIdString uid) + ] + json (UnitNode nks uid) = JSObject [ + ("node-kind", json "unit"), + ("dependencies", JSArray $ map (JSString . unitIdString) nks), + ("unit_id", JSString $ unitIdString uid) + ] + + instance Eq ModuleGraphNode where (==) = (==) `on` mkNodeKey @@ -480,6 +505,12 @@ instance Outputable NodeKey where ppr (NodeKey_Link uid) = ppr uid ppr (NodeKey_ExternalUnit uid) = ppr uid +instance ToJson NodeKey where + json (NodeKey_Unit {}) = panic "--buildplan: backpack not supported" + json (NodeKey_Module (ModNodeKeyWithUid mnwib uid)) = JSObject $ [("unit_id", JSString $ unitIdString uid), ("module_name", JSString $ moduleNameString $ gwib_mod mnwib), ("is_boot", JSBool $ gwib_isBoot mnwib == IsBoot)] + json (NodeKey_Link uid) = JSObject [("unit_id", JSString $ unitIdString uid)] + json (NodeKey_ExternalUnit uid) = JSObject [("unit_id", JSString $ unitIdString uid)] + mkNodeKey :: ModuleGraphNode -> NodeKey mkNodeKey = \case InstantiationNode _ iu -> NodeKey_Unit iu ===================================== docs/users_guide/expected-undocumented-flags.txt ===================================== @@ -1,6 +1,7 @@ -#include --abi-hash --backpack +--buildplan --show-packages -Onot -Walternative-layout-rule-transitional ===================================== ghc/Main.hs ===================================== @@ -1,6 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NondecreasingIndentation #-} +{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TupleSections #-} {-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-} @@ -17,7 +18,7 @@ module Main (main) where -- The official GHC API import qualified GHC import GHC (parseTargetFiles, Ghc, GhcMonad(..), - LoadHowMuch(..) ) + LoadHowMuch(..), moduleName, moduleNameString ) import GHC.Driver.Backend import GHC.Driver.CmdLine @@ -28,6 +29,7 @@ import GHC.Driver.Phases import GHC.Driver.Session import GHC.Driver.Ppr import GHC.Driver.Pipeline ( oneShot, compileFile ) +import GHC.Driver.Make ( ModuleGraphNodeWithBootFile(..), BuildPlan(..), computeBuildPlan, speculateIface ) import GHC.Driver.MakeFile ( doMkDependHS ) import GHC.Driver.Backpack ( doBackpack ) import GHC.Driver.Plugins @@ -49,11 +51,14 @@ import GHC.Unit (UnitId) import GHC.Unit.Home.PackageTable import qualified GHC.Unit.Home.Graph as HUG import GHC.Unit.Module ( ModuleName, mkModuleName ) +import GHC.Unit.Module.Deps +import GHC.Unit.Module.Graph import GHC.Unit.Module.ModIface import GHC.Unit.State ( pprUnits, pprUnitsSimple, emptyUnitState ) +import GHC.Unit.Module.ModSummary import GHC.Unit.Finder ( findImportedModule, FindResult(..) ) import qualified GHC.Unit.State as State -import GHC.Unit.Types ( IsBootInterface(..) ) +import GHC.Unit.Types ( IsBootInterface(..), unitIdString ) import GHC.Types.Basic ( failed ) import GHC.Types.SrcLoc @@ -68,6 +73,8 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Monad ( liftIO, mapMaybeM ) import GHC.Utils.Binary ( openBinMem, put_ ) import GHC.Utils.Logger +import GHC.Utils.Json +import qualified GHC.Utils.Ppr as Ppr import GHC.Settings.Config import GHC.Settings.Constants @@ -93,6 +100,7 @@ import Control.Monad import Control.Monad.Trans.Class import Control.Monad.Trans.Except (throwE, runExceptT) import Data.Char +import Data.Foldable import Data.List ( isPrefixOf, partition, intercalate, (\\) ) import qualified Data.Set as Set import Prelude @@ -182,6 +190,7 @@ main' postLoadMode units dflags0 args flagWarnings = do DoEval _ -> (CompManager, interpreterBackend, LinkInMemory) DoRun -> (CompManager, interpreterBackend, LinkInMemory) DoMake -> (CompManager, dflt_backend, LinkBinary) + DoBuildPlan _ -> (CompManager, dflt_backend, LinkBinary) DoBackpack -> (CompManager, dflt_backend, LinkBinary) DoMkDependHS -> (MkDepend, dflt_backend, LinkBinary) DoAbiHash -> (OneShot, dflt_backend, LinkBinary) @@ -309,6 +318,7 @@ main' postLoadMode units dflags0 args flagWarnings = do (hsc_NC hsc_env) f DoMake -> doMake units srcs + DoBuildPlan f -> doBuildPlan f units srcs DoMkDependHS -> doMkDependHS (map fst srcs) StopBefore p -> liftIO (oneShot hsc_env p srcs) DoInteractive -> ghciUI units srcs Nothing @@ -502,6 +512,7 @@ data PostLoadMode | StopBefore StopPhase -- ghc -E | -C | -S -- StopBefore StopLn is the default | DoMake -- ghc --make + | DoBuildPlan FilePath -- ghc --buildplan | DoBackpack -- ghc --backpack foo.bkp | DoInteractive -- ghc --interactive | DoEval [String] -- ghc -e foo -e bar => DoEval ["bar", "foo"] @@ -519,6 +530,9 @@ doRunMode = mkPostLoadMode DoRun doAbiHashMode = mkPostLoadMode DoAbiHash showUnitsMode = mkPostLoadMode ShowPackages +doBuildPlanMode :: FilePath -> Mode +doBuildPlanMode f = mkPostLoadMode (DoBuildPlan f) + showInterfaceMode :: FilePath -> Mode showInterfaceMode fp = mkPostLoadMode (ShowInterface fp) @@ -584,6 +598,7 @@ isLinkMode _ = False isCompManagerMode :: PostLoadMode -> Bool isCompManagerMode DoRun = True isCompManagerMode DoMake = True +isCompManagerMode (DoBuildPlan _) = True isCompManagerMode DoInteractive = True isCompManagerMode (DoEval _) = True isCompManagerMode _ = False @@ -665,6 +680,7 @@ mode_flags = , defFlag "S" (PassFlag (setMode (stopBeforeMode StopAs))) , defFlag "-run" (PassFlag (setMode doRunMode)) , defFlag "-make" (PassFlag (setMode doMakeMode)) + , defFlag "-buildplan" (HasArg (\f -> setMode (doBuildPlanMode f) "--buildplan")) , defFlag "unit" (SepArg (\s -> addUnit s "-unit")) , defFlag "-backpack" (PassFlag (setMode doBackpackMode)) , defFlag "-interactive" (PassFlag (setMode doInteractiveMode)) @@ -764,6 +780,39 @@ doMake units targets = do ok_flag <- GHC.load LoadAllTargets when (failed ok_flag) (liftIO $ exitWith (ExitFailure 1)) +doBuildPlan :: FilePath -> [String] -> [(String, Maybe Phase)] -> Ghc () +doBuildPlan out units targets = do + hs_srcs <- case NE.nonEmpty units of + Just ne_units -> do + initMulti ne_units + Nothing -> do + s <- initMake targets + return $ map (uncurry (,Nothing,)) s + build_plan <- case hs_srcs of + [] -> pure [] + _ -> do + targets' <- mapM (\(src, uid, phase) -> GHC.guessTarget src uid phase) hs_srcs + GHC.setTargets targets' + computeBuildPlan + let on_usage ms (UsageFile {usg_file_path, usg_file_nonhs = True}) acc = JSObject [("unit_id", JSString $ unitIdString $ ms_unitid ms), ("module_name", JSString $ moduleNameString $ moduleName $ ms_mod ms), ("usage_file", JSString $ unpackFS usg_file_path)] : acc + on_usage _ _ acc = acc + + on_mod_summary ms acc = do + maybe_iface <- speculateIface ms + pure $ case maybe_iface of + Just iface | Just usages <- mi_usages iface -> foldr (on_usage ms) acc usages + Nothing -> acc + + on_node (ModuleNode _ ms) acc = on_mod_summary ms acc + on_node _ acc = pure acc + + on_buildplan (SingleModule node) acc = on_node node acc + on_buildplan (ResolvedCycle nodes) acc = foldrM on_node acc $ map (either id (\(ModuleGraphNodeWithBootFile node _) -> node)) nodes + on_buildplan (UnresolvedCycle nodes) acc = foldrM on_node acc nodes + usage_files <- foldrM on_buildplan [] build_plan + liftIO $ withBinaryFile out WriteMode $ \h -> + printSDoc defaultSDocContext Ppr.OneLineMode h $ renderJSON $ JSObject [("build_plan", JSArray $ map json build_plan), ("usage_files", JSArray usage_files)] + initMake :: [(String,Maybe Phase)] -> Ghc [(String, Maybe Phase)] initMake srcs = do let (hs_srcs, non_hs_srcs) = partition isHaskellishTarget srcs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96fdb8a59aa502380a1a764508ebe502c66db90d...267e74e1b1106d656806d4731efbaf281eb62537 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96fdb8a59aa502380a1a764508ebe502c66db90d...267e74e1b1106d656806d4731efbaf281eb62537 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/29040b95/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 15:44:25 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 10 Mar 2025 11:44:25 -0400 Subject: [Git][ghc/ghc][wip/nfdata-forcing] interfaces: Ensure that forceModIface deeply forces a ModIface Message-ID: <67cf08d8ee39e_25aa2f654604160c4@gitlab.mail> Matthew Pickering pushed to branch wip/nfdata-forcing at Glasgow Haskell Compiler / GHC Commits: b1560f71 by Matthew Pickering at 2025-03-10T15:43:47+00:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 29 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - libraries/ghc-boot/GHC/Serialized.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Core.hs ===================================== @@ -120,6 +120,8 @@ import Data.List.NonEmpty (nonEmpty) import qualified Data.List.NonEmpty as NE import Data.Word +import Control.DeepSeq + infixl 4 `mkApps`, `mkTyApps`, `mkVarApps`, `App`, `mkCoApps` -- Left associative, so that we can say (f `mkTyApps` xs `mkVarApps` ys) @@ -1185,6 +1187,10 @@ instance Binary IsOrphan where n <- get bh return $ NotOrphan n +instance NFData IsOrphan where + rnf IsOrphan = () + rnf (NotOrphan n) = rnf n + {- Note [Orphans] ~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Coercion/Axiom.hs ===================================== @@ -58,6 +58,7 @@ import GHC.Types.SrcLoc import qualified Data.Data as Data import Data.Array import Data.List ( mapAccumL ) +import Control.DeepSeq {- Note [Coercion axiom branches] @@ -559,6 +560,11 @@ instance Binary Role where 3 -> return Phantom _ -> panic ("get Role " ++ show tag) +instance NFData Role where + rnf Nominal = () + rnf Representational = () + rnf Phantom = () + {- ************************************************************************ * * ===================================== compiler/GHC/Core/DataCon.hs ===================================== @@ -112,6 +112,7 @@ import qualified Data.ByteString.Lazy as LBS import qualified Data.Data as Data import Data.Char import Data.List( find ) +import Control.DeepSeq {- Note [Data constructor representation] @@ -1075,6 +1076,16 @@ instance Binary SrcUnpackedness where 1 -> return SrcUnpack _ -> return NoSrcUnpack +instance NFData SrcStrictness where + rnf SrcLazy = () + rnf SrcStrict = () + rnf NoSrcStrict = () + +instance NFData SrcUnpackedness where + rnf SrcNoUnpack = () + rnf SrcUnpack = () + rnf NoSrcUnpack = () + -- | Compare strictness annotations eqHsBang :: HsImplBang -> HsImplBang -> Bool eqHsBang HsLazy HsLazy = True ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -994,6 +994,11 @@ instance Outputable FunSel where ppr SelArg = text "arg" ppr SelRes = text "res" +instance NFData FunSel where + rnf SelMult = () + rnf SelArg = () + rnf SelRes = () + instance Binary CoSel where put_ bh (SelTyCon n r) = do { putByte bh 0; put_ bh n; put_ bh r } put_ bh SelForAll = putByte bh 1 @@ -1010,9 +1015,9 @@ instance Binary CoSel where _ -> return (SelFun SelRes) } instance NFData CoSel where - rnf (SelTyCon n r) = n `seq` r `seq` () + rnf (SelTyCon n r) = rnf n `seq` rnf r `seq` () rnf SelForAll = () - rnf (SelFun fs) = fs `seq` () + rnf (SelFun fs) = rnf fs `seq` () -- | A semantically more meaningful type to represent what may or may not be a -- useful 'Coercion'. ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -181,6 +181,7 @@ import GHC.Settings.Constants import GHC.Utils.Misc import GHC.Types.Unique.Set import GHC.Unit.Module +import Control.DeepSeq import Language.Haskell.Syntax.Basic (FieldLabelString(..)) @@ -731,6 +732,11 @@ instance Binary TyConBndrVis where 0 -> return AnonTCB _ -> do { vis <- get bh; return (NamedTCB vis) } } +instance NFData TyConBndrVis where + rnf AnonTCB = () + rnf (NamedTCB vis) = rnf vis + + {- ********************************************************************* * * @@ -2916,6 +2922,10 @@ instance Binary Injectivity where _ -> do { xs <- get bh ; return (Injective xs) } } +instance NFData Injectivity where + rnf NotInjective = () + rnf (Injective xs) = rnf xs + -- | Returns whether or not this 'TyCon' is definite, or a hole -- that may be filled in at some later point. See Note [Skolem abstract data] tyConSkolem :: TyCon -> Bool ===================================== compiler/GHC/Data/Strict.hs ===================================== @@ -22,10 +22,15 @@ import GHC.Prelude hiding (Maybe(..), Either(..)) import Control.Applicative import Data.Semigroup import Data.Data +import Control.DeepSeq data Maybe a = Nothing | Just !a deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data) +instance NFData a => NFData (Maybe a) where + rnf Nothing = () + rnf (Just x) = rnf x + fromMaybe :: a -> Maybe a -> a fromMaybe d Nothing = d fromMaybe _ (Just x) = x ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -76,7 +76,10 @@ instance Binary Language where get bh = toEnum <$> get bh instance NFData Language where - rnf x = x `seq` () + rnf Haskell98 = () + rnf Haskell2010 = () + rnf GHC2021 = () + rnf GHC2024 = () data OnOff a = On a | Off a ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -111,7 +111,5 @@ instance Outputable ModIfaceSelfRecomp where ])] instance NFData ModIfaceSelfRecomp where - -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so - -- I left it as a shallow force. rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -94,7 +94,7 @@ import GHC.Utils.Binary.Typeable () -- instance Binary AnnPayload import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith, - seqList, zipWithEqual ) + zipWithEqual ) import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..)) @@ -539,6 +539,14 @@ instance Binary IfaceLFInfo where 4 -> pure IfLFUnlifted _ -> panic "Invalid byte" +instance NFData IfaceLFInfo where + rnf = \case + IfLFReEntrant arity -> rnf arity + IfLFThunk updatable mb_fun -> rnf updatable `seq` rnf mb_fun + IfLFCon con -> rnf con + IfLFUnknown fun_flag -> rnf fun_flag + IfLFUnlifted -> () + {- Note [Versioning of instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2767,6 +2775,10 @@ getUnfoldingCache bh = do return (UnfoldingCache { uf_is_value = hnf, uf_is_conlike = conlike , uf_is_work_free = wf, uf_expandable = exp }) +seqUnfoldingCache :: IfUnfoldingCache -> () +seqUnfoldingCache (UnfoldingCache hnf conlike wf exp) = + rnf hnf `seq` rnf conlike `seq` rnf wf `seq` rnf exp `seq` () + infixl 9 .<<|. (.<<|.) :: (Num a, Bits a) => a -> Bool -> a x .<<|. b = (if b then (`setBit` 0) else id) (x `shiftL` 1) @@ -2837,12 +2849,10 @@ instance Binary IfaceExpr where putByte bh 13 put_ bh a put_ bh b - put_ bh (IfaceLitRubbish TypeLike r) = do + put_ bh (IfaceLitRubbish torc r) = do putByte bh 14 put_ bh r - put_ bh (IfaceLitRubbish ConstraintLike r) = do - putByte bh 15 - put_ bh r + put_ bh torc get bh = do h <- getByte bh case h of @@ -2886,9 +2896,8 @@ instance Binary IfaceExpr where b <- get bh return (IfaceECase a b) 14 -> do r <- get bh - return (IfaceLitRubbish TypeLike r) - 15 -> do r <- get bh - return (IfaceLitRubbish ConstraintLike r) + torc <- get bh + return (IfaceLitRubbish torc r) _ -> panic ("get IfaceExpr " ++ show h) instance Binary IfaceTickish where @@ -3047,31 +3056,31 @@ instance NFData IfaceDecl where rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 IfaceData f1 f2 f3 f4 f5 f6 f7 f8 f9 -> - f1 `seq` seqList f2 `seq` f3 `seq` f4 `seq` f5 `seq` + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` rnf f9 IfaceSynonym f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 IfaceFamily f1 f2 f3 f4 f5 f6 -> - rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 `seq` f6 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` () IfaceClass f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 IfaceAxiom nm tycon role ax -> rnf nm `seq` rnf tycon `seq` - role `seq` + rnf role `seq` rnf ax IfacePatSyn f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 -> - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` f6 `seq` - rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` f11 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 `seq` () instance NFData IfaceAxBranch where rnf (IfaceAxBranch f1 f2 f3 f4 f5 f6 f7) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` rnf f7 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 instance NFData IfaceClassBody where rnf = \case @@ -3089,7 +3098,7 @@ instance NFData IfaceAT where rnf (IfaceAT f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceClassOp where - rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` f3 `seq` () + rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` () instance NFData IfaceTyConParent where rnf = \case @@ -3104,19 +3113,22 @@ instance NFData IfaceConDecls where instance NFData IfaceConDecl where rnf (IfCon f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` - rnf f7 `seq` rnf f8 `seq` f9 `seq` rnf f10 `seq` rnf f11 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 instance NFData IfaceSrcBang where - rnf (IfSrcBang f1 f2) = f1 `seq` f2 `seq` () + rnf (IfSrcBang f1 f2) = rnf f1 `seq` rnf f2 `seq` () instance NFData IfaceBang where - rnf x = x `seq` () + rnf IfNoBang = () + rnf IfStrict = () + rnf IfUnpack = () + rnf (IfUnpackCo co) = rnf co instance NFData IfaceIdDetails where rnf = \case IfVanillaId -> () - IfWorkerLikeId dmds -> dmds `seqList` () + IfWorkerLikeId dmds -> rnf dmds `seq` () IfRecSelId (Left tycon) b c d -> rnf tycon `seq` rnf b `seq` rnf c `seq` rnf d IfRecSelId (Right decl) b c d -> rnf decl `seq` rnf b `seq` rnf c `seq` rnf d IfDFunId -> () @@ -3125,23 +3137,22 @@ instance NFData IfaceInfoItem where rnf = \case HsArity a -> rnf a HsDmdSig str -> seqDmdSig str - HsInline p -> p `seq` () -- TODO: seq further? + HsInline p -> rnf p `seq` () HsUnfold b unf -> rnf b `seq` rnf unf HsNoCafRefs -> () - HsCprSig cpr -> cpr `seq` () - HsLFInfo lf_info -> lf_info `seq` () -- TODO: seq further? - HsTagSig sig -> sig `seq` () + HsCprSig cpr -> seqCprSig cpr `seq` () + HsLFInfo lf_info -> rnf lf_info `seq` () + HsTagSig sig -> seqTagSig sig `seq` () instance NFData IfGuidance where rnf = \case IfNoGuidance -> () - IfWhen a b c -> a `seq` b `seq` c `seq` () + IfWhen a b c -> rnf a `seq` rnf b `seq` rnf c `seq` () instance NFData IfaceUnfolding where rnf = \case - IfCoreUnfold src cache guidance expr -> src `seq` cache `seq` rnf guidance `seq` rnf expr + IfCoreUnfold src cache guidance expr -> rnf src `seq` seqUnfoldingCache cache `seq` rnf guidance `seq` rnf expr IfDFunUnfold bndrs exprs -> rnf bndrs `seq` rnf exprs - -- See Note [UnfoldingCache] in GHC.Core for why it suffices to merely `seq` on cache instance NFData IfaceExpr where rnf = \case @@ -3149,16 +3160,16 @@ instance NFData IfaceExpr where IfaceExt nm -> rnf nm IfaceType ty -> rnf ty IfaceCo co -> rnf co - IfaceTuple sort exprs -> sort `seq` rnf exprs + IfaceTuple sort exprs -> rnf sort `seq` rnf exprs IfaceLam bndr expr -> rnf bndr `seq` rnf expr IfaceApp e1 e2 -> rnf e1 `seq` rnf e2 - IfaceCase e nm alts -> rnf e `seq` nm `seq` rnf alts + IfaceCase e nm alts -> rnf e `seq` rnf nm `seq` rnf alts IfaceECase e ty -> rnf e `seq` rnf ty IfaceLet bind e -> rnf bind `seq` rnf e IfaceCast e co -> rnf e `seq` rnf co - IfaceLit l -> l `seq` () -- FIXME - IfaceLitRubbish tc r -> tc `seq` rnf r `seq` () - IfaceFCall fc ty -> fc `seq` rnf ty + IfaceLit l -> rnf l `seq` () + IfaceLitRubbish tc r -> rnf tc `seq` rnf r `seq` () + IfaceFCall fc ty -> rnf fc `seq` rnf ty IfaceTick tick e -> rnf tick `seq` rnf e instance NFData IfaceAlt where @@ -3170,7 +3181,7 @@ instance (NFData b, NFData a) => NFData (IfaceBindingX a b) where IfaceRec binds -> rnf binds instance NFData IfaceTopBndrInfo where - rnf (IfGblTopBndr n) = n `seq` () + rnf (IfGblTopBndr n) = rnf n `seq` () rnf (IfLclTopBndr fs ty info dets) = rnf fs `seq` rnf ty `seq` rnf info `seq` rnf dets `seq` () instance NFData IfaceMaybeRhs where @@ -3192,22 +3203,22 @@ instance NFData IfaceFamTyConFlav where instance NFData IfaceTickish where rnf = \case IfaceHpcTick m i -> rnf m `seq` rnf i - IfaceSCC cc b1 b2 -> cc `seq` rnf b1 `seq` rnf b2 - IfaceSource src str -> src `seq` rnf str + IfaceSCC cc b1 b2 -> rnf cc `seq` rnf b1 `seq` rnf b2 + IfaceSource src str -> rnf src `seq` rnf str IfaceBreakpoint m i fvs -> rnf m `seq` rnf i `seq` rnf fvs instance NFData IfaceConAlt where rnf = \case IfaceDefaultAlt -> () IfaceDataAlt nm -> rnf nm - IfaceLitAlt lit -> lit `seq` () + IfaceLitAlt lit -> rnf lit `seq` () instance NFData IfaceCompleteMatch where rnf (IfaceCompleteMatch f1 mtc) = rnf f1 `seq` rnf mtc instance NFData IfaceRule where rnf (IfaceRule f1 f2 f3 f4 f5 f6 f7 f8) = - rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` f8 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` () instance NFData IfaceDefault where rnf (IfaceDefault f1 f2 f3) = @@ -3215,11 +3226,11 @@ instance NFData IfaceDefault where instance NFData IfaceFamInst where rnf (IfaceFamInst f1 f2 f3 f4) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` () instance NFData IfaceClsInst where rnf (IfaceClsInst f1 f2 f3 f4 f5 f6) = - f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` f5 `seq` rnf f6 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 instance NFData IfaceWarnings where rnf = \case @@ -3227,12 +3238,12 @@ instance NFData IfaceWarnings where IfWarnSome vs ds -> rnf vs `seq` rnf ds instance NFData IfaceWarningTxt where - rnf = \case - IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 - IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 + rnf = \case + IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 + IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 instance NFData IfaceStringLiteral where - rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 + rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceAnnotation where - rnf (IfaceAnnotation f1 f2) = f1 `seq` f2 `seq` () + rnf (IfaceAnnotation f1 f2) = rnf f1 `seq` rnf f2 `seq` () ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -2577,18 +2577,23 @@ instance Binary (DefMethSpec IfaceType) where 0 -> return VanillaDM _ -> do { t <- get bh; return (GenericDM t) } +instance NFData (DefMethSpec IfaceType) where + rnf = \case + VanillaDM -> () + GenericDM t -> rnf t + instance NFData IfaceType where rnf = \case IfaceFreeTyVar f1 -> f1 `seq` () IfaceTyVar f1 -> rnf f1 IfaceLitTy f1 -> rnf f1 IfaceAppTy f1 f2 -> rnf f1 `seq` rnf f2 - IfaceFunTy f1 f2 f3 f4 -> f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 - IfaceForAllTy f1 f2 -> f1 `seq` rnf f2 + IfaceFunTy f1 f2 f3 f4 -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 + IfaceForAllTy f1 f2 -> rnf f1 `seq` rnf f2 IfaceTyConApp f1 f2 -> rnf f1 `seq` rnf f2 IfaceCastTy f1 f2 -> rnf f1 `seq` rnf f2 IfaceCoercionTy f1 -> rnf f1 - IfaceTupleTy f1 f2 f3 -> f1 `seq` f2 `seq` rnf f3 + IfaceTupleTy f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 instance NFData IfaceTyLit where rnf = \case @@ -2599,21 +2604,25 @@ instance NFData IfaceTyLit where instance NFData IfaceCoercion where rnf = \case IfaceReflCo f1 -> rnf f1 - IfaceGReflCo f1 f2 f3 -> f1 `seq` rnf f2 `seq` rnf f3 - IfaceFunCo f1 f2 f3 f4 -> f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 - IfaceTyConAppCo f1 f2 f3 -> f1 `seq` rnf f2 `seq` rnf f3 + IfaceGReflCo f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 + IfaceFunCo f1 f2 f3 f4 -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 + IfaceTyConAppCo f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 IfaceAppCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceForAllCo f1 f2 f3 f4 f5 -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 IfaceCoVarCo f1 -> rnf f1 IfaceAxiomCo f1 f2 -> rnf f1 `seq` rnf f2 - IfaceUnivCo f1 f2 f3 f4 deps -> rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf deps + IfaceUnivCo f1 f2 f3 f4 deps -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf deps IfaceSymCo f1 -> rnf f1 IfaceTransCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceSelCo f1 f2 -> rnf f1 `seq` rnf f2 - IfaceLRCo f1 f2 -> f1 `seq` rnf f2 + IfaceLRCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceInstCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceKindCo f1 -> rnf f1 IfaceSubCo f1 -> rnf f1 + -- These are not deeply forced because they are not used in ModIface, + -- these constructors are for pretty-printing. + -- See Note [Free TyVars and CoVars in IfaceType] + -- See Note [Holes in IfaceCoercion] IfaceFreeCoVar f1 -> f1 `seq` () IfaceHoleCo f1 -> f1 `seq` () @@ -2624,15 +2633,17 @@ instance NFData IfaceAxiomRule where IfaceAR_B n i -> rnf n `seq` rnf i instance NFData IfaceMCoercion where - rnf x = seq x () + rnf IfaceMRefl = () + rnf (IfaceMCo c) = rnf c instance NFData IfaceOneShot where - rnf x = seq x () + rnf IfaceOneShot = () + rnf IfaceNoOneShot = () instance NFData IfaceTyConSort where rnf = \case IfaceNormalTyCon -> () - IfaceTupleTyCon arity sort -> rnf arity `seq` sort `seq` () + IfaceTupleTyCon arity sort -> rnf arity `seq` rnf sort `seq` () IfaceSumTyCon arity -> rnf arity IfaceEqualityTyCon -> () @@ -2640,7 +2651,7 @@ instance NFData IfLclName where rnf (IfLclName lfs) = rnf lfs instance NFData IfaceTyConInfo where - rnf (IfaceTyConInfo f s) = f `seq` rnf s + rnf (IfaceTyConInfo f s) = rnf f `seq` rnf s instance NFData IfaceTyCon where rnf (IfaceTyCon nm info) = rnf nm `seq` rnf info @@ -2653,4 +2664,4 @@ instance NFData IfaceBndr where instance NFData IfaceAppArgs where rnf = \case IA_Nil -> () - IA_Arg f1 f2 f3 -> rnf f1 `seq` f2 `seq` rnf f3 + IA_Arg f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -148,6 +148,7 @@ import qualified GHC.Boot.TH.Ppr as TH #if defined(HAVE_INTERNAL_INTERPRETER) import Unsafe.Coerce ( unsafeCoerce ) import GHC.Desugar ( AnnotationWrapper(..) ) +import Control.DeepSeq #endif import Control.Monad @@ -1039,11 +1040,7 @@ convertAnnotationWrapper fhv = do -- annotation are exposed at this point. This is also why we are -- doing all this stuff inside the context of runMeta: it has the -- facilities to deal with user error in a meta-level expression - seqSerialized serialized `seq` serialized - --- | Force the contents of the Serialized value so weknow it doesn't contain any bottoms -seqSerialized :: Serialized -> () -seqSerialized (Serialized the_type bytes) = the_type `seq` bytes `seqList` () + rnf serialized `seq` serialized #endif ===================================== compiler/GHC/Types/Annotations.hs ===================================== @@ -31,7 +31,7 @@ import Control.Monad import Data.Maybe import Data.Typeable import Data.Word ( Word8 ) - +import Control.DeepSeq -- | Represents an annotation after it has been sufficiently desugared from -- it's initial form of 'GHC.Hs.Decls.AnnDecl' @@ -71,6 +71,10 @@ instance Binary name => Binary (AnnTarget name) where 0 -> liftM NamedTarget $ get bh _ -> liftM ModuleTarget $ get bh +instance NFData name => NFData (AnnTarget name) where + rnf (NamedTarget n) = rnf n + rnf (ModuleTarget m) = rnf m + instance Outputable Annotation where ppr ann = ppr (ann_target ann) ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -167,6 +167,11 @@ instance Binary LeftOrRight where 0 -> return CLeft _ -> return CRight } +instance NFData LeftOrRight where + rnf CLeft = () + rnf CRight = () + + {- ************************************************************************ @@ -529,6 +534,10 @@ instance Binary FunctionOrData where 1 -> return IsData _ -> panic "Binary FunctionOrData" +instance NFData FunctionOrData where + rnf IsFunction = () + rnf IsData = () + {- ************************************************************************ * * @@ -612,6 +621,11 @@ instance Binary CbvMark where 1 -> return MarkedCbv _ -> panic "Invalid binary format" +instance NFData CbvMark where + rnf MarkedCbv = () + rnf NotMarkedCbv = () + + isMarkedCbv :: CbvMark -> Bool isMarkedCbv MarkedCbv = True isMarkedCbv NotMarkedCbv = False @@ -871,6 +885,9 @@ data OverlapMode -- See Note [Rules for instance lookup] in GHC.Core.InstEnv instance Outputable OverlapFlag where ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag) +instance NFData OverlapFlag where + rnf (OverlapFlag mode safe) = rnf mode `seq` rnf safe + instance Outputable OverlapMode where ppr (NoOverlap _) = empty ppr (Overlappable _) = text "[overlappable]" @@ -879,6 +896,14 @@ instance Outputable OverlapMode where ppr (Incoherent _) = text "[incoherent]" ppr (NonCanonical _) = text "[noncanonical]" +instance NFData OverlapMode where + rnf (NoOverlap s) = rnf s + rnf (Overlappable s) = rnf s + rnf (Overlapping s) = rnf s + rnf (Overlaps s) = rnf s + rnf (Incoherent s) = rnf s + rnf (NonCanonical s) = rnf s + instance Binary OverlapMode where put_ bh (NoOverlap s) = putByte bh 0 >> put_ bh s put_ bh (Overlaps s) = putByte bh 1 >> put_ bh s @@ -1032,6 +1057,11 @@ instance Binary TupleSort where 1 -> return UnboxedTuple _ -> return ConstraintTuple +instance NFData TupleSort where + rnf BoxedTuple = () + rnf UnboxedTuple = () + rnf ConstraintTuple = () + tupleSortBoxity :: TupleSort -> Boxity tupleSortBoxity BoxedTuple = Boxed @@ -1860,6 +1890,14 @@ instance Binary Activation where ab <- get bh return (ActiveAfter src ab) +instance NFData Activation where + rnf = \case + AlwaysActive -> () + NeverActive -> () + ActiveBefore src aa -> rnf src `seq` rnf aa + ActiveAfter src ab -> rnf src `seq` rnf ab + FinalActive -> () + instance Outputable RuleMatchInfo where ppr ConLike = text "CONLIKE" ppr FunLike = text "FUNLIKE" @@ -1872,6 +1910,11 @@ instance Binary RuleMatchInfo where if h == 1 then return ConLike else return FunLike +instance NFData RuleMatchInfo where + rnf = \case + ConLike -> () + FunLike -> () + instance Outputable InlineSpec where ppr (Inline src) = text "INLINE" <+> pprWithSourceText src empty ppr (NoInline src) = text "NOINLINE" <+> pprWithSourceText src empty @@ -1906,6 +1949,14 @@ instance Binary InlineSpec where s <- get bh return (Opaque s) +instance NFData InlineSpec where + rnf = \case + Inline s -> rnf s + NoInline s -> rnf s + Inlinable s -> rnf s + Opaque s -> rnf s + NoUserInlinePrag -> () + instance Outputable InlinePragma where ppr = pprInline @@ -1925,6 +1976,9 @@ instance Binary InlinePragma where d <- get bh return (InlinePragma s a b c d) +instance NFData InlinePragma where + rnf (InlinePragma s a b c d) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c `seq` rnf d + -- | Outputs string for pragma name for any of INLINE/INLINABLE/NOINLINE. This -- differs from the Outputable instance for the InlineSpec type where the pragma -- name string as well as the accompanying SourceText (if any) is printed. @@ -2017,6 +2071,13 @@ instance Binary UnfoldingSource where 2 -> return StableSystemSrc _ -> return VanillaSrc +instance NFData UnfoldingSource where + rnf = \case + CompulsorySrc -> () + StableUserSrc -> () + StableSystemSrc -> () + VanillaSrc -> () + instance Outputable UnfoldingSource where ppr CompulsorySrc = text "Compulsory" ppr StableUserSrc = text "StableUser" @@ -2161,6 +2222,19 @@ data TypeOrConstraint = TypeLike | ConstraintLike deriving( Eq, Ord, Data ) +instance Binary TypeOrConstraint where + put_ bh = \case + TypeLike -> putByte bh 0 + ConstraintLike -> putByte bh 1 + get bh = getByte bh >>= \case + 0 -> pure TypeLike + 1 -> pure ConstraintLike + _ -> panic "TypeOrConstraint.get: invalid value" + +instance NFData TypeOrConstraint where + rnf = \case + TypeLike -> () + ConstraintLike -> () {- ********************************************************************* * * @@ -2209,18 +2283,6 @@ instance Outputable (TyConFlavour tc) where go BuiltInTypeFlavour = "built-in type" go PromotedDataConFlavour = "promoted data constructor" -instance NFData tc => NFData (TyConFlavour tc) where - rnf ClassFlavour = () - rnf (TupleFlavour !_) = () - rnf SumFlavour = () - rnf DataTypeFlavour = () - rnf NewtypeFlavour = () - rnf AbstractTypeFlavour = () - rnf (OpenFamilyFlavour !_ mb_tc) = rnf mb_tc - rnf ClosedTypeFamilyFlavour = () - rnf TypeSynonymFlavour = () - rnf BuiltInTypeFlavour = () - rnf PromotedDataConFlavour = () -- | Get the enclosing class TyCon (if there is one) for the given TyConFlavour tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc ===================================== compiler/GHC/Types/CostCentre.hs ===================================== @@ -36,6 +36,7 @@ import GHC.Utils.Outputable import GHC.Types.SrcLoc import GHC.Data.FastString import GHC.Types.CostCentre.State +import Control.DeepSeq import Data.Data @@ -395,6 +396,21 @@ instance Binary CostCentre where -- CostCentre in the original module, it is not used by importing -- modules. +instance NFData CostCentre where + rnf (NormalCC aa ab ac ad) = rnf aa `seq` rnf ab `seq` rnf ac `seq` rnf ad + rnf (AllCafsCC ae ad) = rnf ae `seq` rnf ad + +instance NFData CCFlavour where + rnf CafCC = () + rnf (IndexedCC flav i) = rnf flav `seq` rnf i + +instance NFData IndexedCCFlavour where + rnf ExprCC = () + rnf DeclCC = () + rnf HpcCC = () + rnf LateCC = () + rnf CallerCC = () + getAllCAFsCC :: Module -> (CostCentre, CostCentreStack) getAllCAFsCC this_mod = let ===================================== compiler/GHC/Types/CostCentre/State.hs ===================================== @@ -15,6 +15,7 @@ import GHC.Data.FastString.Env import Data.Data import GHC.Utils.Binary +import Control.DeepSeq -- | Per-module state for tracking cost centre indices. -- @@ -29,6 +30,9 @@ newCostCentreState = CostCentreState emptyFsEnv newtype CostCentreIndex = CostCentreIndex { unCostCentreIndex :: Int } deriving (Eq, Ord, Data, Binary) +instance NFData CostCentreIndex where + rnf (CostCentreIndex i) = rnf i + -- | Get a new index for a given cost centre name. getCCIndex :: FastString -> CostCentreState ===================================== compiler/GHC/Types/ForeignCall.hs ===================================== @@ -30,6 +30,8 @@ import GHC.Types.SourceText ( SourceText, pprWithSourceText ) import Data.Char import Data.Data +import Control.DeepSeq (NFData(..)) + {- ************************************************************************ * * @@ -344,3 +346,31 @@ instance Binary Header where get bh = do s <- get bh h <- get bh return (Header s h) + +instance NFData ForeignCall where + rnf (CCall c) = rnf c + +instance NFData Safety where + rnf PlaySafe = () + rnf PlayInterruptible = () + rnf PlayRisky = () + +instance NFData CCallSpec where + rnf (CCallSpec t c s) = rnf t `seq` rnf c `seq` rnf s + +instance NFData CCallTarget where + rnf (StaticTarget s a b c) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c + rnf DynamicTarget = () + +instance NFData CCallConv where + rnf CCallConv = () + rnf StdCallConv = () + rnf PrimCallConv = () + rnf CApiConv = () + rnf JavaScriptCallConv = () + +instance NFData CType where + rnf (CType s mh fs) = rnf s `seq` rnf mh `seq` rnf fs + +instance NFData Header where + rnf (Header s h) = rnf s `seq` rnf h ===================================== compiler/GHC/Types/GREInfo.hs ===================================== @@ -126,12 +126,6 @@ data GREInfo deriving Data -instance NFData GREInfo where - rnf Vanilla = () - rnf UnboundGRE = () - rnf (IAmTyCon tc) = rnf tc - rnf (IAmConLike info) = rnf info - rnf (IAmRecField info) = rnf info plusGREInfo :: GREInfo -> GREInfo -> GREInfo plusGREInfo Vanilla Vanilla = Vanilla ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -84,6 +84,7 @@ import Data.Char import Data.Data ( Data ) import GHC.Exts( isTrue#, dataToTag#, (<#) ) import Numeric ( fromRat ) +import Control.DeepSeq {- ************************************************************************ @@ -204,6 +205,20 @@ instance Binary LitNumType where h <- getByte bh return (toEnum (fromIntegral h)) +instance NFData LitNumType where + rnf (LitNumBigNat) = () + rnf (LitNumInt) = () + rnf (LitNumInt8) = () + rnf (LitNumInt16) = () + rnf (LitNumInt32) = () + rnf (LitNumInt64) = () + rnf (LitNumWord) = () + rnf (LitNumWord8) = () + rnf (LitNumWord16) = () + rnf (LitNumWord32) = () + rnf (LitNumWord64) = () + + {- Note [BigNum literals] ~~~~~~~~~~~~~~~~~~~~~~ @@ -288,6 +303,16 @@ instance Binary Literal where return (LitNumber nt i) _ -> pprPanic "Binary:Literal" (int (fromIntegral h)) +instance NFData Literal where + rnf (LitChar c) = rnf c + rnf (LitNumber nt i) = rnf nt `seq` rnf i + rnf (LitString s) = rnf s + rnf LitNullAddr = () + rnf (LitFloat r) = rnf r + rnf (LitDouble r) = rnf r + rnf (LitLabel l1 k2) = rnf l1 `seq` rnf k2 + rnf (LitRubbish {}) = () -- LitRubbish is not contained within interface files. + -- See Note [Rubbish literals]. instance Outputable Literal where ppr = pprLiteral id ===================================== compiler/GHC/Types/SourceFile.hs ===================================== @@ -13,6 +13,7 @@ where import GHC.Prelude import GHC.Utils.Binary import GHC.Unit.Types +import Control.DeepSeq {- Note [HscSource types] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -53,6 +54,10 @@ data HsBootOrSig | Hsig -- ^ .hsig file deriving (Eq, Ord, Show) +instance NFData HsBootOrSig where + rnf HsBoot = () + rnf Hsig = () + data HscSource -- | .hs file = HsSrcFile @@ -73,6 +78,10 @@ hscSourceToIsBoot :: HscSource -> IsBootInterface hscSourceToIsBoot HsBootFile = IsBoot hscSourceToIsBoot _ = NotBoot +instance NFData HscSource where + rnf HsSrcFile = () + rnf (HsBootOrSig h) = rnf h + instance Binary HscSource where put_ bh HsSrcFile = putByte bh 0 put_ bh HsBootFile = putByte bh 1 ===================================== compiler/GHC/Types/SrcLoc.hs ===================================== @@ -223,7 +223,8 @@ data RealSrcLoc -- We use 'BufPos' in in GHC.Parser.PostProcess.Haddock to associate Haddock -- comments with parts of the AST using location information (#17544). newtype BufPos = BufPos { bufPos :: Int } - deriving (Eq, Ord, Show, Data) + deriving (Eq, Ord, Show, Data, NFData) + -- | Source Location data SrcLoc @@ -373,11 +374,13 @@ data RealSrcSpan } deriving Eq --- | StringBuffer Source Span data BufSpan = BufSpan { bufSpanStart, bufSpanEnd :: {-# UNPACK #-} !BufPos } deriving (Eq, Ord, Show, Data) +instance NFData BufSpan where + rnf (BufSpan a1 a2) = rnf a1 `seq` rnf a2 + instance Semigroup BufSpan where BufSpan start1 end1 <> BufSpan start2 end2 = BufSpan (min start1 start2) (max end1 end2) @@ -439,8 +442,19 @@ instance ToJson RealSrcSpan where end = JSObject [ ("line", JSInt srcSpanELine), ("column", JSInt srcSpanECol) ] +instance NFData RealSrcSpan where + rnf (RealSrcSpan' file line col endLine endCol) = rnf file `seq` rnf line `seq` rnf col `seq` rnf endLine `seq` rnf endCol + instance NFData SrcSpan where - rnf x = x `seq` () + rnf (RealSrcSpan a1 a2) = rnf a1 `seq` rnf a2 + rnf (UnhelpfulSpan a1) = rnf a1 + +instance NFData UnhelpfulSpanReason where + rnf (UnhelpfulNoLocationInfo) = () + rnf (UnhelpfulWiredIn) = () + rnf (UnhelpfulInteractive) = () + rnf (UnhelpfulGenerated) = () + rnf (UnhelpfulOther a1) = rnf a1 getBufSpan :: SrcSpan -> Strict.Maybe BufSpan getBufSpan (RealSrcSpan _ mbspan) = mbspan ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -132,6 +132,7 @@ import GHC.Utils.Panic import GHC.Hs.Specificity () import Language.Haskell.Syntax.Specificity +import Control.DeepSeq import Data.Data @@ -499,6 +500,12 @@ instance Binary FunTyFlag where 2 -> return FTF_C_T _ -> return FTF_C_C +instance NFData FunTyFlag where + rnf FTF_T_T = () + rnf FTF_T_C = () + rnf FTF_C_T = () + rnf FTF_C_C = () + mkFunTyFlag :: TypeOrConstraint -> TypeOrConstraint -> FunTyFlag mkFunTyFlag TypeLike torc = visArg torc mkFunTyFlag ConstraintLike torc = invisArg torc @@ -734,6 +741,9 @@ instance (Binary tv, Binary vis) => Binary (VarBndr tv vis) where get bh = do { tv <- get bh; vis <- get bh; return (Bndr tv vis) } +instance (NFData tv, NFData vis) => NFData (VarBndr tv vis) where + rnf (Bndr tv vis) = rnf tv `seq` rnf vis + instance NamedThing tv => NamedThing (VarBndr tv flag) where getName (Bndr tv _) = getName tv ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -39,6 +39,7 @@ import Data.List (sortBy, sort, partition) import Data.Set (Set) import qualified Data.Set as Set import Data.Bifunctor +import Control.DeepSeq -- | Dependency information about ALL modules and packages below this one -- in the import hierarchy. This is the serialisable version of `ImportAvails`. @@ -104,6 +105,18 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +instance NFData Dependencies where + rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) + = rnf dmods + `seq` rnf dpkgs + `seq` rnf ppkgs + `seq` rnf hsigms + `seq` rnf tps + `seq` rnf bmods + `seq` rnf orphs + `seq` rnf finsts + `seq` () + -- | Extract information from the rename and typecheck phases to produce -- a dependencies information for the module being compiled. @@ -326,6 +339,13 @@ data Usage -- And of course, for modules that aren't imported directly we don't -- depend on their export lists +instance NFData Usage where + rnf (UsagePackageModule mod hash safe) = rnf mod `seq` rnf hash `seq` rnf safe `seq` () + rnf (UsageHomeModule mod uid hash entities exports safe) = rnf mod `seq` rnf uid `seq` rnf hash `seq` rnf entities `seq` rnf exports `seq` rnf safe `seq` () + rnf (UsageFile file hash label) = rnf file `seq` rnf hash `seq` rnf label `seq` () + rnf (UsageMergedRequirement mod hash) = rnf mod `seq` rnf hash `seq` () + rnf (UsageHomeModuleInterface mod uid hash) = rnf mod `seq` rnf uid `seq` rnf hash `seq` () + instance Binary Usage where put_ bh usg at UsagePackageModule{} = do putByte bh 0 ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -655,57 +655,50 @@ mkIfaceHashCache pairs emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint) emptyIfaceHashCache _occ = Nothing --- Take care, this instance only forces to the degree necessary to --- avoid major space leaks. +-- ModIface is completely forced since it will live in memory for a long time. +-- If forcing it uses a lot of memory, then store less things in ModIface. instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ - , mi_exports_, mi_fixities_, mi_warns_, mi_anns_ - , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ - , mi_fam_insts_, mi_rules_, mi_trust_, mi_trust_pkg_ - , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_ }) - = rnf mi_module_ - `seq` rnf mi_sig_of_ - `seq` mi_hsc_src_ - `seq` mi_hi_bytes_ - `seq` mi_deps_ - `seq` mi_exports_ - `seq` mi_fixities_ - `seq` rnf mi_warns_ - `seq` rnf mi_anns_ - `seq` rnf mi_decls_ - `seq` rnf mi_defaults_ - `seq` rnf mi_extra_decls_ - `seq` rnf mi_foreign_ - `seq` rnf mi_top_env_ - `seq` rnf mi_insts_ - `seq` rnf mi_fam_insts_ - `seq` rnf mi_rules_ - `seq` mi_trust_ - `seq` rnf mi_trust_pkg_ - `seq` rnf mi_complete_matches_ - `seq` rnf mi_docs_ - `seq` mi_final_exts_ - `seq` mi_ext_fields_ - `seq` () - -instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_mod_hash - , mi_orphan, mi_finsts, mi_exp_hash - , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn - , mi_hash_fn}) - = rnf mi_mod_hash - `seq` rnf mi_orphan - `seq` rnf mi_finsts - `seq` rnf mi_exp_hash - `seq` rnf mi_orphan_hash - `seq` rnf mi_decl_warn_fn - `seq` rnf mi_export_warn_fn - `seq` rnf mi_fix_fn - `seq` rnf mi_hash_fn + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + `seq` rnf a15 + `seq` rnf a16 + `seq` rnf a17 + `seq` rnf a18 + `seq` rnf a19 + `seq` rnf a20 + `seq` rnf a21 + `seq` rnf a22 + -- IfaceBinHandle + `seq` (a23 :: IfaceBinHandle phase) + `seq` rnf a24 + +instance NFData ModIfaceBackend where + rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 forceModIface :: ModIface -> IO () ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -517,6 +517,9 @@ newtype UnitId = UnitId } deriving (Data) +instance NFData UnitId where + rnf (UnitId fs) = rnf fs `seq` () + instance Binary UnitId where put_ bh (UnitId fs) = put_ bh fs get bh = do fs <- get bh; return (UnitId fs) @@ -704,6 +707,9 @@ data GenWithIsBoot mod = GWIB -- IsBootInterface: this is assumed to perform filtering of non-boot modules, -- e.g. in GHC.Driver.Env.hptModulesBelow +instance NFData mod => NFData (GenWithIsBoot mod) where + rnf (GWIB mod isBoot) = rnf mod `seq` rnf isBoot `seq` () + type ModuleNameWithIsBoot = GenWithIsBoot ModuleName type ModuleWithIsBoot = GenWithIsBoot Module ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,11 +2,11 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where -import Data.Data +import Data.Data (Data) import Data.Eq import Data.Ord import Data.Bool -import Data.Int (Int) +import Prelude import GHC.Data.FastString (FastString) import Control.DeepSeq @@ -134,5 +134,13 @@ data FixityDirection | InfixN deriving (Eq, Data) +instance NFData FixityDirection where + rnf InfixL = () + rnf InfixR = () + rnf InfixN = () + data Fixity = Fixity Int FixityDirection deriving (Eq, Data) + +instance NFData Fixity where + rnf (Fixity i d) = rnf i `seq` rnf d `seq` () ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -80,6 +80,7 @@ import Data.Bool import Data.Char import Prelude (Integer) import Data.Ord (Ord) +import Control.DeepSeq {- ************************************************************************ @@ -99,6 +100,10 @@ isPromoted :: PromotionFlag -> Bool isPromoted IsPromoted = True isPromoted NotPromoted = False +instance NFData PromotionFlag where + rnf NotPromoted = () + rnf IsPromoted = () + {- ************************************************************************ * * ===================================== compiler/Language/Haskell/Syntax/Type.hs-boot ===================================== @@ -4,6 +4,8 @@ import Data.Bool import Data.Eq import Data.Ord +import Control.DeepSeq + {- ************************************************************************ * * @@ -19,5 +21,6 @@ data PromotionFlag instance Eq PromotionFlag instance Ord PromotionFlag +instance NFData PromotionFlag isPromoted :: PromotionFlag -> Bool ===================================== libraries/ghc-boot/GHC/Serialized.hs ===================================== @@ -22,11 +22,15 @@ import Prelude -- See note [Why do we import Prelude here?] import Data.Bits import Data.Word ( Word8 ) import Data.Data +import Control.DeepSeq -- | Represents a serialized value of a particular type. Attempts can be made to deserialize it at certain types data Serialized = Serialized TypeRep [Word8] +instance NFData Serialized where + rnf (Serialized tr ws) = rnf tr `seq` rnf ws + -- | Put a Typeable value that we are able to actually turn into bytes into a 'Serialized' value ready for deserialization later toSerialized :: forall a. Typeable a => (a -> [Word8]) -> a -> Serialized toSerialized serialize what = Serialized (typeOf what) (serialize what) ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -52,7 +52,6 @@ import Data.Map (Map) import qualified Data.Map as Map import qualified Data.Set as Set import GHC -import qualified GHC.Data.Strict as Strict import GHC.Data.BooleanFormula (BooleanFormula) import GHC.Driver.Session (Language) import qualified GHC.LanguageExtensions as LangExt @@ -61,7 +60,7 @@ import GHC.Types.Fixity (Fixity (..)) import GHC.Types.Name (stableNameCmp) import GHC.Types.Name.Occurrence import GHC.Types.Name.Reader (RdrName (..)) -import GHC.Types.SrcLoc (BufPos (..), BufSpan (..), srcSpanToRealSrcSpan) +import GHC.Types.SrcLoc (srcSpanToRealSrcSpan) import GHC.Types.Var (Specificity) import GHC.Utils.Outputable @@ -987,15 +986,6 @@ instance NFData RdrName where rnf (Orig m on) = m `deepseq` on `deepseq` () rnf (Exact n) = rnf n -instance NFData FixityDirection where - rnf InfixL = () - rnf InfixR = () - rnf InfixN = () - -instance NFData Fixity where - rnf (Fixity n dir) = - n `deepseq` dir `deepseq` () - instance NFData (EpAnn NameAnn) where rnf (EpAnn en ann cs) = en `deepseq` ann `deepseq` cs `deepseq` () @@ -1065,15 +1055,6 @@ instance NFData EpaCommentTok where rnf (EpaLineComment s) = rnf s rnf (EpaBlockComment s) = rnf s -instance NFData a => NFData (Strict.Maybe a) where - rnf Strict.Nothing = () - rnf (Strict.Just x) = rnf x - -instance NFData BufSpan where - rnf (BufSpan p1 p2) = p1 `deepseq` p2 `deepseq` () - -instance NFData BufPos where - rnf (BufPos n) = rnf n instance NFData DeltaPos where rnf (SameLine n) = rnf n View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1560f71efad1a37af28c7d739c35403d5b5085b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1560f71efad1a37af28c7d739c35403d5b5085b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/1af075d8/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 15:58:22 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 10 Mar 2025 11:58:22 -0400 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] fixing record update error messages Message-ID: <67cf0c1ecf454_25aa2f833d44204e4@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 7789c823 by Apoorv Ingle at 2025-03-10T10:57:58-05:00 fixing record update error messages - - - - - 1 changed file: - compiler/GHC/Tc/Gen/Expr.hs Changes: ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -651,7 +651,7 @@ tcExpr expr@(RecordUpd { rupd_expr = record_expr -- Typecheck the expanded expression. ; expr' <- addErrCtxt err_ctxt $ - tcExpr (mkExpandedExpr expr ds_expr) (Check ds_res_ty) + tcExpr ds_expr (Check ds_res_ty) -- NB: it's important to use ds_res_ty and not res_ty here. -- Test case: T18802b. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7789c82366fd37d16a3d3c2f1d262c7f7cf4caf5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7789c82366fd37d16a3d3c2f1d262c7f7cf4caf5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/c0f5d99e/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 10 16:08:26 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 10 Mar 2025 12:08:26 -0400 Subject: [Git][ghc/ghc][wip/backports-9.10] mk-ghcup-metadata: Fix misnamed identifiers Message-ID: <67cf0e7a99ef3_272ba116b6608867c@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: ade5ae4f by Ben Gamari at 2025-03-10T12:08:07-04:00 mk-ghcup-metadata: Fix misnamed identifiers - - - - - 1 changed file: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py Changes: ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -183,7 +183,7 @@ def mk_from_platform(release_mode, pipeline_type, platform): , f"ghc{{version}}-{platform.name}") # Generate the new metadata for a specific GHC mode etc -def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): +def mk_new_yaml(release_mode, version, date, pipeline_type, job_map) -> object: def mk(platform): eprint("\n=== " + platform.name + " " + ('=' * (75 - len(platform.name)))) return mk_one_metadata(release_mode, version, job_map, mk_from_platform(release_mode, pipeline_type, platform)) @@ -231,8 +231,8 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): , "Linux_UnknownLinux" : { "unknown_versioning": rocky8 } , "Darwin" : { "unknown_versioning" : darwin_x86 } , "Windows" : { "unknown_versioning" : windows } - , "Linux_Alpine" : { "( >= 3.12 && < 3.18 )": alpine_3_12 - , ">= 3.18": alpine_3_18 + , "Linux_Alpine" : { "( >= 3.12 && < 3.18 )": alpine3_12 + , ">= 3.18": alpine3_18 , "unknown_versioning": alpine3_12 } } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ade5ae4f12f81eb0841e6a1627eb03cc762b803b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ade5ae4f12f81eb0841e6a1627eb03cc762b803b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/9ea519f1/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 16:23:02 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Mon, 10 Mar 2025 12:23:02 -0400 Subject: [Git][ghc/ghc][wip/int-index/conpat-one-list] 40 commits: compiler: Add export list to GHC.SysTools.Tasks Message-ID: <67cf11e6834f9_272ba1239f74888bd@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/conpat-one-list at Glasgow Haskell Compiler / GHC Commits: 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - bd64f42b by Vladislav Zavialov at 2025-03-10T19:22:36+03:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - 238 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/include/RtsAPI.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/640080a9e85c12934fea655ec6f0d70c936e30d0...bd64f42b23c0138f659cce3f4519609e23767fde -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/640080a9e85c12934fea655ec6f0d70c936e30d0...bd64f42b23c0138f659cce3f4519609e23767fde You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/bbd1491a/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 16:38:44 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 10 Mar 2025 12:38:44 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/ghcup-metadata-cleanup Message-ID: <67cf1594f233_272ba1263b809367a@gitlab.mail> Ben Gamari pushed new branch wip/ghcup-metadata-cleanup at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghcup-metadata-cleanup You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/284ddef8/attachment.html> From gitlab at gitlab.haskell.org Mon Mar 10 17:57:41 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Mon, 10 Mar 2025 13:57:41 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] Cleanup warnings Message-ID: <67cf2815c6f60_28524d71f9e41013b6@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: bd98351d by Sven Tennie at 2025-03-10T18:57:24+01:00 Cleanup warnings - - - - - 4 changed files: - compiler/CodeGen.Platform.h - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs Changes: ===================================== compiler/CodeGen.Platform.h ===================================== @@ -1274,44 +1274,6 @@ freeReg REG_XMM5 = False freeReg REG_XMM6 = False # endif -# if defined(REG_YMM1) -freeReg REG_YMM1 = False -# endif -# if defined(REG_YMM2) -freeReg REG_YMM2 = False -# endif -# if defined(REG_YMM3) -freeReg REG_YMM3 = False -# endif -# if defined(REG_YMM4) -freeReg REG_YMM4 = False -# endif -# if defined(REG_YMM5) -freeReg REG_YMM5 = False -# endif -# if defined(REG_YMM6) -freeReg REG_YMM6 = False -# endif - -# if defined(REG_ZMM1) -freeReg REG_ZMM1 = False -# endif -# if defined(REG_ZMM2) -freeReg REG_ZMM2 = False -# endif -# if defined(REG_ZMM3) -freeReg REG_ZMM3 = False -# endif -# if defined(REG_ZMM4) -freeReg REG_ZMM4 = False -# endif -# if defined(REG_ZMM5) -freeReg REG_ZMM5 = False -# endif -# if defined(REG_ZMM6) -freeReg REG_ZMM6 = False -# endif - freeReg _ = True #else ===================================== compiler/GHC/CmmToAsm/RV64/CodeGen.hs ===================================== @@ -1107,7 +1107,6 @@ getRegister' config plat expr = | fitsIn12bitImm n -> return $ Any toFmt (\d -> unitOL $ annExpr expr (ORI (OpReg toFmt d) (OpReg fromFmt r') (OpImm (ImmInteger n)))) where - w' = formatToWidth (cmmTypeFormat (cmmRegType reg)) r' = getRegisterReg plat reg toFmt = intFormat w fromFmt = (cmmTypeFormat (cmmRegType reg)) @@ -1274,8 +1273,8 @@ getRegister' config plat expr = MO_S_Shr w -> intOp True w (\d x y -> unitOL $ annExpr expr (SRA d x y)) -- Vector operations - MO_VF_Extract length w -> vecExtract ((scalarFormatFormat . floatScalarFormat) w) - MO_V_Extract length w -> vecExtract ((scalarFormatFormat . intScalarFormat) w) + MO_VF_Extract _length w -> vecExtract ((scalarFormatFormat . floatScalarFormat) w) + MO_V_Extract _length w -> vecExtract ((scalarFormatFormat . intScalarFormat) w) MO_VF_Add length w -> vecOp (floatVecFormat length w) VADD MO_VF_Sub length w -> vecOp (floatVecFormat length w) VSUB @@ -1433,7 +1432,7 @@ getRegister' config plat expr = -- Return 0 when the operation cannot overflow, /= 0 otherwise do_mul_may_oflo :: Width -> CmmExpr -> CmmExpr -> NatM Register do_mul_may_oflo w _x _y | w > W64 = pprPanic "Cannot multiply larger than 64bit" (ppr w) - do_mul_may_oflo w at W64 x y = do + do_mul_may_oflo W64 x y = do (reg_x, format_x, code_x) <- getSomeReg x (reg_y, format_y, code_y) <- getSomeReg y -- TODO: Can't we clobber reg_x and reg_y to save registers? @@ -1762,12 +1761,12 @@ genCondJump :: genCondJump bid expr = do case expr of -- Optimized == 0 case. - CmmMachOp (MO_Eq w) [x, CmmLit (CmmInt 0 _)] -> do + CmmMachOp (MO_Eq _w) [x, CmmLit (CmmInt 0 _)] -> do (reg_x, format_x, code_x) <- getSomeReg x return $ code_x `snocOL` annExpr expr (BCOND EQ zero (OpReg format_x reg_x) (TBlock bid)) -- Optimized /= 0 case. - CmmMachOp (MO_Ne w) [x, CmmLit (CmmInt 0 _)] -> do + CmmMachOp (MO_Ne _w) [x, CmmLit (CmmInt 0 _)] -> do (reg_x, format_x, code_x) <- getSomeReg x return $ code_x `snocOL` annExpr expr (BCOND NE zero (OpReg format_x reg_x) (TBlock bid)) @@ -1811,8 +1810,8 @@ genCondJump bid expr = do `appOL` unitOL (annExpr expr (BCOND cmp x' y' (TBlock bid))) _ -> code_x `appOL` code_y `appOL` unitOL (annExpr expr (BCOND cmp x' y' (TBlock bid))) - fbcond :: Width -> Cond -> NatM (OrdList Instr) - fbcond w cmp = do + fbcond :: Cond -> NatM (OrdList Instr) + fbcond cmp = do -- ensure we get float regs (reg_fx, format_fx, code_fx) <- getFloatReg x (reg_fy, format_fy, code_fy) <- getFloatReg y @@ -1825,12 +1824,12 @@ genCondJump bid expr = do `snocOL` BCOND EQ condOpReg (OpReg II64 oneReg) (TBlock bid) case mop of - MO_F_Eq w -> fbcond w EQ - MO_F_Ne w -> fbcond w NE - MO_F_Gt w -> fbcond w FGT - MO_F_Ge w -> fbcond w FGE - MO_F_Lt w -> fbcond w FLT - MO_F_Le w -> fbcond w FLE + MO_F_Eq _w -> fbcond EQ + MO_F_Ne _w -> fbcond NE + MO_F_Gt _w -> fbcond FGT + MO_F_Ge _w -> fbcond FGE + MO_F_Lt _w -> fbcond FLT + MO_F_Le _w -> fbcond FLE MO_Eq w -> sbcond w EQ MO_Ne w -> sbcond w NE MO_S_Gt w -> sbcond w SGT @@ -2029,7 +2028,7 @@ genCCall target@(ForeignTarget expr _cconv) dest_regs arg_regs = do passArguments gpRegs fpRegs vRegs args stackSpaceWords (vReg : accumRegs) accumCode' -- No more vector regs, and we want to pass a vector argument. - passArguments gpRegs fpRegs (vReg : vRegs) ((r, format, _hint, code_r) : args) stackSpaceWords accumRegs accumCode + passArguments _gpRegs _fpRegs (_vReg : _vRegs) ((_r, format, _hint, _code_r) : _args) _stackSpaceWords _accumRegs _accumCode | isVecFormat format = pprPanic "passArguments" (text "TODO: Implement and test vector argument passing on the stack.") passArguments _ _ _ _ _ _ _ = pprPanic "passArguments" (text "invalid state") @@ -2217,7 +2216,7 @@ genCCall (PrimTarget mop) dest_regs arg_regs = do format = intFormat w return code | otherwise -> panic "mal-formed AtomicRead" - mo@(MO_AtomicWrite w ord) + mo@(MO_AtomicWrite _w ord) | [p_reg, val_reg] <- arg_regs -> do (p, _fmt_p, code_p) <- getSomeReg p_reg (val, fmt_val, code_val) <- getSomeReg val_reg ===================================== compiler/GHC/CmmToAsm/RV64/Instr.hs ===================================== @@ -20,7 +20,6 @@ import GHC.CmmToAsm.Utils import GHC.Data.FastString (LexicalFastString) import GHC.Platform import GHC.Platform.Reg -import GHC.Platform.Reg.Class.Separate import GHC.Platform.Regs import GHC.Prelude import GHC.Stack ===================================== compiler/GHC/CmmToAsm/RV64/Ppr.hs ===================================== @@ -797,7 +797,7 @@ pprInstr platform instr = case instr of FNMSub -> text "\tfnmsub" <> dot <> floatPrecission d in op4 fma d r1 r2 r3 VFMA variant o1@(OpReg fmt _reg) o2 o3 - | VecFormat l fmt' <- fmt -> + | VecFormat _l fmt' <- fmt -> let formatString = if (isFloatFormat . scalarFormatFormat) fmt' then text "f" else text "" prefix = text "v" <> formatString suffix = text "vv" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd98351dc047e8714b8265cd803e48e06c666188 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd98351dc047e8714b8265cd803e48e06c666188 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/80599020/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 18:11:48 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Mon, 10 Mar 2025 14:11:48 -0400 Subject: [Git][ghc/ghc][wip/int-index/vdq-emptycase-errmsg] 34 commits: rts: fix top handler closure type signatures Message-ID: <67cf2b646fa30_29ef1531e9088884a@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/vdq-emptycase-errmsg at Glasgow Haskell Compiler / GHC Commits: c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 957832b0 by Vladislav Zavialov at 2025-03-10T21:11:32+03:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 183 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Unique.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/include/RtsAPI.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b4999d0e99fe6edcaac1ca808796bc4c0b54a86c...957832b08e76c4c374ea34d5830d53e300b5fc05 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b4999d0e99fe6edcaac1ca808796bc4c0b54a86c...957832b08e76c4c374ea34d5830d53e300b5fc05 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/e98f2c4a/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 19:22:33 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Mon, 10 Mar 2025 15:22:33 -0400 Subject: [Git][ghc/ghc][wip/T25647] 16 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67cf3bf912e9f_29ef15bdb8e8990ab@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - e792e408 by Patrick at 2025-03-10T20:20:15+08:00 add note and comment - - - - - 34ee6003 by Patrick at 2025-03-10T20:20:26+08:00 Merge branch 'master' into wip/T25647 - - - - - 6b38aefc by Patrick at 2025-03-11T03:22:24+08:00 refactor - - - - - 122 changed files: - compiler/GHC.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Instance/Class.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/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Types/LclEnv.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b791749b6284f22c85df91bc55ed914d6bd2c00c...6b38aefcc753b846be43b59490864f9785571c0a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b791749b6284f22c85df91bc55ed914d6bd2c00c...6b38aefcc753b846be43b59490864f9785571c0a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/df1ae1fa/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 19:27:25 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 10 Mar 2025 15:27:25 -0400 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] remove special case of tcbody from tcLambdaMatches Message-ID: <67cf3d1d76960_2c2395c5cd887730@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 55d506d1 by Apoorv Ingle at 2025-03-10T13:49:10-05:00 remove special case of tcbody from tcLambdaMatches - - - - - 3 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -531,13 +531,6 @@ type instance XXExpr GhcTc = XXExprGhcTc data HsThingRn = OrigExpr (HsExpr GhcRn) -- ^ The source, user written, expression | OrigStmt (ExprLStmt GhcRn) HsDoFlavour -- ^ which kind of do-block did this statement come from -isHsThingRnExpr, isHsThingRnStmt :: HsThingRn -> Bool -isHsThingRnExpr (OrigExpr{}) = True -isHsThingRnExpr _ = False - -isHsThingRnStmt (OrigStmt{}) = True -isHsThingRnStmt _ = False - data XXExprGhcRn = ExpandedThingRn { xrn_orig :: HsThingRn -- The original source thing to be used for error messages , xrn_expanded :: HsExpr GhcRn -- The compiler generated expanded thing ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -1252,5 +1252,4 @@ addExprCtxt e thing_inside -- when we don't want to say "In the expression: _", -- because it is mentioned in the error message itself HsUnboundVar {} -> thing_inside - XExpr (ExpandedThingRn {}) -> thing_inside _ -> addErrCtxt (ExprCtxt e) thing_inside ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -155,21 +155,13 @@ tcLambdaMatches e lam_variant matches invis_pat_tys res_ty ; (wrapper, r) <- matchExpectedFunTys herald GenSigCtxt arity res_ty $ \ pat_tys rhs_ty -> - tcMatches tc_body (invis_pat_tys ++ pat_tys) rhs_ty matches + tcMatches tcBody (invis_pat_tys ++ pat_tys) rhs_ty matches ; return (wrapper, r) } where herald = ExpectedFunTyLam lam_variant e -- See Note [Herald for matchExpectedFunTys] in GHC.Tc.Utils.Unify - tc_body | isDoExpansionGenerated (mg_ext matches) - -- See Part 3. B. of Note [Expanding HsDo with XXExprGhcRn] in - -- `GHC.Tc.Gen.Do`. Testcase: Typeable1 - = tcBodyNC -- NB: Do not add any error contexts - -- It has already been done - | otherwise - = tcBody - {- @tcCaseMatches@ doesn't do the argument-count check because the parser guarantees that each equation has exactly one argument. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/55d506d156a9668411c5d816bc59249ac5b31412 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/55d506d156a9668411c5d816bc59249ac5b31412 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/d181c4e9/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 19:29:23 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 10 Mar 2025 15:29:23 -0400 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] remove special case of tcbody from tcLambdaMatches Message-ID: <67cf3d938eb10_2c2395195b5488221@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: cb8ce844 by Apoorv Ingle at 2025-03-10T14:29:05-05:00 remove special case of tcbody from tcLambdaMatches - - - - - 3 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -531,13 +531,6 @@ type instance XXExpr GhcTc = XXExprGhcTc data HsThingRn = OrigExpr (HsExpr GhcRn) -- ^ The source, user written, expression | OrigStmt (ExprLStmt GhcRn) HsDoFlavour -- ^ which kind of do-block did this statement come from -isHsThingRnExpr, isHsThingRnStmt :: HsThingRn -> Bool -isHsThingRnExpr (OrigExpr{}) = True -isHsThingRnExpr _ = False - -isHsThingRnStmt (OrigStmt{}) = True -isHsThingRnStmt _ = False - data XXExprGhcRn = ExpandedThingRn { xrn_orig :: HsThingRn -- The original source thing to be used for error messages , xrn_expanded :: HsExpr GhcRn -- The compiler generated expanded thing ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -1252,5 +1252,4 @@ addExprCtxt e thing_inside -- when we don't want to say "In the expression: _", -- because it is mentioned in the error message itself HsUnboundVar {} -> thing_inside - XExpr (ExpandedThingRn {}) -> thing_inside _ -> addErrCtxt (ExprCtxt e) thing_inside ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -79,7 +79,7 @@ import GHC.Types.Name import GHC.Types.Name.Reader (LocalRdrEnv) import GHC.Types.Id import GHC.Types.SrcLoc -import GHC.Types.Basic( VisArity, isDoExpansionGenerated ) +import GHC.Types.Basic( VisArity ) import qualified GHC.Data.List.NonEmpty as NE @@ -155,21 +155,13 @@ tcLambdaMatches e lam_variant matches invis_pat_tys res_ty ; (wrapper, r) <- matchExpectedFunTys herald GenSigCtxt arity res_ty $ \ pat_tys rhs_ty -> - tcMatches tc_body (invis_pat_tys ++ pat_tys) rhs_ty matches + tcMatches tcBody (invis_pat_tys ++ pat_tys) rhs_ty matches ; return (wrapper, r) } where herald = ExpectedFunTyLam lam_variant e -- See Note [Herald for matchExpectedFunTys] in GHC.Tc.Utils.Unify - tc_body | isDoExpansionGenerated (mg_ext matches) - -- See Part 3. B. of Note [Expanding HsDo with XXExprGhcRn] in - -- `GHC.Tc.Gen.Do`. Testcase: Typeable1 - = tcBodyNC -- NB: Do not add any error contexts - -- It has already been done - | otherwise - = tcBody - {- @tcCaseMatches@ doesn't do the argument-count check because the parser guarantees that each equation has exactly one argument. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb8ce8449cc59d4186bc8f1830c9da630c28fc53 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb8ce8449cc59d4186bc8f1830c9da630c28fc53 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/b078029a/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 19:31:36 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Mon, 10 Mar 2025 15:31:36 -0400 Subject: [Git][ghc/ghc][wip/T25647] fix test T25647d Message-ID: <67cf3e188715a_2c23951a92f88876e@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 7f973173 by Patrick at 2025-03-11T03:31:25+08:00 fix test T25647d - - - - - 4 changed files: - testsuite/tests/typecheck/should_compile/T25647d.hs - + testsuite/tests/typecheck/should_compile/T25647d_fail.hs - + testsuite/tests/typecheck/should_compile/T25647d_fail.stderr - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== testsuite/tests/typecheck/should_compile/T25647d.hs ===================================== @@ -15,14 +15,6 @@ type Cast1 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: type family Cast1 r s a b c d p where Cast1 _ c _ b Refl Refl (p->q) = Int -type Cast2 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type +type Cast2 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: a) -> (b :~: b) -> Type -> Type type family Cast2 r s a b c d p where - Cast2 _ c _ b Refl Refl (p->q) = Int - -type Cast3 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type -type family Cast3 r s a b c d p where - forall. Cast3 _ c _ b Refl Refl (p->q) = Int - -type Cast4 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type -type family Cast4 r s a b c d p where - forall aa cc. Cast4 aa cc _ b Refl Refl (p->q) = Int + forall c b p q.Cast2 _ c _ b Refl Refl (p->q) = Int ===================================== testsuite/tests/typecheck/should_compile/T25647d_fail.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE DataKinds, TypeFamilies, PolyKinds, MagicHash #-} + +module T25647d_fail where + +import GHC.Exts +import Data.Kind +import GHC.Exts (RuntimeRep) +import Data.Type.Equality ((:~:)(Refl) ) + +type Cast3 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type +type family Cast3 r s a b c d p where + forall. Cast3 _ c _ b Refl Refl (p->q) = Int + +type Cast4 :: forall (r :: RuntimeRep) (s :: RuntimeRep) (a :: RuntimeRep) (b :: RuntimeRep) -> (a :~: IntRep) -> (b :~: IntRep) -> Type -> Type +type family Cast4 r s a b c d p where + forall aa cc b p q. Cast4 aa cc _ b Refl Refl (p->q) = Int ===================================== testsuite/tests/typecheck/should_compile/T25647d_fail.stderr ===================================== @@ -0,0 +1,12 @@ +T25647d_fail.hs:12:19: error: [GHC-76037] + Not in scope: type variable ‘c’ + +T25647d_fail.hs:12:23: error: [GHC-76037] + Not in scope: type variable ‘b’ + +T25647d_fail.hs:12:36: error: [GHC-76037] + Not in scope: type variable ‘p’ + +T25647d_fail.hs:12:39: error: [GHC-76037] + Not in scope: type variable ‘q’ + ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -940,4 +940,5 @@ test('T25647b', normal, compile, ['']) test('T25647c', normal, compile, ['']) test('T25647d', normal, compile, ['']) test('T25647_fail', normal, compile_fail, ['']) +test('T25647d_fail', normal, compile_fail, ['']) test('T25725', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f97317308a441cb0a65c55140e767e685ac1ad4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f97317308a441cb0a65c55140e767e685ac1ad4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/d80f8d24/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 20:08:09 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 10 Mar 2025 16:08:09 -0400 Subject: [Git][ghc/ghc][wip/kill-ioport] 353 commits: Add regression test for #16234 Message-ID: <67cf46a9986ea_2c239576d7989861b@gitlab.mail> Ben Gamari pushed to branch wip/kill-ioport at Glasgow Haskell Compiler / GHC Commits: fa66fa64 by Ryan Scott at 2024-11-14T19:05:00-05:00 Add regression test for #16234 Issue #16234 was likely fixed by !9765. This adds a regression test to ensure that it remains fixed. Fixes #16234. - - - - - bfe64df8 by Matthew Pickering at 2024-11-14T19:05:36-05:00 ghc-internal: Update to Unicode 16 This patch updates the automatically generated code for querying unicode properties to unicode 16. Fixes #25402 - - - - - 1fd83f86 by Ben Gamari at 2024-11-14T19:06:13-05:00 configure: Accept happy-2.1.2 happy-2.1 was released in late Oct 2024. I have confirmed that master bootstraps with it. Here we teach configure to accept this tool. Fixes #25438. - - - - - aa58fc5b by Ben Gamari at 2024-11-14T19:06:49-05:00 rts: Tighten up invariants of PACK - - - - - 8aa4c10a by Ben Gamari at 2024-11-14T19:06:49-05:00 testsuite: Fix badly escaped literals Use raw string literals to ensure that `\s` is correctly interpreted as a character class. - - - - - 0e084029 by Ben Gamari at 2024-11-14T19:06:49-05:00 rts: Improve documentation of SLIDE bytecode instruction - - - - - 9bf3663b by Ben Gamari at 2024-11-14T19:06:49-05:00 rts/Interpreter: Assert that TEST*_P discriminators are valid - - - - - 1f668511 by Ben Gamari at 2024-11-14T19:06:49-05:00 rts/Interpreter: Improve documentation of TEST*_P instructions - - - - - 59e0a770 by Cheng Shao at 2024-11-14T19:07:25-05:00 misc: improve clangd compile_flags.txt flags This patch improves the compile_flags.txt config used to power clangd for the rts C codebase. The flags in the file are sampled & deduped from a real stage1 build with clang-19 and vastly improves the IDE accuracy when hacking the rts. For maximum code coverage under the default settings, compile_flags.txt defaults to threaded+profiled+dynamic+debug way. This does not mean profdyn needs to be actually built in _build/stage1 for IDE to work. To activate IDE for other RTS ways, simply remove one of the -D flags at the end of compile_flags.txt and restart clangd. - - - - - c2c562e0 by Ben Gamari at 2024-11-14T19:08:01-05:00 testsuite: Don't consider untracked files in dirtiness check Considering trees containing untracked files as dirty is a bridge too far. The chance of an untracked file significantly affecting measured performanced metrics is quite small whereas not collecting measurements is quite inconvenient for some workflows. We now ignore untracked files in the dirtiness check. Fixes #25471. - - - - - ed2ed6c5 by Cheng Shao at 2024-11-14T19:08:37-05:00 testsuite: add regression test T25473 This commit adds regression test T25473 marked as broken due to #25473. It will be fixed in the subsequent commit. - - - - - bd0a8b7e by Cheng Shao at 2024-11-14T19:08:37-05:00 wasm: fix foreign import javascript "wrapper" in TH/ghci This patch fixes foreign import javascript "wrapper" in wasm backend's TH/ghci by fixing the handling of dyld/finalization_registry magic variables. Fixes T25473 and closes #25473. - - - - - f1b0bc32 by Ben Gamari at 2024-11-14T19:09:13-05:00 rts/linker: Make FreeBSD declarations proper prototypes The iconv declarations for FreeBSD were previously not prototypes, leading to warnings. - - - - - 086cbbc1 by Ben Gamari at 2024-11-14T19:09:13-05:00 base: Drop redundant import in FreeBSD ExecutablePath implementation - - - - - 79ecd199 by Ben Gamari at 2024-11-14T19:09:13-05:00 compiler: Fix partial selector warnings in GHC.Runtime.Heap.Inspect - - - - - 1acb73bf by Andrew Lelechenko at 2024-11-15T06:10:47-05:00 gitlab: mention CLC in MR template - - - - - 8f2e0832 by Ben Gamari at 2024-11-15T06:11:24-05:00 rts: Allow use of GNU-stack notes on FreeBSD Previously we gated use of GNU-style non-executable stack notes to only apply on Linux. However, these are also supported by FreeBSD, which also uses ELF. Fix this. Fixes #25475. - - - - - 2c427cb0 by Ben Gamari at 2024-11-16T05:27:40-05:00 rts: Fix EINTR check in timerfd ticker When `poll` failed we previously checked that `errno == -EINTR` to silence the failure warning. However, this is wrong as `errno` values are generally not negated error codes (in contrast to many system call results, which is likely what the original author had in mind). Fixes #25477. - - - - - a0fa4941 by Ben Gamari at 2024-11-16T05:28:16-05:00 rts: Increase gen_workspace alignment to 128 bytes on AArch64 Increase to match the 128-byte cache-line size of Apple's ARMv8 implementation. Closes #25459. - - - - - 142d8afa by Ben Gamari at 2024-11-16T16:20:47-05:00 rts/RtsFlags: Refactor size parsing This makes a number of improvements mentioned in #20201: * fail if the argument cannot be parsed as a number (`-Mturtles`) * fail if an unrecognized unit is given (e.g. `-M1x`) - - - - - b7a146e5 by Ben Gamari at 2024-11-16T16:20:47-05:00 testsuite: Add tests for RTS flag parsing error handling See #20201. - - - - - ddb7afa6 by Ben Gamari at 2024-11-16T16:21:23-05:00 users guide: Mention language extensions in equality constraints discussion As suggested in #24127, mention the language extensions necessary for usage of equality constriants in their documentation. Closes #24127. - - - - - 36133dac by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide/9.14.1-notes: Fix list syntax - - - - - 888de658 by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide/debug-info: Fix duplicate flag descriptions - - - - - f120e427 by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide: Fix reference to 9.14.1 release notes - - - - - 8e975032 by Ben Gamari at 2024-11-16T16:21:59-05:00 Introduce GHC.Tc.Plugin.lookupTHName This makes it significantly more convenient (and less GHC-version-dependent) to resolve a template-haskell name into a GHC Name. As proposed in #24741. - - - - - a0e168ec by ARATA Mizuki at 2024-11-16T16:22:40-05:00 x86 NCG SIMD: Lower packFloatX4#, insertFloatX4# and broadcastFloatX4# to SSE1 instructions Fixes #25441 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 3936bf1b by sheaf at 2024-11-16T16:23:22-05:00 X86 NCG: allow VXOR at scalar floating-point types The NCG can emit VXOR instructions at scalar floating-point types, but the pretty-printer would panic instead of emitting the appropriate VXORPS/VXORPD instructions. This patch rectifies that oversight. Fixes #25455 - - - - - d9dff93a by Ben Gamari at 2024-11-16T16:23:58-05:00 rts: Fix platform-dependent pointer casts Previously we had unnecessary (and incorrect) platform-dependent casts to turn `OSThreadIds`s into a integer. We now just uniformly cast first to a `uintptr_t` (which is always safe, regardless of whether `OSThreadId` is a pointer), and then cast to the desired integral type. This fixes a warning on musl platforms. - - - - - 6d95cdb8 by Ben Gamari at 2024-11-16T16:24:34-05:00 testsuite: Mark encoding004 as broken on FreeBSD Due to #22003, CP936 fails to roundtrip: ```diff == CP936 +Failed to roundtrip given mutant byte at index 891 (251 /= 123 at index 891) +Failed to roundtrip given mutant byte at index 1605 (197 /= 69 at index 1605) +Failed to roundtrip given mutant byte at index 2411 (235 /= 107 at index 2411) +Failed to roundtrip given mutant byte at index 6480 (208 /= 80 at index 6480) +Failed to roundtrip given mutant byte at index 6482 (210 /= 82 at index 6482) +Failed to roundtrip given mutant byte at index 6484 (212 /= 84 at index 6484) +Failed to roundtrip given mutant byte at index 6496 (224 /= 96 at index 6496) +Failed to roundtrip given mutant byte at index 7243 (203 /= 75 at index 7243) +Failed to roundtrip given mutant byte at index 7277 (237 /= 109 at index 7277) +Failed to roundtrip given mutant byte at index 8027 (219 /= 91 at index 8027) +Failed to roundtrip given mutant byte at index 8801 (225 /= 97 at index 8801) ``` - - - - - 26e86984 by Ben Gamari at 2024-11-18T04:05:31-05:00 hadrian: Allow haddock options to be passed via key-value settings - - - - - 6e68b117 by Matthew Pickering at 2024-11-18T04:06:07-05:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - a4e0d235 by Rodrigo Mesquita at 2024-11-18T04:06:07-05:00 exceptions: Improve the message layout as per #285 This commit fixes the layout of the additional information included when displaying an exception, namely the type of the exception. It also fixes the default handler's heading message to work well together with the improved display message of SomeException. CLC proposal#285 - - - - - 284ffab3 by Rodrigo Mesquita at 2024-11-18T04:06:07-05:00 Display type and callstack of exception on handler This commit changes the Exception instance of SomeException to *simply* display the underlying exception in `displayException`. The augmented exception message that included the type and backtrace of the exception are now only printed on a call to `displayExceptionWithInfo`. At a surface level, existing programs should behave the same since the `uncaughtExceptionHandler`, which is responsible for printing out uncaught exceptions to the user, will use `displayExceptionWithInfo` by default. However, unlike the instance's `displayException` method, the `uncaughtExceptionHandler` can be overriden with `setUncaughtExceptionHandler`. This makes the extra information opt-in without fixing it the instance, which can be valuable if your program wants to display uncaught exceptions to users in a user-facing way (ie without backtraces). This is what was originally agreed for CLC#231 or CLC#261 with regard to the type of the exception information. The call stack also becoming part of the default handler rather than the Exception instance is an ammendment to CLC#164. Discussion of the ammendment is part of CLC#285. - - - - - 36cddd2c by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Remove redundant CallStack from exceptions Before the exception backtraces proposal was implemented, ErrorCall accumulated its own callstack via HasCallStack constraints, but ExceptionContext is now accumulated automatically. The original ErrorCall mechanism is now redundant and we get a duplicate CallStack Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall CLC proposal#285 Fixes #25283 - - - - - 7a74330b by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Freeze call stack in error throwing functions CLC proposal#285 - - - - - 3abf31a4 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 De-duplicate displayContext and displayExceptionContext The former was unused except for one module where it was essentially re-defining displayExceptionContext. Moreover, this commit extends the fix from bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too, which was missing. - - - - - c0d783f8 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Re-export NoBacktrace from Control.Exception This was originally proposed and accepted in section "2.7 Capturing Backtraces on Exceptions" of the CLC proposal for exception backtraces. However, the implementation missed this re-export, which this commit now fixes. - - - - - 802b5c3e by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Fix exception backtraces from GHCi When running the program with `runhaskell`/`runghc` the backtrace should match the backtrace one would get by compiling and running the program. But currently, an exception thrown in a program interpreted with `runhaskell` will: * Not include the original exception backtrace at all * Include the backtrace from the internal GHCi/ghc rethrowing of the original exception This commit fixes this divergence by not annotating the ghc(i) backtrace (with NoBacktrace) and making sure that the backtrace of the original exception is serialized across the boundary and rethrown with the appropriate context. Fixes #25116 The !13301 MR (not this commit in particular) improves performance of MultiLayerModules. Unfortunately, T3294 regresses on aarch64-linux-deb12 by 1% allocations. Since this patch must be merged for 9.12 ASAP, we will not be able to investigate the slight regression on this platform in time. ------------------------- Metric Decrease: MultiLayerModulesRecomp MultiLayerModulesTH_OneShot Metric Increase: T3294 ------------------------- - - - - - 3e89eb65 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 base: Add to changelog.md CLC #285 - - - - - d9326a48 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Bump array and stm submodules for testsuite The testsuites of array and stm had to be updated according to !13301. Updates submodule array and stm. - - - - - 325fcb5d by Ben Gamari at 2024-11-18T04:06:45-05:00 rts/adjustor: Clean up code style of Nativei386 adjustor - - - - - 39bb6e58 by Ben Gamari at 2024-11-18T04:06:45-05:00 rts/adjustor: Fix stack overrun error in Nativei386 adjustor We were reserving the wrong kind of adjustor context (the generic `AdjustorContext` used by other adjustor implementations, rather than the i386-specific `CCallContext`) to return the adjustor context while freeing, resulting in #25485. Fixes #25485. - - - - - 831aab22 by sheaf at 2024-11-18T21:22:36-05:00 Include diagnostic reason in -fdiagnostics-as-json This commit ensures that the -fdiagnostics-as-json output includes the diagnostic reason. This allows the full error message produced by GHC to be re-constructed from the JSON output. Fixes #25403 - - - - - 3e5bfdd3 by Ben Gamari at 2024-11-18T21:23:12-05:00 rts: Introduce printIPE This is a convenience utility for use in GDB. - - - - - 44d909a3 by Sjoerd Visscher at 2024-11-19T14:38:24-05:00 Don't store boot locations in finder cache Partially reverts commit fff55592a7b Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache. Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for. - - - - - 64c95292 by Sjoerd Visscher at 2024-11-19T14:38:24-05:00 Concentrate boot extension logic in Finder With new mkHomeModLocation that takes an extra HscSource to add boot extensions if required. - - - - - 11bad98d by ARATA Mizuki at 2024-11-19T14:39:08-05:00 Better documentation for floating-point min/max and SIMD primitives See #25350 for floating-point min/max Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 791a47b2 by Arnaud Spiwack at 2024-11-20T14:00:05+00:00 Add test for #25185 - - - - - 374e18e5 by Arnaud Spiwack at 2024-11-20T14:09:30+00:00 Quick look: emit the multiplicity of app heads in tcValArgs Otherwise it's not scaled properly by the context, allowing unsound expressions. Fixes #25185. - - - - - 1fc02399 by sheaf at 2024-11-20T18:11:03-05:00 x86 NCG: fix regUsageOfInstr for VMOVU & friends This commit fixes the implementation of 'regUsageOfInstr' for vector operations that take an 'Operand' as the destination, by ensuring that when the destination is an address then the address should be *READ*, and not *WRITTEN*. Getting this wrong is a disaster, as it means the register allocator has incorrect information, which can lead to it discard stores to registers, segfaults ensuing. Fixes #25486 - - - - - 7bd407a6 by Brandon Chinn at 2024-11-21T14:08:15-05:00 Fix CRLF in multiline strings (#25375) - - - - - 7575709b by Rodrigo Mesquita at 2024-11-21T14:08:52-05:00 Improve reachability queries on ModuleGraph Introduces `ReachabilityIndex`, an index constructed from a `GHC.Data.Graph.Directed` `Graph` that supports fast reachability queries (in $O(1)$). This abstract data structure is exposed from `GHC.Data.Graph.Directed.Reachability`. This index is constructed from the module graph nodes and cached in `ModuleGraph`, enabling efficient reachability queries on the module graph. Previously, we'd construct a Map of Set of ModuleGraph nodes which used a lot of memory (`O(n^2)` in the number of nodes) and cache that in the `ModuleGraph`. By using the reachability index we get rid of this space leak in the module graph -- even though the index is still quadratic in the number of modules, it is much, much more space efficient due to its representation using an IntMap of IntSet as opposed to the transitive closure we previously cached. In a memory profile of MultiLayerModules with 100x100 modules, memory usage improved from 6GB residency to 2.8GB, out of which roughly 1.8GB are caused by a second space leak related to ModuleGraph. On the same program, it brings compile time from 7.5s to 5.5s. Note how we simplify `checkHomeUnitsClosed` in terms of `isReachableMany` and by avoiding constructing a second graph with the full transitive closure -- it suffices to answer the reachability query on the full graph without collapsing the transitive closure completely into nodes. Unfortunately, solving this leak means we have to do a little bit more work since we can no longer cache the result of turning vertex indices into nodes. This results in a slight regression in MultiLayerModulesTH_Make, but results in large performance and memory wins when compiling large amounts of modules. ------------------------- Metric Decrease: mhu-perf Metric Increase: MultiLayerModulesTH_Make ------------------------- - - - - - bcbcdaaf by Cheng Shao at 2024-11-21T14:09:28-05:00 driver: fix hpc undefined symbol issue in TH with -fprefer-byte-code This commit fixes an undefined symbol error in RTS linker when attempting to compile home modules with -fhpc and -fbyte-code-and-object-code/-fprefer-byte-code, see #25510 for detailed description and analysis of the bug. Also adds T25510/T25510c regression tests to test make mode/oneshot mode of the bug. - - - - - 970ada5a by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Bump ci-images For introduction of Alpine/i386 image. Thanks to Julian for the base image. Co-Authored-By: Julian Ospald <hasufell at hasufell.de> - - - - - 8115abc2 by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Add release job for i386/Alpine As requested by Mikolaj and started by Julian. Co-Authored-By: Julian Ospald <hasufell at hasufell.de> - - - - - 639f0149 by Ben Gamari at 2024-11-22T23:32:06-05:00 rts/linker/Elf: Resolve _GLOBAL_OFFSET_TABLE_ - - - - - 490d4d0a by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Mark i386 Alpine test breakages Marks the following tests as broken on i386/Alpine: * T22033 due to #25497 * simd009, T25062_V16, T25169, T22187_run due to #25498 - - - - - 536cdf09 by Cheng Shao at 2024-11-22T23:32:42-05:00 compiler: remove unused GHC.Linker.Loader.loadExpr This patch removes the unused `GHC.Linker.Loader.loadExpr` function. It was moved from `GHC.Runtime.Linker.linkExpr` in `ghc-9.0` to `GHC.Linker.Loader.loadExpr` in `ghc-9.2`, and remain completely unused and untested ever since. There's also no third party user of this function to my best knowledge, so let's remove this. Anyone who wants to write their own GHC API function to load bytecode can consult the source code in older release branches. - - - - - 6ee35024 by Drew Fenwick at 2024-11-22T23:33:26-05:00 Fix a non-compiling example in the type abstractions docs This patch adds a missing Show constraint to a code example in the User Guide's type abstractions docs to fix issue #25422. - - - - - d1172e20 by Rodrigo Mesquita at 2024-11-22T23:34:02-05:00 Re-introduce ErrorCallWithLocation with a deprecation pragma With the removal of the duplicate backtrace, part of CLC proposal #285, the constructor `ErrorCallWithLocation` was removed from base. This commit re-introduces it with a deprecation. - - - - - 1187a60a by Ben Gamari at 2024-11-22T23:34:39-05:00 testsuite: Skip tests requiring Hadrian deps in out-of-tree testsuite runs Some testsuite tests require specific tools (e.g. `check-ppr` and `check-exact`) beyond those shipped in the binary distribution. Skip these tests. Fixes #13897. - - - - - c37d7a2e by Ben Gamari at 2024-11-22T23:34:39-05:00 testsuite: Declare exactprint tests' dependency on check-exact - - - - - 454ce957 by Ben Gamari at 2024-11-22T23:35:15-05:00 ghc-internal: Fix a few cases of missing Haddock markup - - - - - a249649b by Ben Gamari at 2024-11-22T23:35:51-05:00 testsuite/GHCiPrimCall : Add missing Makefile includes - - - - - a021a493 by Ben Gamari at 2024-11-22T23:35:51-05:00 testsuite/IpeStats: Use Make rather than shell interpolation - - - - - 6e1fbda7 by Ben Gamari at 2024-11-25T03:55:44-05:00 hadrian-ghci-multi: Pass -this-package-name in unit response files As noted in #25509, the `-this-package-name` must be passed for each package to ensure that GHC can response references to the packages' exposed modules via package-qualified imports. Fix this. Closes #25509. - - - - - a05e4a9b by Simon Hengel at 2024-11-25T03:56:33-05:00 Refactoring: Use `OnOff` more consistently for `Extension` - - - - - 7536181d by Matthew Pickering at 2024-11-25T14:00:07-05:00 driver: Always link against "base" package when one shot linking The default value for base-unit-id is stored in the settings file. At install time, this can be set by using the BASE_UNIT_ID environment variable. At runtime, the value can be set by `-base-unit-id` flag. For whether all this is a good idea, see #25382 Fixes #25382 - - - - - 7f90f319 by Andreas Klebinger at 2024-11-25T14:00:44-05:00 Compacting GC: Handle black holes in large objects. As #14497 showed black holes can appear inside large objects when we capture a computation and later blackhole it like we do for AP_STACK closures. Fixes #24791 - - - - - 291388e1 by Cheng Shao at 2024-11-25T14:01:19-05:00 ci: minor nix-in-docker improvements This patch makes some minor improvements re nix-in-docker logic in the ci configuration: - Update `nixos/nix` to the latest version - Apply $CPUS to `cores`/`max-jobs` to avoid oversubscribing while allowing a reasonable degree of parallelism - Remove redundant `--extra-experimental-features nix-command` in later `nix shell` invocations, it's already configured in `/etc/nix/nix.conf` - - - - - e684c406 by Cheng Shao at 2024-11-25T14:01:57-05:00 ci: avoid depending on stack job for test-bootstrap jobs This patch makes test-bootstrap related ci jobs only depend on hadrian-ghc-in-ghci job to finish, consistent with other jobs in the full-build stage generated by gen_ci.hs. This allows the jobs to be spawned earlier and improve overall pipeline parallelism. - - - - - caaf5388 by Simon Hengel at 2024-11-25T14:02:41-05:00 Refactoring: Remove `pSupportedExts` from `ParserOpts` This is never used for lexing / parsing. It is only used by `GHC.Parser.Header.getOptions`. - - - - - 41f8365c by Arnaud Spiwack at 2024-11-25T14:03:23-05:00 Add test for #25515 - - - - - 9279619f by Arnaud Spiwack at 2024-11-25T14:03:23-05:00 Desugar record notation with correct multiplicities Simply uses the multiplicity as stored in the field. As I'm writing this commit, the only possible multiplicity is 1, but !13525 is changing this. It's actually easier to take !13525 into account. Fixes #25515. - - - - - fcc3ae6e by Andreas Klebinger at 2024-11-26T08:24:58-05:00 Clarify INLINE unfolding optimization docs. Fixes #24660 - - - - - 88c4fe1d by Cheng Shao at 2024-11-26T08:25:34-05:00 rts: remove -Wl,-U,___darwin_check_fd_set_overflow hack This patch bumps macOS minimum SDK version to 11.0 for x86_64-darwin to align it with aarch64-darwin. This allows us to get rid of the horrible -Wl,-U,___darwin_check_fd_set_overflow hack, which is causing linker warnings and testsuite failures on macOS 15. Fixes #25504. - - - - - 53f978c0 by doyougnu at 2024-11-26T16:07:26-05:00 ghc-experimental: expose GHC.RTS.Flags, GHC.Stats See this CLC proposal: - https://github.com/haskell/core-libraries-committee/issues/289 and this CLC proposal for background: - https://github.com/haskell/core-libraries-committee/issues/288 Metric Decrease: MultiLayerModulesTH_OneShot - - - - - e70d4140 by Wang Xin at 2024-11-26T16:08:10-05:00 Add -mcmodel=medium moduleflag to generated LLVM IR on LoongArch platform With the Medium code model, the jump range of the generated jump instruction is larger than that of the Small code model. It's a temporary fix of the problem descriped in https://gitlab.haskell .org/ghc/ghc/-/issues/25495. This commit requires that the LLVM used contains the code of commit 9dd1d451d9719aa91b3bdd59c0c6679 83e1baf05, i.e., version 8.0 and later. Actually we should not rely on LLVM, so the only way to solve this problem is to implement the LoongArch backend. Add new type for codemodel - - - - - df42ba16 by Andreas Klebinger at 2024-11-27T11:40:49-05:00 Cmm constant folding: Narrow results to operations bitwidth. When constant folding ensure the result is still within bounds for the given type by explicitly narrowing the results. Not doing so results in a lot of spurious assembler warnings especially when testing primops. - - - - - bf3db97e by Ben Gamari at 2024-11-27T11:41:26-05:00 ghc-toolchain: Introduce basic flag validation We verify that required flags (currently `--output` and `--triple`) are provided. The implementation is truly awful, but so is getopt. Begins to address #25500. - - - - - a104508d by Ben Gamari at 2024-11-27T11:42:03-05:00 rts: Allow ExecPage to allocate anywhere in address space Currently the ExecPage facility has two users: * GHCi, for constructing info tables, and * the adjustor allocation path Despite neither of these have any spatial locality constraints ExecPage was using the linker's `mmapAnonForLinker`, which tries hard to ensure that mappings end up nearby the executable image. This makes adjustor allocation needlessly subject to fragmentation concerns. We now instead return less constrained mappings, improving the robustness of the mechanism. Addresses #25503. - - - - - c3fc9b86 by Ben Gamari at 2024-11-27T11:42:39-05:00 base: Fix incorrect mentions of GHC.Internal.Numeric These were incorrectly changed by the automated refactoring of the `ghc-internal` migration. Fixes #25521. - - - - - a362b943 by sheaf at 2024-11-27T23:44:28-05:00 Add checkExact to toolTargets This change means that the Hadrian multi target will include exactprint. In particular, this means that HLS will work on exactprint inside the GHC tree. - - - - - e6c957e4 by Arnaud Spiwack at 2024-11-27T23:45:09-05:00 Add test for #25428 - - - - - 52d97f4e by Arnaud Spiwack at 2024-11-27T23:45:09-05:00 Don't bypass MonoLocalBind in empty patterns Fixes #25428 - - - - - 7890f2d8 by Ben Gamari at 2024-11-28T10:26:46-05:00 hadrian: Bump directory bound to >=1.3.9 Earlier versions of `directory` are racy on Windows due to #24382. Also includes necessary Hadrian bootstrap plan bump. Fixes #24382. - - - - - 0fd43ea6 by Adam Sandberg Ericsson at 2024-11-28T10:27:22-05:00 mention -Iw in +RTS -? - - - - - 6cf579b9 by Ben Gamari at 2024-11-28T10:27:59-05:00 gitlab-ci: Set GIT_SUBMODULE_FORCE_HTTPS GitLab recommends using `https://` to clone submodules and provides the `GIT_SUBMODULE_FORCE_HTTPS` variable to force this. Fixes #25528. - - - - - 5b4774f9 by sheaf at 2024-12-03T15:22:07+01:00 Remove TcRnDeprecatedInvisTyArgInConPat mechanism The combination of ScopedTypeVariables + TypeApplications now no longer enables the use of type applications in constructor patterns, as per GHC proposal #448. This completes the deprecation that begun with GHC 9.8. We also remove the -Wdeprecated-type-abstractions flag, which was introduced in GHC 9.10. - - - - - f813c8d7 by sheaf at 2024-12-03T17:10:15-05:00 Hadrian: use / when making filepaths absolute In Hadrian, we are careful to use -/- rather than </>, in order to use / instead of \ in filepaths. However, this gets ruined by the use of makeAbsolute from System.Directory, which, on Windows, changes back forward slashes to backslashes. - - - - - 292ed74e by Ben Gamari at 2024-12-03T17:10:52-05:00 rts/linker: Fix out-of-bounds mapping logic Previously the structure of `mmapInRegion` concealed a subtle bug concerning handling of `mmap` returning mappings below the beginning of the desired region. Specifically, we would reset `p = result + bytes` and then again reset `p = region->start` before looping around for another iteration. This resulted in an infinite loop on FreeBSD. Fixes #25492. - - - - - 20912f5b by Ben Gamari at 2024-12-03T17:10:52-05:00 rts/linker: Clarify debug output - - - - - f98b3ac0 by Simon Hengel at 2024-12-03T17:11:30-05:00 SysTools: Avoid race conditions when processing output (fixes #16450) - - - - - 03851b64 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 mg: Drop unnecessary HasCallStack This HasCallStack was a debugging artifact from a previous commit. - - - - - 01d213b5 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 Improve haddock of graphReachabilityCyclic - - - - - f7cbffe2 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 Refactor ModuleGraph interface The 'ModuleGraph' abstraction represents the relationship and strucutre of the modules being compiled. This structure is meant to be constructed once at the start of compilation, and never changed again. However, it's exposed interface was confusing and exposed too many footguns which led to inneficient usages of the ModuleGraph. This commit improves significantly the exported interface of ModuleGraph, taking into consideration the recent improvements around reachability queries. Since the ModuleGraph graphs and related structures (HPT, EPS) are performance critical in the sense that somewhat simple mistakes can cause bad leaks and non-linear memory usage, we want to have proper APIs that guide efficient usage. This is a good step in that direction. - - - - - b69a7f3c by David Binder at 2024-12-04T18:37:42-05:00 Use consistent capitalization for "GHC Proposal" in user guide - - - - - 18d9500d by David Binder at 2024-12-04T18:37:42-05:00 Fix reference to GHC proposal 193 in user guide - - - - - dd959406 by Ben Gamari at 2024-12-04T18:38:18-05:00 Revert "rts/Interpreter: Assert that TEST*_P discriminators are valid" This assertion was based on the misconception that `GET_TAG` was returning the pointer tag whereas it is actually returning the constructor tag. This reverts commit 9bf3663b9970851e7b5701d68147450272823197. Fixes #25527. - - - - - cad6fede by Ben Gamari at 2024-12-04T18:38:54-05:00 rts/IOManager: Drop dead code This assignment is dead code as it occurs after all branches have returned. Moreover, it can't possibly be relevant since the "available" branch already sets `flag`. Potentially fixes #25542. - - - - - 55d8304e by Ben Gamari at 2024-12-06T16:56:00-05:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - 56b9f484 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 336d392e by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - dd7ca939 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Mention incorrect Data.Enum addition in changelog - - - - - dfd1db48 by Ben Gamari at 2024-12-06T16:56:36-05:00 base: Reintroduce {Show,Enum} IoSubSystem These instances were dropped in !9676 but not approved by the CLC. Addresses #25549. - - - - - 090fc7c1 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements on T25240 T25240 doesn't need RTS linker, GHCi is sufficient and GHCi can also be dynamically linked. - - - - - 3fb5d399 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements for T25155 Loading C objects requires RTS linker. - - - - - 4c58bdf6 by Leary at 2024-12-07T03:42:07-05:00 TH: Add typed variants of dataToExpQ and liftData This commit introduces to template-haskell (via ghc-internal) two functions `dataToCodeQ` and `liftDataTyped`, typed variants of `dataToExpQ` and `liftData` respectively. Tested in: `dataToCodeQUnit`. - - - - - 63027593 by Serge S. Gulin at 2024-12-08T13:52:05+03:00 JS: Basic cleanup for unused stuff to simplify things. 1. Make `staticInitStat`, `staticDeclStat`, `allocUnboxedConStatic`, `allocateStaticList`, `jsStaticArg` local to modules. 2. Remove unused `hdRawStr`, `hdStrStr` from Haskell and JavaScript (`h$pstr`, `h$rstr`, `h$str`). 3. Introduce a special type `StaticAppKind` enumeration and `StaticApp` to represent boxed scalar static applications. Originally, StaticThunk supported to pass Maybe when it became Nothing for initializied thunks in an alternatie way but it is not used anymore. - - - - - a9f8f1fb by Serge S. Gulin at 2024-12-08T14:10:45+03:00 JS: Add trivial optimizations for `unpackCString` and `unpackCStringUtf8`. It became possible due of introduction strings unfloating at Sinker pass (#13185). Earns few more bytes at optimizations. - - - - - b519c06b by Serge S. Gulin at 2024-12-08T15:50:26+03:00 JS: Specialize unpackCString# CAFs (fixes #24744) Code analysis shown that such optimization would be possible out of the box if `cachedIdentForId` allowed to do that for Haskell `Id`s which are represented by few JavaScript `Ident`s. It is a usual for strings which are represented at JavaScript as a pair of 2 values: the string content and the offset where to start reading actual string from the full content. Usually offset is 0 but technically we need to allow such complex structures to be treated as "global". Enabling it there shown that `genToplevelRhs` and `globalOccs` had inaccuracies in their implementations: 1. `globalOccs` operated over JavaScript's `Ident`s but for complex structures it didn't pay attention to the fact that different Idents actually could be pointed to same Id. Now the algo is changed to calculate occurencies for Ids. 2. `genToplevelRhs` didn't assume that different Idents pointed to same Id can have mixed order of occurence. But actually the order is important. Strings are encoded into 2 variables where first is content and second is offset and their order are not interchangeable. It is fixed by regeneration Idents from collected Ids which is fine because all Idents generation is passed through the Cache and they are quasi-stable. - - - - - a8ceccf3 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Fix panic in multiline string with unterminated gap (#25530) - - - - - 9e464ad0 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Add test case for unterminated multiline string - - - - - ed1ed5c6 by Rodrigo Mesquita at 2024-12-09T16:26:19-05:00 Revert mapMG renaming We had previously renamed this function for consistency, but that caused unnecessary breakage - - - - - 158261f7 by Sylvain Henry at 2024-12-09T16:27:01-05:00 RTS: make Cabal flags manual Cabal shouldn't automatically try to set them. We set them explicitly. - - - - - a83b7ed6 by Matthew Stephenson at 2024-12-10T14:01:22-05:00 Add missing @since documentation for (!?) function - - - - - e745e3a3 by Ben Gamari at 2024-12-10T14:01:59-05:00 compiler: Don't attempt to TSAN-instrument SIMD operations TSAN only provides instrumentation for 8, 16, 32, and 64-bit memory loads/stores. Don't attempt to instrument wider operations. Fixes #25563. - - - - - 684c0018 by Ben Gamari at 2024-12-10T14:02:35-05:00 gitlab/ci: Don't clobber RUNTEST_ARGS Previously the logic handling `IGNORE_PERF_FAILURES` clobbered the user's `RUNTEST_ARGS`. Fix this. - - - - - 41dae5b8 by Ben Gamari at 2024-12-10T14:03:11-05:00 hadrian: Mitigate mktexfmt race At least some versions of Texlive's `mktexfmt` utility cannot be invoked concurrently in their initial run since they fail to handle failure of `mkdir` due to racing. Specifically, we see ``` | Run Xelatex: users_guide.tex => /tmp/extra-dir-9616886274866 | Run Xelatex: Haddock.tex => /tmp/extra-dir-9616886274869 This is XeTeX, Version 3.14159265-2.6-0.999992 (TeX Live 2020) (preloaded format=xelatex) restricted \write18 enabled. kpathsea: Running mktexfmt xelatex.fmt mktexfmt: mktexfmt is using the following fmtutil.cnf files (in precedence order): mktexfmt: /usr/share/texlive/texmf-dist/web2c/fmtutil.cnf mktexfmt: mktexfmt is using the following fmtutil.cnf file for writing changes: mktexfmt: /builds/ghc/ghc/tmp-home/.texlive2020/texmf-config/web2c/fmtutil.cnf /usr/bin/mktexfmt: mkdir(/builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c/) failed for tree /builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c: File exists at /usr/share/texlive/tlpkg/TeXLive/TLUtils.pm line 937. I can't find the format file `xelatex.fmt'! ``` That is two `mktexfmt` invocations (for the user's guide and haddock builds) attempted to create `$HOME/texlive2020/texmf-var/web2c` and raced. One of the two `mkdir`'s consequently failed, bringing down the entire build. We avoid this by ensuring that the first `xelatex` invocation is always performed serially. Fixes #25564. - - - - - 9efbc51f by Ben Gamari at 2024-12-10T14:03:48-05:00 rts/CheckUnload: Reset old_objects if unload is skipped Previously `checkUnload` failed to reset `old_objects` when it decided not to unload (e.g. due to heap profiling being enabled). Fixes #24935. - - - - - 5192a75f by Ben Gamari at 2024-12-11T04:28:11-05:00 rts: Annotate BCOs with their Name This introduces a new bytecode instruction, `BCO_NAME`, to aid in debugging bytecode execution. This instruction is injected by `mkProtoBCO` and captures the Haskell name of the BCO. It is then printed by the disassembler, allowing ready correlation with STG dumps. - - - - - 99225996 by Ben Gamari at 2024-12-11T04:28:48-05:00 configure: Implement ld override whitelist Bring `configure` into alignment with `ghc-toolchain`, ensuring that the ld-override logic will only take effect on Linux and Windows. Fixes #25501. - - - - - 4a8fc928 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Unmark T14028 as broken on FreeBSD This now appears to pass on FreeBSD 14. Closes #19723. - - - - - d7c0eb5a by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Migrate FreeBSD runner tag to FreeBSD 14 - - - - - 7246dacc by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Reintroduce FreeBSD 14 job - - - - - 4af936da by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Allow use of newer cabal-install bindists Newer cabal-install bindists have internal directory structure. Here we detect and account for the presence of such structure. - - - - - cbf38c1b by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Enable documentation build on FreeBSD 14 - - - - - d68107fb by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Use system libffi on FreeBSD - - - - - fea3b590 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark linker_unload as broken on FreeeBSD Due to #25491. - - - - - ccf171ee by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Prefer system toolchain on FreeBSD It's not uncommon to find machines with gcc installed via ports. We should be using the system's default clang-based toolchain instead. - - - - - cfb34738 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T21969 as broken on FreeBSD Due to #25512. - - - - - 0b64e37c by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark RestartEventLogging as broken on FreeBSD I am seeing this fail quite reproducibly. Due to #19724. - - - - - 3b412019 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T16180 as "broken" on FreeBSD Sadly we in fact need to skip it as it merely times out during compilation. See #14012. - - - - - 57e3cab5 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Skip T16992 unless in slow speed This test has extraordinary memory requirements and tests a rather niche aspect of the compact region mechanism. It has been suggested multiple times that we shouldn't run it in the default testsuite configuration. Finally implement this. See #21890. See #21892. - - - - - f08a72eb by Ben Gamari at 2024-12-11T19:30:54-05:00 rts(setNumCapabilities): Assert that n_caps < MAX_N_CAPS It was noticed in #25560 that this would previously be allowed, resulting in a segfault. I will add a proper exception in `base` in a future commit. - - - - - e10d31ad by Ben Gamari at 2024-12-11T19:30:55-05:00 ghc-internal: Fix inconsistent FFI import types The foreign imports of `enabled_capabilities` and `getNumberOfProcessors` were declared as `CInt` whereas they are defined as `uint32_t`. - - - - - 06265655 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Mention maximum capability count in users guide Addresses #25560. - - - - - d488470b by Ben Gamari at 2024-12-11T19:30:55-05:00 rts/Capability: Move induction variable declaration into `for`s Just a stylistic change. - - - - - 71f050b7 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Determine max_n_capabilities at RTS startup Previously the maximum number of capabilities supported by the RTS was statically capped at 256. However, this bound is uncomfortably low given the size of today's machine. While supporting unbounded, fully-dynamic adjustment would be nice, it is complex and so instead we do something simpler: Probe the logical core count at RTS startup and use this as the static bound for the rest of our execution. This should avoid users running into the capability limit on large machines while avoiding wasting memory on a large capabilities array for most users and keeping complexity at bay. Addresses #25560. - - - - - 1e84b411 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Introduce req_c_rts As suggested by @hsyl20, this is intended to mark tests that rely on the behavior of the C RTS. - - - - - 683115a4 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Add test for #25560 - - - - - ef2052a8 by Ben Gamari at 2024-12-12T04:42:32-05:00 testsuite: Only run T14497_compact in normal way This test targets the compacting GC so it makes little sense to run it across all ways. Moreover, it outright conflicts with the `nonmoving` way. - - - - - 34d3e8e6 by Ben Gamari at 2024-12-12T04:43:08-05:00 rts/CheckUnload: Don't prepare to unload if we can't unload Previously `prepareUnloadCheck` would move the `objects` list to `old_objects` even when profiling (where we cannot unload). This caused us to vacate the `objects` list during major GCs, losing track of loaded objects. Fix this by ensuring that `prepareUnloadCheck` and `checkUnload` both use the same short-cutting logic. - - - - - 9c53489d by Andrei Borzenkov at 2024-12-12T15:06:42-05:00 Update GHCi :info type declaration printing (#24459) - Do not print result's kind in type families because we have full kind in SAKS and we display invisible arity using @-binders - Do not suppress significant invisible binders An invisible binder is considered significant when it meets at least one of the following two criteria: - It visibly occurs in the declaration's body - It is followed by a significant binder, so it affects positioning For non-generative type declarations (type synonyms and type families) there is one additional criterion: - It is not followed by a visible binder, so it affects the arity of a type synonym See Note [Print invisible binders in interface declarations] for more information about what is "visibly occurs" - - - - - 13fe48d4 by Matthew Pickering at 2024-12-12T15:07:19-05:00 typechecker: Perform type family consistency checks in topological order Consider a module M importing modules A, B and C. We can waste a lot of work depending on the order that the modules are checked for family consistency. Consider that C imports A and B. When compiling C we must have already checked A and B for consistency, therefore if C is processed first then A and B will not need to be checked for consistency again. If A and B are compared first, then the consistency checks will be performed against (wasted as we already performed them for C). At the moment the order which modules are checked is non-deterministic. Clearly we should engineer that C is checked before B and A, but by what scheme? A simple one is to observe that if a module M is in the transitive closure of X then the size of the consistent family set of M is less than or equal to size of the consistent family set of X. Therefore by sorting the imports by the size of the consistent family set and processing the largest first, you make sure to process modules in topological order. In practice we have observed that this strategy has reduced the amount of consistency checks performed. One solution to #25554 - - - - - 62a2b25f by Sylvain Henry at 2024-12-14T04:31:09-05:00 TNTC: set CmmProc entry_label properly (#25565) Before this patch we were renaming the entry label of a CmmProc late in the CmmToAsm pass. It led to inconsistencies and to some labels being used in info tables but not being emitted (#25565). Now we set the CmmProc entry label earlier in the StgToCmm monad and we don't renamed it afterwards. - - - - - b339e7c3 by Simon Hengel at 2024-12-14T04:31:47-05:00 Make filter functionality for system tools line-based This is more efficient as: - All existing filter functions were line-based anyway. They broke up the input into lines and then joined it back together. - We already break up the output from system tools into lines when processing it. Splitting up the output of system tools once and then filtering and processing it reduces both code and runtime complexity. - - - - - 39669077 by Simon Hengel at 2024-12-14T04:31:47-05:00 Refactoring: Don't use a `Chan` when parsing SysTools output - - - - - 64756530 by Simon Peyton Jones at 2024-12-14T22:28:04-05:00 Tidy up the handling of `assert` Fixes #25493 - - - - - 8658fbc1 by Rodrigo Mesquita at 2024-12-14T22:28:41-05:00 base: displayException for SomeAsyncException Provide a better implementation of `SomeException` for `SomeAsyncException`. The previous, implicit, implementation, would not use the `displayException` of the exception wrapped by `SomeAsyncException`. Implements CLC-Proposal#309 Closes #25513 - - - - - 2d3a0a70 by ARATA Mizuki at 2024-12-15T18:35:30-05:00 LLVM: When emitting a vector literal with ppTypeLit, include the type information Fixes #25561 - - - - - bfacc086 by Simon Peyton Jones at 2024-12-15T18:36:05-05:00 Fix signature lookup in instance declarations This fixes a bug introduced by the fix to #16610 - - - - - 80f0e02d by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Improve GHC build times Two small changes * In GHC.Data.Unboxed, never omit interface pragmas. In "fast builds" one might omit them generally, but doing so gives very bad performance for code that imports this module. * In GHC.Hs.Dump don't do type-class specialisation. For some reason it goes mad and generates vast amounts of useless code. See #25463. - - - - - 175a1355 by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Refactor Lint Refactor Lint for two reasons: * To improve performance * To prepare for type-lets The big changes are all in GHC.Core.Lint: * Change the main APIs: * `lintType` returns nothing rather than returning a `LintedType`; * `lintCoercion` return nothing rather than returning a `LintedCoercion` Reason: these functions did a lot of allocation to return a substituted type/coercion that was often discarded, or used only to extract its kind. Instead we now return nothing, and, when needed, extract the kind and substitute. * Applications are treated as a whole, by `lintApp`. By treating multiple arguments all at once we avoid performing multiple substitutions, each substituting a single type variable. This can make an absolutely huge difference. Overall this led to a pretty massive rewrite of Lint, with many smaller changes. Smaller chnages elsewhere * Rename `GHC.Core.TyCo.Subst.getSubstInScope` to `substInScopeSet` for consistency * Define and use `GHC.Core.Type.liftedTypeOrConstraintKind` Performance. This MR someimtes gives gives a very large improvement in compile time, when Lint is on. here is a selection of changes over 5% in perf/compiler (with -dcore-lint) T25196 -97.0% T14766 -89.7% T14683 -74.4% T5631 -60.9% T20261 -56.7% T18923 -17.6% T13035 -15.8% T6048 -15.8% CoOpt_Read -14.4% T9630 -10.9% T5642 -7.3% Eliminating the egregious offenders is a big win. However, in some cases the compiler allocation /increases/. Here ae the changes over 1%: T9961 1.5% T8095 2.8% T14052 3.9% T12545 4.5% T14052Type 5.5% T5030 8.0% T5321Fun 8.3% T3064 12.7% CoOpt_Singletons 15.6% T9198 16.0% LargeRecord 18.1% I looked at the two biggest increases in compile-time bytes allocated. Interestingly, they both show substantial *decreases* in actual compile time, due to much smaller GC times. I'm honestly not sure either why the allocation increases, or why the GC time decreases; but I'm going to take the win! T9198 Baseline With patch No Lint Alloc 44.6M 44.6M Mut time 0.23s 0.22s GC time 0.21s 0.21s With Lint Alloc 309M 360M Mut time 1.51s 0.85s GC time 2.97s 0.25s ------------------- LargeRecord Baseline With patch No Lint Alloc 1.37G 1.37G Mut time 2.33s 2.33s GC time 2.40s 2.42s With Lint Alloc 3.4G 4.0G Mut time 6.02s 5.68s GC time 3.67s 3.03s IMPORTANT NOTE: These changes don't show up in CI because in CI the tests in perf/compiler are all run with -dcore-lint switched off. I gathered this data with some manual runs. - - - - - 8ef2dad6 by Simon Peyton Jones at 2024-12-17T02:48:09-05:00 Add Note [Typechecking overloaded literals] See #25494. - - - - - e86b1b20 by Ben Gamari at 2024-12-17T13:51:39-05:00 testsuite: Use math.inf instead of division-by-zero This both more directly captures the intent and also fixes #25580. - - - - - 430d965a by Ben Gamari at 2024-12-17T13:52:15-05:00 rts: Fix incorrect format specifiers in era profiling Fixes #25581. - - - - - 267098ad by Andreas Klebinger at 2024-12-18T23:43:13-05:00 Document `-prof` and non `-prof` code being incompatible. Fixes #25518. - - - - - 04433916 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: output metadata fragment in CI (cherry picked from commit 52b58a660e735b20961d792d8fa9267f01247a50) - - - - - 7c78804e by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metatdata: use fedora33 for redhat Redhat 9 doesn't have libtinfo.so.5 anymore (cherry picked from commit dc86785eb43afd1bd292287c064fb5ad94fe8c7f) - - - - - 1d72cfb2 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: still use centos for redhat <9 - - - - - 3f7ebc58 by Sylvain Henry at 2024-12-19T20:40:14-05:00 Merge ghc-bignum into ghc-internal (#24453) First step towards merging ghc-bignum and ghc-prim into ghc-internal. After this patch, ghc-bignum is deprecated and is just a shallow package reexporting modules from ghc-internal and base. Use those directly instead. Move `gmp` submodule into ghc-internal directory. - - - - - ee0150c2 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Improve performance of deriving Show Significantly improves performance of deriving Show instances by avoiding using the very polymorphic `.` operator in favour of inlining its definition. We were generating tons of applications of it, each which had 3 type arguments! Improves on #9557 ------------------------- Metric Decrease: InstanceMatching T12707 T3294 ------------------------ - - - - - 8b266671 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Don't eta expand cons when deriving Data This eta expansion was introduced with the initial commit for Linear types. I believe this isn't needed any longer. My guess is it is an artifact from the initial linear types implementation: data constructors are linear, but they shouldn't need to be eta expanded to be used as higher order functions. I suppose in the early days this wasn't true. For instance, this works now: data T x = T x f = \(x :: forall y. y -> T y) -> x True f T -- ok! T is linear, but can be passed where an unrestricted higher order function is expected. I recall there being some magic around to make this work for data constructors... Since this works, there's no need to eta_expand the data constructors in the derived Data instances. - - - - - 1f67ad21 by Andrei Borzenkov at 2024-12-25T01:42:31-05:00 Flip the order of arguments of setField (#24668) GHC Proposal 583 "HasField redesign" specifies the following order of a setField function arguments as this: setField :: forall fld a b. SetField fld a b. b -> a -> a This patch flips the application order to match the spec. - - - - - 3e0c948d by Ben Gamari at 2024-12-25T01:43:08-05:00 rel-eng/upload: Add set_symlink mode This slightly eases updating of the `latest` symlinks. - - - - - 63d63f9d by Simon Peyton Jones at 2024-12-25T01:43:45-05:00 Preserve orientation when unifying kinds This MR fixes yet another manifestation of the trickiness caused by Note [Fundeps with instances, and equality orientation]. I wish there was a more robust way to do this, but this fix is a definite improvement. Fixes #25597 - - - - - 94ba9a6a by ARATA Mizuki at 2024-12-26T10:47:57-05:00 x86 NCG SIMD: Support pack/insert/broadcast/unpack of 128-bit integer vectors - - - - - 6bf0d587 by Andrew Lelechenko at 2024-12-26T10:48:33-05:00 docs: fix haddock formatting in Control.Monad.Fix - - - - - feb14af1 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Remove unnecessary irrefutable patterns from NonEmpty functions Implementation of https://github.com/haskell/core-libraries-committee/issues/107 - - - - - 6a0d91b4 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Make cons, Semigroup, IsList, and Monad instances stricter - - - - - 1249e597 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Restore some laziness in <| and Semigroup instance, improve Monad instance The Monad instance shouldn't produce the outer :| unless f a reduces to WHNF. (Notice that the b :| bs match is implicitly lazy.) - - - - - 8699d826 by Sergey Vinokurov at 2024-12-27T15:12:30+00:00 Add comment outlining Data.List.NonEmpty implementation guiding principles - - - - - 7febe00e by Sergey Vinokurov at 2024-12-27T22:24:43+00:00 Fix tests since location of ‘>>=’ changed - - - - - a928c326 by ARATA Mizuki at 2024-12-28T03:06:14-05:00 Fix LLVM version detection With a recent LLVM, `llc -version` emits the version on the first line if the vendor is set. It emits the version on the second line otherwise. Therefore, we need to check the both lines to detect the version. GHC now emits a warning if it fails to detect the LLVM version, so we can notice if the output of `llc -version` changes in the future. Also, the warning for using LLVM < 10 on s390x is removed, because we assume LLVM >= 13 now. This fixes the definition of __GLASGOW_HASKELL_LLVM__ macro. Fixes #25606 - - - - - 7f79257a by Zubin Duggal at 2024-12-29T13:04:35+00:00 Bump base, ghc-prim and template-haskell versions for 9.12 Also bump various submodules. (cherry picked from commit 6fc1fa3bdc8f53acdb19e47145789274060e498f) Bump base bound to 4.21 for GHC 9.12 (cherry picked from commit 473a201c6b55aea5bf9c9db0836a66ea1b657e04) Bump binary submodule to 0.8.9.2 (cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20) (cherry picked from commit ec2f40b45c1a3d82d17a2fc07e9ddb9218bc3940) Bump exceptions submodule to 0.10.9 (cherry picked from commit f5b5d1dc2d326368e5b173d622630d77f019b629) Bump file-io submodule to 0.1.4 (cherry picked from commit ba786681de6ac5fa49938e2cd71a5988f0f40d1f) bump os-string submodule to 2.0.6 (cherry picked from commit 3a7ffdbb832c045a55fd1ef24f546abdd9d9e30f) bump transformers submodule to 0.6.1.2 (cherry picked from commit 53b46fd437421b9e5a001edc6d1c427439d7714f) Bump directory submodule to v1.3.9.0 (cherry picked from commit 27dc2664c5404bb462092bb216c2c37b418fd1f8) Bump Win32 submodule to v2.14.1.0 (cherry picked from commit 80df88086180f5e39212b2feacf70a9d2b263c6c) Bump filepath submodule to 1.5.3.0 (cherry picked from commit 29bfae2c58a7303a081a6e7956b9f55e5faf3eeb) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 97b0dff223a6c4cc003adec448104c277f214645) Bump unix submodule to 2.8.6.0 (cherry picked from commit a1f56d6d6a99c100f88ef0a8b4d51298cf24a42d) Bump os-string submodule to 2.0.8 (cherry picked from commit 0121b76fd52ea0c0ce5d07085bc195666b63c625) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 962ceb50c8a6fc370e1c0a267f5cd5562a8cf759) Bump filepath submodule to 1.5.4.0 (cherry picked from commit 7bc6877fd5d41c6d5900678ad5e73ed30f366569) Bump file-io submodule to 0.1.5 (cherry picked from commit 9478b5aefe2877d58baf527edcf936dddbb955b7) Bump Cabal submodule to 3.14.1.0 (cherry picked from commit 5c9c3e3f79a79bb6d9a77a17c716dc3a0bcbd2aa) Bump directory submodule to 0.12.2.0 (cherry picked from commit 897906265db37af34ae2aaa016cec417f263407b) Bump array submodule for base bump Bump stm submodule for base bump Bump process submodule for base bump - - - - - f6079408 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix ghc-e005 after HasCallstack changes (cherry picked from commit 77f340a24561cea8a6f2ada296b3ea356ab1823c) - - - - - 3e10fa75 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Add haskeline to stage0Packages Otherwise we link against boot inplace and boot unix as boot haskeline depends on boot unix. (cherry picked from commit 90b493769ebdf3cd7be404d18462dc20ac1044df) - - - - - 4ad6aec4 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix TH changelog - - - - - ea3f7fd5 by Zubin Duggal at 2024-12-29T13:04:35+00:00 release: copy index.html from correct directory (cherry picked from commit cbfd0829cd61928976c9eb17ba4af18272466063) - - - - - fafb70db by Zubin Duggal at 2024-12-29T13:04:35+00:00 hadrian-multi: warn on unused imports os-string has redundant imports (cherry picked from commit dde3796be689ea57543936e22aa5ea4ef7ed995e) - - - - - c02b1e46 by Simon Peyton Jones at 2024-12-29T17:04:30-05:00 Fix in-scope set for CSE Ticket #25468 showed an assertion failure in CSE because a top-level Id was being used before it was defined. Reason: Note [Glomming] in GHC.Core.Opt.OccurAnal. Solution (used in many places): just put all the top-level bindings in scope at the beginning of CSE. Compile-time allocation wobbles up and down a tiny bit; geo mean is zero. But MultiLayerModulesTH_OneShot and hard_hole_fits increase (on some architectures only) by a bit oever 2% . I think these are just a random fluctuations. Metric Increase: MultiLayerModulesTH_OneShot hard_hole_fits - - - - - 559d4f84 by Krzysztof Gogolewski at 2024-12-30T11:53:19-05:00 Add tests for #23883 The issue has been fixed by commit f5d3e03c56ffc63. Only T23883a is the actual regression test, the remaining ones are tricky cases found during development of an independent fix !11313. - - - - - 278a53ee by Sergey Vinokurov at 2024-12-30T11:53:59-05:00 Update changelog for CLC proposal #107 (NonEmpty laziness) - - - - - f56558be by Matthew Pickering at 2025-01-07T13:53:03-05:00 warnings: Find out if a qualified name is in the interactive scope directly There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600 - - - - - 84155cdb by Simon Peyton Jones at 2025-01-07T13:53:40-05:00 Tidy up kcConDecls Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types - - - - - 6c12b6cf by Bryan Richter at 2025-01-07T18:15:02-05:00 Remove tmp files after toolchain check Fixes #25620 - - - - - 42826a89 by Cheng Shao at 2025-01-07T18:15:39-05:00 xxhash: bump to v0.8.3 - - - - - 185f17e4 by sheaf at 2025-01-07T18:16:15-05:00 Fix typo in GHC.Tc.Solver.Solve.runTcPluginsWanted - - - - - 23099752 by Luite Stegeman at 2025-01-08T00:33:33+01:00 Add flags for switching off speculative evaluation. We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284 - - - - - 0161badc by Ben Gamari at 2025-01-09T17:30:05-05:00 rts/printClosure: Print IPE information for thunks and functions This makes it considerably easier to grok the structure of the heap when IPE information is available. - - - - - 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz Goślinowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 66b808ce by Ben Gamari at 2025-03-10T16:07:52-04:00 Kill IOPort# This type is unnecessary, having been superceded by `MVar` and a rework of WinIO's blocking logic. See #20947. See https://github.com/haskell/core-libraries-committee/issues/213. - - - - - 1911 changed files: - .gitattributes - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/hello.hs - .gitlab/jobs.yaml - .gitlab/merge_request_templates/Default.md - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload.sh - .gitlab/rel_eng/upload_ghc_libs.py - .gitmodules - compile_flags.txt - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - + compiler/GHC/Data/Graph/Directed/Internal.hs - + compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/Unboxed.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Config/CoreToStg/Prep.hs - compiler/GHC/Driver/Config/Linker.hs - compiler/GHC/Driver/Config/Parser.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Phases.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Coverage.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Config.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Llvm/Ppr.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Hpc.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/CodeGen.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Monad.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/StgToJS/Symbols.hs - compiler/GHC/StgToJS/Types.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Finder/Types.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Info.hs - compiler/GHC/Unit/Module/Env.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/Location.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/Module/Warnings.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Panic/Plain.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/cbits/genSym.c - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/debug-info.rst - docs/users_guide/debugging.rst - docs/users_guide/diagnostics-as-json-schema-1_0.json - + docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/expected-undocumented-flags.txt - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/equality_constraints.rst - docs/users_guide/exts/multiline_strings.rst - docs/users_guide/exts/overloaded_record_update.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/exts/primitives.rst - docs/users_guide/exts/rewrite_rules.rst - docs/users_guide/exts/stolen_syntax.rst - docs/users_guide/exts/strict.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/exts/type_abstractions.rst - docs/users_guide/ghci.rst - docs/users_guide/packages.rst - docs/users_guide/phases.rst - docs/users_guide/profiling.rst - docs/users_guide/release-notes.rst - docs/users_guide/runtime_control.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using-warnings.rst - docs/users_guide/using.rst - docs/users_guide/wasm.rst - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/bindist/Makefile - hadrian/bindist/config.mk.in - hadrian/bootstrap/plan-9_10_1.json - hadrian/bootstrap/plan-9_6_1.json - hadrian/bootstrap/plan-9_6_2.json - hadrian/bootstrap/plan-9_6_3.json - hadrian/bootstrap/plan-9_6_4.json - hadrian/bootstrap/plan-9_6_5.json - hadrian/bootstrap/plan-9_6_6.json - hadrian/bootstrap/plan-9_8_1.json - hadrian/bootstrap/plan-9_8_2.json - hadrian/bootstrap/plan-bootstrap-9_10_1.json - hadrian/bootstrap/plan-bootstrap-9_6_1.json - hadrian/bootstrap/plan-bootstrap-9_6_2.json - hadrian/bootstrap/plan-bootstrap-9_6_3.json - hadrian/bootstrap/plan-bootstrap-9_6_4.json - hadrian/bootstrap/plan-bootstrap-9_6_5.json - hadrian/bootstrap/plan-bootstrap-9_6_6.json - hadrian/bootstrap/plan-bootstrap-9_8_1.json - hadrian/bootstrap/plan-bootstrap-9_8_2.json - hadrian/cabal.project - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/doc/user-settings.md - hadrian/hadrian.cabal - hadrian/src/CommandLine.hs - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/src/Rules/ToolArgs.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Warnings.hs - hadrian/stack.yaml - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/array - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Control/Exception.hs - libraries/base/src/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Char.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/Data/Semigroup.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Exception.hs - libraries/base/src/GHC/Exts.hs - − libraries/base/src/GHC/IOPort.hs - + libraries/base/src/GHC/Num/BigNat.hs - + libraries/base/src/GHC/Num/Integer.hs - + libraries/base/src/GHC/Num/Natural.hs - libraries/base/src/Prelude.hs - libraries/base/src/System/Timeout.hs - libraries/base/tests/IO/T21336/T21336a.stderr - libraries/base/tests/IO/T21336/T21336b.stderr - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/all.T - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/openFile002.stderr-mingw32 - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withBinaryFile002.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFile002.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/IO/withFileBlocking002.stderr - libraries/base/tests/T15349.stderr - libraries/base/tests/T16111.stderr - libraries/base/tests/T19288.stderr - libraries/base/tests/T24807.stderr - libraries/base/tests/all.T - libraries/base/tests/assert.stderr - libraries/base/tests/readFloat.stderr - − libraries/base/tests/topHandler04.hs - − libraries/base/tests/topHandler04.stderr - libraries/base/tests/unicode002.stdout - libraries/base/tests/unicode003.hs - libraries/base/tests/unicode003.stdout - libraries/binary - libraries/bytestring - libraries/deepseq - libraries/directory - libraries/exceptions - libraries/file-io - libraries/filepath - − libraries/ghc-bignum/.gitignore - + libraries/ghc-bignum/Dummy.hs - − libraries/ghc-bignum/Setup.hs - − libraries/ghc-bignum/aclocal.m4 - libraries/ghc-bignum/changelog.md - − libraries/ghc-bignum/config.mk.in - − libraries/ghc-bignum/configure.ac - − libraries/ghc-bignum/ghc-bignum.buildinfo.in - libraries/ghc-bignum/ghc-bignum.cabal - − libraries/ghc-bignum/install-sh - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-compact/tests/all.T - libraries/ghc-compact/tests/compact_function.stderr - libraries/ghc-compact/tests/compact_mutable.stderr - libraries/ghc-compact/tests/compact_pinned.stderr - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-experimental/src/Data/Sum/Experimental.hs - libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - + libraries/ghc-experimental/src/GHC/RTS/Flags/Experimental.hs - + libraries/ghc-experimental/src/GHC/Stats/Experimental.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/stack_big_ret.hs - libraries/ghc-internal/.gitignore - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/aclocal.m4 - libraries/ghc-bignum/README.rst → libraries/ghc-internal/bignum-backend.rst - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-bignum/cbits/gmp_wrappers.c → libraries/ghc-internal/cbits/gmp_wrappers.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/ghc-internal/configure.ac - libraries/ghc-internal/ghc-internal.buildinfo.in - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-bignum/GMP.rst → libraries/ghc-internal/gmp-backend.rst - libraries/ghc-bignum/gmp/ghc-gmp.h → libraries/ghc-internal/gmp/ghc-gmp.h - libraries/ghc-bignum/gmp/gmp-tarballs → libraries/ghc-internal/gmp/gmp-tarballs - libraries/ghc-bignum/include/HsIntegerGmp.h.in → libraries/ghc-internal/include/HsIntegerGmp.h.in - libraries/ghc-bignum/include/WordSize.h → libraries/ghc-internal/include/WordSize.h - libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-bignum/src/GHC/Num/Backend.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Check.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - libraries/ghc-bignum/src/GHC/Num/Backend/FFI.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Native.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Selected.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Selected.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - libraries/ghc-bignum/src/GHC/Num/Integer.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-bignum/src/GHC/Num/Integer.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - libraries/ghc-bignum/src/GHC/Num/Natural.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-bignum/src/GHC/Num/Natural.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - libraries/ghc-bignum/src/GHC/Num/Primitives.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-bignum/src/GHC/Num/WordArray.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - libraries/ghc-internal/src/GHC/Internal/Char.hs - libraries/ghc-prim/GHC/Classes.hs → libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - libraries/ghc-internal/src/GHC/Internal/Err.hs - libraries/ghc-internal/src/GHC/Internal/Event.hs - libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Float/ConversionUtils.hs - libraries/ghc-internal/src/GHC/Internal/Float/RealFracMethods.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/Types.hs - libraries/ghc-internal/src/GHC/Internal/Generics.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/Buffer.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/SubSystem.hs - libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc - − libraries/ghc-internal/src/GHC/Internal/IOPort.hs - libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Int.hs - libraries/ghc-internal/src/GHC/Internal/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - libraries/ghc-internal/src/GHC/Internal/IsList.hs - libraries/ghc-internal/src/GHC/Internal/Ix.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - libraries/ghc-internal/src/GHC/Internal/Maybe.hs - libraries/ghc-internal/src/GHC/Internal/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs-boot - libraries/ghc-internal/src/GHC/Internal/Numeric/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-prim/GHC/Prim/Exception.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Read.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - libraries/ghc-internal/src/GHC/Internal/Records.hs - libraries/ghc-internal/src/GHC/Internal/Show.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs-boot - − libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hs-boot - libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - libraries/ghc-prim/GHC/Tuple.hs → libraries/ghc-internal/src/GHC/Internal/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats/Internal.hs - libraries/ghc-prim/GHC/Types.hs → libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghc-internal/src/GHC/Internal/Word.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/unicode_version - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/integer-gmp/integer-gmp.cabal - libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs - libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - libraries/template-haskell/tests/all.T - + libraries/template-haskell/tests/dataToCodeQUnit.hs - + libraries/template-haskell/tests/dataToCodeQUnit.stdout - libraries/terminfo - libraries/text - libraries/transformers - libraries/unix - linters/lint-codes/LintCodes/Static.hs - linters/lint-codes/Main.hs - m4/find_ld.m4 - m4/fp_settings.m4 - m4/fptools_happy.m4 - m4/ghc_toolchain.m4 - rts/Capability.c - rts/Capability.h - rts/CheckUnload.c - rts/Disassembler.c - rts/Exception.cmm - rts/ExecPage.c - rts/IOManager.c - rts/IPE.c - rts/Interpreter.c - rts/Interpreter.h - rts/Linker.c - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/ProfHeap.c - rts/RtsFlags.c - rts/RtsMain.c - rts/RtsSymbols.c - rts/Schedule.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStdThunks.cmm - rts/Task.h - rts/adjustor/NativeAmd64Asm.S - rts/adjustor/NativeAmd64MingwAsm.S - rts/adjustor/Nativei386.c - rts/adjustor/Nativei386Asm.S - rts/configure.ac - rts/external-symbols.list.in - rts/include/RtsAPI.h - rts/include/Stg.h - rts/include/rts/Bytecodes.h - rts/include/rts/Config.h - rts/include/rts/IPE.h - rts/include/rts/Threads.h - rts/include/rts/storage/HeapAlloc.h - rts/include/rts/storage/InfoTables.h - rts/include/stg/MiscClosures.h - rts/include/stg/Prim.h - rts/include/stg/SMP.h - rts/js/environment.js - rts/js/mem.js - rts/js/string.js - rts/js/verify.js - rts/linker/MMap.c - rts/linker/MMap.h - rts/linker/MachO.c - rts/posix/ticker/TimerFd.c - rts/rts.cabal - rts/sm/Compact.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GCThread.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - rts/wasm/scheduler.cmm - rts/win32/AsyncWinIO.c - rts/win32/libHSghc-internal.def - rts/win32/libHSghc-prim.def - rts/xxhash.h - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/all.T - testsuite/tests/annotations/should_fail/annfail12.stderr - testsuite/tests/arityanal/should_run/T21694a.stderr - testsuite/tests/arityanal/should_run/T24296.stderr - testsuite/tests/array/should_run/arr003.stderr - testsuite/tests/array/should_run/arr004.stderr - testsuite/tests/array/should_run/arr007.stderr - testsuite/tests/array/should_run/arr008.stderr - testsuite/tests/arrows/should_compile/T21301.stderr - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - testsuite/tests/backpack/should_run/bkprun05.stderr - testsuite/tests/bytecode/T24634/Makefile - + testsuite/tests/bytecode/T25510/Makefile - + testsuite/tests/bytecode/T25510/T25510A.hs - + testsuite/tests/bytecode/T25510/T25510B.hs - + testsuite/tests/bytecode/T25510/all.T - + testsuite/tests/cmm/opt/T24556.cmm - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - testsuite/tests/codeGen/should_compile/T25166.stdout - testsuite/tests/codeGen/should_run/T16846.stderr - testsuite/tests/codeGen/should_run/T23146/all.T - testsuite/tests/codeGen/should_run/T25364.hs - testsuite/tests/codeGen/should_run/T25364.stdout - testsuite/tests/codeGen/should_run/T5626.stderr - testsuite/tests/codeGen/should_run/T7319.stderr - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/codeGen/should_run/cgrun016.stderr - testsuite/tests/codeGen/should_run/cgrun025.stderr - testsuite/tests/codeGen/should_run/cgrun045.stderr - testsuite/tests/codeGen/should_run/cgrun051.stderr - testsuite/tests/codeGen/should_run/cgrun059.stderr - testsuite/tests/concurrent/should_run/T13330.stderr - testsuite/tests/concurrent/should_run/T4030.stderr - testsuite/tests/concurrent/should_run/T5611.stderr - testsuite/tests/concurrent/should_run/T5611a.stderr - testsuite/tests/concurrent/should_run/T5866.stderr - testsuite/tests/concurrent/should_run/all.T - testsuite/tests/concurrent/should_run/allocLimit1.stderr - testsuite/tests/concurrent/should_run/allocLimit3.stderr - testsuite/tests/concurrent/should_run/conc009.stderr - testsuite/tests/concurrent/should_run/conc020.stderr - testsuite/tests/concurrent/should_run/conc021.stderr - testsuite/tests/concurrent/should_run/conc031.stderr - testsuite/tests/concurrent/should_run/conc040.stderr - testsuite/tests/concurrent/should_run/conc058.stderr - testsuite/tests/concurrent/should_run/conc064.stderr - testsuite/tests/concurrent/should_run/conc068.stderr - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - + testsuite/tests/core-to-stg/T25284/A.hs - + testsuite/tests/core-to-stg/T25284/B.hs - + testsuite/tests/core-to-stg/T25284/Cls.hs - + testsuite/tests/core-to-stg/T25284/Main.hs - + testsuite/tests/core-to-stg/T25284/T25284.stdout - + testsuite/tests/core-to-stg/T25284/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/deSugar/should_fail/DsStrictFail.stderr - testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr - testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr - testsuite/tests/deSugar/should_run/Or5.stderr - testsuite/tests/deSugar/should_run/T11193.stderr - testsuite/tests/deSugar/should_run/T11572.stderr - testsuite/tests/deSugar/should_run/T11601.stderr - testsuite/tests/deSugar/should_run/T20024.stderr - testsuite/tests/deSugar/should_run/dsrun005.stderr - testsuite/tests/deSugar/should_run/dsrun007.stderr - testsuite/tests/deSugar/should_run/dsrun008.stderr - testsuite/tests/default/DefaultImportFail01.stderr - testsuite/tests/default/DefaultImportFail02.stderr - testsuite/tests/default/DefaultImportFail03.stderr - testsuite/tests/default/DefaultImportFail04.stderr - testsuite/tests/default/DefaultImportFail05.stderr - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail07.stderr - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/deriving/should_run/T9576.stderr - testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/dmdanal/should_run/T12368.stderr - testsuite/tests/dmdanal/should_run/T12368a.stderr - testsuite/tests/dmdanal/should_run/T13380.stderr - testsuite/tests/dmdanal/should_run/T13380d.stderr - testsuite/tests/dmdanal/should_run/T13380e.stderr - testsuite/tests/dmdanal/should_run/T23208.stderr - testsuite/tests/dmdanal/should_run/strun002.stderr - testsuite/tests/driver/Makefile - testsuite/tests/driver/T13914/T13914.stdout - testsuite/tests/driver/T20604/T20604.stdout - + testsuite/tests/driver/T25382.hs - testsuite/tests/driver/all.T - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/json.stderr - testsuite/tests/driver/json_warn.hs - testsuite/tests/driver/json_warn.stderr - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits_callstack.stderr - testsuite/tests/driver/recomp24656/recomp24656.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/exceptions/T25052.stdout - testsuite/tests/ffi/should_run/T7170.stderr - testsuite/tests/ffi/should_run/ffi008.stderr - testsuite/tests/ffi/should_run/fptrfail01.stderr - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/ghc-api/T10942.hs - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/T20757.stderr - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-api/exactprint/all.T - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail7.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - testsuite/tests/ghc-e/should_fail/T23663.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghc-e/should_fail/T9930fail.stderr - testsuite/tests/ghc-e/should_run/ghc-e005.stderr - testsuite/tests/ghci.debugger/scripts/break006.stderr - testsuite/tests/ghci.debugger/scripts/break009.stdout - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break017.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - testsuite/tests/ghci/linking/T25240/all.T - testsuite/tests/ghci/linking/all.T - testsuite/tests/ghci/scripts/Defer02.stderr - testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10501.stderr - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T15325.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T19310.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T21294a.stdout - testsuite/tests/ghci/scripts/T23686.stderr - + testsuite/tests/ghci/scripts/T24459.script - + testsuite/tests/ghci/scripts/T24459.stdout - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T5557.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci055.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_run/GHCiPrimCall/Makefile - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/hpc/function/tough.stdout - testsuite/tests/hpc/function2/tough2.stdout - testsuite/tests/hpc/simple/tixs/T10529a.stderr - testsuite/tests/hpc/simple/tixs/T10529b.stderr - testsuite/tests/hpc/simple/tixs/T10529c.stderr - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/T11361a.stderr - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs → testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12522a.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/javascript/Makefile - testsuite/tests/javascript/T23479_1.hs → testsuite/tests/javascript/T23479.hs - testsuite/tests/javascript/T23479_1.stdout → testsuite/tests/javascript/T23479.stdout - testsuite/tests/javascript/T23479_2.hs → testsuite/tests/javascript/T24744.hs - testsuite/tests/javascript/T23479_2.stdout → testsuite/tests/javascript/T24744.stdout - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/lib/integer/T20066.stderr - + testsuite/tests/linear/should_compile/T25428.hs - + testsuite/tests/linear/should_compile/T25515.hs - testsuite/tests/linear/should_compile/all.T - testsuite/tests/linear/should_fail/LinearConfusedDollar.stderr - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLet10.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/linear/should_fail/T25185.hs - + testsuite/tests/linear/should_fail/T25185.stderr - testsuite/tests/linear/should_fail/all.T - + testsuite/tests/llvm/should_compile/T25606.hs - testsuite/tests/llvm/should_compile/all.T - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/mdo/should_fail/mdofail006.stderr - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19892.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.hs - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - + testsuite/tests/parser/should_fail/T25530.hs - + testsuite/tests/parser/should_fail/T25530.stderr - testsuite/tests/parser/should_fail/all.T - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - testsuite/tests/parser/should_run/RecordDotSyntax1.hs - + testsuite/tests/parser/should_run/T25375.hs - + testsuite/tests/parser/should_run/T25375.stdout - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/patsyn/should_run/ghci.stderr - testsuite/tests/perf/compiler/MultiLayerModulesTH_Make.stderr - testsuite/tests/perf/compiler/MultiLayerModulesTH_OneShot.stderr - testsuite/tests/perf/compiler/T11068.stdout - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/perf/size/all.T - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/all.T - testsuite/tests/primops/should_run/T10481.stderr - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - testsuite/tests/primops/should_run/UnliftedIOPort.hs - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/profiling/should_run/ioprof.prof.sample - testsuite/tests/profiling/should_run/toplevel_scc_1.prof.sample - testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quasiquotation/all.T - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/T18263.stderr - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_localname.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TTH_top_splice.stderr - testsuite/tests/rebindable/RebindableFailA.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/Or3.hs - testsuite/tests/rename/should_fail/Or3.stderr - testsuite/tests/rename/should_fail/T12686a.stderr - testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T22478b.hs - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23740i.stderr - + testsuite/tests/rename/should_fail/T25437.hs - + testsuite/tests/rename/should_fail/T25437.stderr - testsuite/tests/rename/should_fail/T5001b.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyMcGuard.stderr - testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T12709.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/T23153.stderr - + testsuite/tests/rep-poly/T23153b.hs - testsuite/tests/rep-poly/T23154.stderr - + testsuite/tests/rep-poly/T23883a.hs - + testsuite/tests/rep-poly/T23883a.stderr - + testsuite/tests/rep-poly/T23883b.hs - + testsuite/tests/rep-poly/T23883b.stderr - + testsuite/tests/rep-poly/T23883c.hs - + testsuite/tests/rep-poly/T23883c.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rep-poly/all.T - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T13832.stderr - + testsuite/tests/rts/T14497-compact.hs - + testsuite/tests/rts/T14497-compact.stdout - testsuite/tests/rts/T1791/Makefile - + testsuite/tests/rts/T20201a.hs - + testsuite/tests/rts/T20201a.stderr - + testsuite/tests/rts/T20201b.hs - + testsuite/tests/rts/T20201b.stderr - + testsuite/tests/rts/T25560.hs - testsuite/tests/rts/T2783.stderr - testsuite/tests/rts/T7087.stderr - testsuite/tests/rts/T7636.stderr - testsuite/tests/rts/all.T - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/continuations/cont_missing_prompt_err.stderr - testsuite/tests/rts/ipe/IpeStats/Makefile - testsuite/tests/rts/ipe/T24005/t24005.hs - testsuite/tests/rts/linker/all.T - testsuite/tests/runghc/T7859.stderr - testsuite/tests/runghc/T7859.stderr-mingw32 - testsuite/tests/safeHaskell/check/pkg01/all.T - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang09.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/Orphans.stdout - + testsuite/tests/simd/should_run/T25455.hs - + testsuite/tests/simd/should_run/T25455.stdout - + testsuite/tests/simd/should_run/T25486.hs - + testsuite/tests/simd/should_run/T25486.stdout - + testsuite/tests/simd/should_run/T25561.hs - + testsuite/tests/simd/should_run/T25561.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/int16x8_basic.hs - + testsuite/tests/simd/should_run/int16x8_basic.stdout - + testsuite/tests/simd/should_run/int16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/int16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/int32x4_basic.hs - + testsuite/tests/simd/should_run/int32x4_basic.stdout - + testsuite/tests/simd/should_run/int32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/int32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/int64x2_basic.hs - + testsuite/tests/simd/should_run/int64x2_basic.stdout - + testsuite/tests/simd/should_run/int64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/int64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/int8x16_basic.hs - + testsuite/tests/simd/should_run/int8x16_basic.stdout - + testsuite/tests/simd/should_run/int8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/int8x16_basic_baseline.stdout - + testsuite/tests/simd/should_run/simd_insert.hs - + testsuite/tests/simd/should_run/simd_insert.stdout - + testsuite/tests/simd/should_run/simd_insert_array.hs - + testsuite/tests/simd/should_run/simd_insert_array.stdout - + testsuite/tests/simd/should_run/simd_insert_array_baseline.hs - + testsuite/tests/simd/should_run/simd_insert_array_baseline.stdout - + testsuite/tests/simd/should_run/simd_insert_baseline.hs - + testsuite/tests/simd/should_run/simd_insert_baseline.stdout - + testsuite/tests/simd/should_run/word16x8_basic.hs - + testsuite/tests/simd/should_run/word16x8_basic.stdout - + testsuite/tests/simd/should_run/word16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/word16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/word32x4_basic.hs - + testsuite/tests/simd/should_run/word32x4_basic.stdout - + testsuite/tests/simd/should_run/word32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/word32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/word64x2_basic.hs - + testsuite/tests/simd/should_run/word64x2_basic.stdout - + testsuite/tests/simd/should_run/word64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/word64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/word8x16_basic.hs - + testsuite/tests/simd/should_run/word8x16_basic.stdout - + testsuite/tests/simd/should_run/word8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/word8x16_basic_baseline.stdout - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T21286.stderr - testsuite/tests/simplCore/should_compile/T21851_2.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T22428.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplCore/should_fail/T7411.stderr - testsuite/tests/simplCore/should_run/T16066.stderr - testsuite/tests/simplCore/should_run/T16893/T16893.stderr - testsuite/tests/simplCore/should_run/T457.stderr - testsuite/tests/simplCore/should_run/T5587.stderr - testsuite/tests/simplCore/should_run/T5625.stderr - testsuite/tests/simplCore/should_run/T7924.stderr - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10279.hs - testsuite/tests/th/T10279.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10796b.stderr - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15360b.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T16980.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23927.stdout - testsuite/tests/th/T24111.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T5976.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T8987.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_exn2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - + testsuite/tests/th/wasm/T25473A.hs - + testsuite/tests/th/wasm/T25473B.hs - + testsuite/tests/th/wasm/all.T - testsuite/tests/type-data/should_run/T22332a.stderr - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClasses.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesCore.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesEffects.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesReader.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesState.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadPrimitive.hs - + testsuite/tests/typecheck/should_compile/T16234/DataPeano.hs - + testsuite/tests/typecheck/should_compile/T16234/Main.hs - + testsuite/tests/typecheck/should_compile/T16234/Makefile - + testsuite/tests/typecheck/should_compile/T16234/all.T - testsuite/tests/typecheck/should_compile/T17343.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.stderr - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25597.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T15883d.stderr - testsuite/tests/typecheck/should_fail/T15883e.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20443b.hs - testsuite/tests/typecheck/should_fail/T20443b.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - testsuite/tests/typecheck/should_fail/T22478c.hs - testsuite/tests/typecheck/should_fail/T22478c.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_fail/T23734.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T23778.stderr - testsuite/tests/typecheck/should_fail/T24298.stderr - testsuite/tests/typecheck/should_fail/T24553.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T7279.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_ExistentialEscape.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearMultiAppPat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearMultiPat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearSinglePat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearSinglePat.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_Nonmatching.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBinding.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.hs - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail1.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_run/T10284.stderr - testsuite/tests/typecheck/should_run/T11049.stderr - testsuite/tests/typecheck/should_run/T11715.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T21973a.stderr - testsuite/tests/typecheck/should_run/T22510.stdout - testsuite/tests/typecheck/should_run/T9497a-run.stderr - testsuite/tests/typecheck/should_run/T9497b-run.stderr - testsuite/tests/typecheck/should_run/T9497c-run.stderr - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/UnlGadt1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - testsuite/tests/unsatisfiable/T23816.stderr - testsuite/tests/unsatisfiable/UnsatDefer.stderr - testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - testsuite/tests/vdq-rta/should_compile/T23739_th_pprint1.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/T24396.stderr - testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - testsuite/tests/wcompat-warnings/Template.hs - testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Parsers.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/Instances.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - utils/hsc2hs - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/18eb9eb3a1bc478908756dc66106c9c40519fd3d...66b808cea65ee7865a99e0a64430dba52d859d32 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/18eb9eb3a1bc478908756dc66106c9c40519fd3d...66b808cea65ee7865a99e0a64430dba52d859d32 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/61457241/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 20:29:59 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 10 Mar 2025 16:29:59 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: wasm: do not use wasm type reflection in dyld Message-ID: <67cf4bc7ae04e_2ddb52c5d006219b@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 2e5ffe73 by Ben Gamari at 2025-03-10T16:29:40-04:00 users guide: Fix typo - - - - - 18536e15 by Ben Gamari at 2025-03-10T16:29:40-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 2befa653 by Matthew Pickering at 2025-03-10T16:29:41-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - 15 changed files: - compiler/GHC/Data/Maybe.hs - compiler/GHC/Utils/Panic.hs - docs/users_guide/using-concurrent.rst - docs/users_guide/wasm.rst - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/tests/jsffi/jsffigc.hs - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs Changes: ===================================== compiler/GHC/Data/Maybe.hs ===================================== @@ -34,6 +34,8 @@ import Control.Exception (SomeException(..)) import Data.Maybe import Data.Foldable ( foldlM, for_ ) import GHC.Utils.Misc (HasCallStack) +import GHC.Utils.Panic +import GHC.Utils.Outputable import Data.List.NonEmpty ( NonEmpty ) import Control.Applicative( Alternative( (<|>) ) ) @@ -72,7 +74,7 @@ expectJust :: HasCallStack => Maybe a -> a expectJust = fromMaybe expectJustError expectJustError :: HasCallStack => a -expectJustError = error "expectJust" +expectJustError = pprPanic "expectJust" empty {-# NOINLINE expectJustError #-} whenIsJust :: Monad m => Maybe a -> (a -> m ()) -> m () ===================================== compiler/GHC/Utils/Panic.hs ===================================== @@ -188,7 +188,7 @@ handleGhcException = MC.handle -- | Throw an exception saying "bug in GHC" with a callstack pprPanic :: HasCallStack => String -> SDoc -> a -pprPanic s doc = panicDoc s (doc $$ callStackDoc) +pprPanic s doc = withFrozenCallStack $ panicDoc s (doc $$ callStackDoc) -- | Throw an exception saying "bug in GHC" panicDoc :: String -> SDoc -> a ===================================== docs/users_guide/using-concurrent.rst ===================================== @@ -157,7 +157,7 @@ use the RTS :rts-flag:`-N ⟨x⟩` options. .. note:: The maximum number of capabilities supported by the GHC runtime system is - determined when at RTS startup to be either 256, the value given by + determined at RTS startup to be either 256, the value given by :rts-flag:`-N ⟨x⟩`, or the number of logical CPU cores, whichever is greater. ===================================== docs/users_guide/wasm.rst ===================================== @@ -189,9 +189,9 @@ use of ``freeJSVal`` when you’re sure about a ``JSVal``\ ’s lifetime, especially for the temporary ``JSVal``\ s. This will help reducing the memory footprint at runtime. -Note that ``freeJSVal`` is not idempotent and it’s only safe to call it -exactly once or not at all. Once it’s called, any subsequent usage of -that ``JSVal`` results in a runtime panic. +Note that ``freeJSVal`` is idempotent and it’s safe to call it more +than once. After it’s called, any subsequent usage of that ``JSVal`` +by passing to the JavaScript side results in a runtime panic. .. _wasm-jsffi-import: @@ -390,7 +390,7 @@ callback and intends to call it later, so the Haskell function closure is still retained by default. Still, the runtime can gradually drop these retainers by using -``FinalizerRegistry`` to invoke the finalizers to free the underlying +``FinalizationRegistry`` to invoke the finalizers to free the underlying stable pointers once the JavaScript callbacks are recycled. One last corner case is cyclic reference between the two heaps: if a ===================================== libraries/ghc-experimental/src/GHC/Wasm/Prim.hs ===================================== @@ -1,22 +1,21 @@ {-# LANGUAGE NoImplicitPrelude #-} module GHC.Wasm.Prim ( - -- User-facing JSVal type and freeJSVal + -- * User-facing 'JSVal' and related utilities JSVal, freeJSVal, mkWeakJSVal, - -- The JSString type and conversion from/to Haskell String + -- * 'JSString' and conversion from/to Haskell 'String' JSString (..), fromJSString, toJSString, - -- Exception types related to JSFFI + -- * Exception types related to JSFFI JSException (..), WouldBlockException (..), - PromisePendingException (..), - -- Is JSFFI used in the current wasm module? + -- * Is JSFFI used in the current wasm module? isJSFFIUsed ) where ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs ===================================== @@ -1,22 +1,21 @@ {-# LANGUAGE NoImplicitPrelude #-} module GHC.Internal.Wasm.Prim ( - -- User-facing JSVal type and freeJSVal + -- * User-facing 'JSVal' and related utilities JSVal (..), freeJSVal, mkWeakJSVal, - -- The JSString type and conversion from/to Haskell String + -- * 'JSString' and conversion from/to Haskell 'String' JSString (..), fromJSString, toJSString, - -- Exception types related to JSFFI + -- * Exception types related to JSFFI JSException (..), WouldBlockException (..), - PromisePendingException (..), - -- Is JSFFI used in the current wasm module? + -- * Is JSFFI used in the current wasm module? isJSFFIUsed ) where ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs ===================================== @@ -43,10 +43,14 @@ import GHC.Internal.Word mkJSCallback :: (StablePtr a -> IO JSVal) -> a -> IO JSVal mkJSCallback adjustor f = do sp@(StablePtr sp#) <- newStablePtr f - JSVal v w _ <- adjustor sp - let r = JSVal v w sp# - js_callback_register r sp - pure r + v@(JSVal p) <- adjustor sp + IO $ \s0 -> case stg_setJSVALsp p sp# s0 of + (# s1 #) -> (# s1, () #) + js_callback_register v sp + pure v + +foreign import prim "stg_setJSVALsp" + stg_setJSVALsp :: JSVal# -> StablePtr# a -> State# RealWorld -> (# State# RealWorld #) foreign import javascript unsafe "__ghc_wasm_jsffi_finalization_registry.register($1, $2, $1)" js_callback_register :: JSVal -> StablePtr a -> IO () ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs ===================================== @@ -7,4 +7,8 @@ where import GHC.Internal.Base +-- | If the current wasm module has any JSFFI functionality linked in, +-- this would be 'True' at runtime and 'False' otherwise. If this is +-- 'False', the wasm module would be a self-contained wasm32-wasi +-- module that can be run by non-web runtimes as well. foreign import ccall unsafe "rts_JSFFI_used" isJSFFIUsed :: Bool ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -1,7 +1,9 @@ {-# LANGUAGE GHC2021 #-} +{-# LANGUAGE GHCForeignImportPrim #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE UnliftedFFITypes #-} {-# LANGUAGE UnliftedNewtypes #-} module GHC.Internal.Wasm.Prim.Types ( @@ -26,7 +28,6 @@ import GHC.Internal.IO import GHC.Internal.IO.Encoding import GHC.Internal.Num import GHC.Internal.Show -import GHC.Internal.Stable import GHC.Internal.Weak {- @@ -38,76 +39,150 @@ On wasm, the Haskell heap lives in the linear memory space, and it can only contain bit patterns, not opaque references of the host JavaScript heap. As long as we have two heaps that coexist in this way, the best we can do is representing JavaScript references as -unique ids in the Haskell heap. - -In JavaScript, we have a JSValManager which exposes some interfaces as -wasm imports. The JSValManager is in charge of allocating unique ids -and managing the mapping from ids to the actual JavaScript values. In -fact we can implement the entire JSValManager in wasm, using a wasm -table with externref elements to hold the JavaScript values and a -special allocator to manage free slots in the table. That'll take more -work to implement though, with one more caveat: browsers typically -limit max wasm table size to 10000000 which may not be large enough -for some use cases. We can workaround the table size restriction by -managing a pool or tree of wasm tables, but at this point we really -should ditch the idea of doing everything in wasm just because we can. - -Next, we have the unlifted JSVal# type, defined in jsval.cmm and -contains one non-pointer word which is the id allocated by -JSValManager. On top of JSVal#, we have the user-facing lifted JSVal -type, which carries the JSVal#, as well as a weak pointer and a stable -pointer. - -The weak pointer is used to garbage collect JSVals. Its key is the -JSVal# closure, and it has a C finalizer that tells the JSValManager -to drop the mapping when the JSVal# closure is collected. Since we -want to provide freeJSVal to allow eager freeing of JSVals, we need to -carry it as a field of JSVal. - -The stable pointer field is NULL for normal JSVals created via foreign -import results or foreign export arguments. But for JSFFI dynamic -exports that wraps a Haskell function closure as a JavaScript callback -and returns that callback's JSVal, it is a stable pointer that pins -that Haskell function closure. If this JSVal is garbage collected, -then we can only rely on a JavaScript FinalizerRegistry to free the -stable pointer in the future, but if we eagerly free the callback with -freeJSVal, then we can eagerly free this stable pointer as well. - -The lifted JSVal type is meant to be an abstract type. Its creation -and consumption is mainly handled by the RTS API functions rts_mkJSVal -and rts_getJSVal, which are used in C stub files generated when -desugaring JSFFI foreign imports/exports. +ids in the Haskell heap. + +First, we have the unlifted JSVal# type, defined in jsval.cmm with the +following memory layout: + ++--------------+-----+----+----------+ +|stg_JSVAL_info|Weak#|Int#|StablePtr#| ++--------------+-----+----+----------+ + +The first non-pointer Int# field is a 32-bit id allocated and +returned by the JSValManager on the JavaScript side. The JSValManager +maintains a Map from ids to actual JavaScript values. This field is +immutable throughout a JSVal# closure's lifetime and is unique for +each JSVal# ever created. + +The Weak# poiner sets the JSVal# closure as key and has a C finalizer +that drops the mapping in JSValManager. When the JSVal# closure is +garbage collected, the finalizer is invoked, but it can also be +eagerly invoked by freeJSVal, that's why we carry the Weak# in JSVal# +as a pointer field. + +Normally, one JSVal# manage one kind of resource: the JavaScript value +retained in JSValManager. However, in case of JSFFI exports where we +convert Haskell functions to JavaScript callbacks, the JSVal# manages +not only the callback on the JavaScript side, but also a stable +pointer that pins the exported function on the Haskell side. That +StablePtr# is recorded in the JSVal# closure. + +Even if the JSVal# closure is garbage collected, we don't know if the +JavaScript side still retains the callback somewhere other than +JSValManager, so the stable pointer will continue to pin the Haskell +function closure. We do a best effort cleanup on the JavaScript side +by using a FinalizationRegistry: if the JSVal# is automatically +collected, the callback is dropped in JSValManager and also not used +elsewhere, the FinalizationRegistry calls into the RTS to drop the +stable pointer as well. + +However, JSVal# can be eagerly freed by freeJSVal. It'll deregister +the callback in the FinalizationRegistry, finalize the Weak# pointer +and also free the stable pointer. In order to make freeJSVal +idempotent, we must not free the stable pointer twice; therefore the +StablePtr# field is mutable and will be overwritten with NULL upon +first freeJSVal invocation; it's also NULL upon creation by +rts_mkJSVal and later overwritten with the StablePtr# upon the +callback creation. + +On top of JSVal#, we have the user-facing lifted JSVal type, which +wraps the JSVal#. The lifted JSVal type is meant to be an abstract +type. Its creation and consumption is mainly handled by the RTS API +functions rts_mkJSVal and rts_getJSVal, which are used in C stub files +generated when desugaring JSFFI foreign imports/exports. -} newtype JSVal# = JSVal# (Any :: UnliftedType) +-- | A 'JSVal' is a first-class Haskell value on the Haskell heap that +-- represents a JavaScript value. You can use 'JSVal' or its @newtype@ +-- as a supported argument or result type in JSFFI import & export +-- declarations, in addition to those lifted FFI types like 'Int' or +-- 'Ptr' that's already supported by C FFI. It is garbage collected by +-- the GHC RTS: +-- +-- * There can be different 'JSVal's that point to the same JavaScript +-- value. As long as there's at least one 'JSVal' still alive on the +-- Haskell heap, that JavaScript value will still be alive on the +-- JavaScript heap. +-- * If there's no longer any live 'JSVal' that points to the +-- JavaScript value, after Haskell garbage collection, the +-- JavaScript runtime will be able to eventually garbage collect +-- that JavaScript value as well. +-- +-- There's a special kind of 'JSVal' that represents a JavaScript +-- callback exported from a Haskell function like this: +-- +-- > foreign import javascript "wrapper" +-- > exportFibAsAsyncJSCallback :: (Int -> Int) -> IO JSVal +-- +-- Such a 'JSVal' manages an additional kind of resource: the exported +-- Haskell function closure. Even if it is automatically garbage +-- collected, the Haskell function closure would still be retained +-- since the JavaScript callback might be retained elsewhere. We do a +-- best-effort collection here using JavaScript +-- [@FinalizationRegistry@](https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/FinalizationRegistry), +-- so the Haskell function closure might be eventually dropped if the +-- JavaScript callback is garbage collected. +-- +-- Note that even the @FinalizationRegistry@ logic can't break cyclic +-- references between the Haskell/JavaScript heap: when an exported +-- Haskell function closure retains a 'JSVal' that represents a +-- JavaScript callback. Though this can be solved by explicit +-- 'freeJSVal' calls. data JSVal - = forall a . JSVal JSVal# (Weak# JSVal) (StablePtr# a) + = JSVal JSVal# +-- | 'freeJSVal' eagerly frees a 'JSVal' in the runtime. It drops the +-- retained JavaScript value on the JavaScript side, and in case of a +-- 'JSVal' that represents a callback, also drops the retained Haskell +-- function closure. Once a 'JSVal' is freed by 'freeJSVal', later +-- attempts to pass it to the JavaScript side would result in runtime +-- crashes, so you should only call 'freeJSVal' when you're confident +-- that 'JSVal' won't be used again (and in case of callbacks, that +-- callback won't be invoked again). +-- +-- 'freeJSVal' is idempotent: it's safe to call it more than once on +-- the same 'JSVal', subsequent invocations are no-ops. You are +-- strongly recommended to call 'freeJSVal' on short-lived +-- intermediate 'JSVal' values for timely release of resources! freeJSVal :: JSVal -> IO () -freeJSVal v@(JSVal _ w sp) = do - case sp `eqStablePtr#` unsafeCoerce# nullAddr# of - 0# -> do - js_callback_unregister v - freeStablePtr $ StablePtr sp - _ -> pure () - IO $ \s0 -> case finalizeWeak# w s0 of +freeJSVal v@(JSVal p) = do + js_callback_unregister v + IO $ \s0 -> case stg_freeJSVal# p s0 of (# s1, _, _ #) -> (# s1, () #) +-- | 'mkWeakJSVal' allows you to create a 'Weak' pointer that observes +-- the liveliness of a 'JSVal' closure on the Haskell heap and +-- optionally attach a finalizer. +-- +-- Note that this liveliness is not affected by 'freeJSVal': even if +-- 'freeJSVal' is called, the 'JSVal' might still be alive on the +-- Haskell heap as a dangling reference and 'deRefWeak' might still be +-- able to retrieve the 'JSVal' before it is garbage collected. mkWeakJSVal :: JSVal -> Maybe (IO ()) -> IO (Weak JSVal) -mkWeakJSVal v@(JSVal k _ _) (Just (IO fin)) = IO $ \s0 -> - case mkWeak# k v fin s0 of +mkWeakJSVal v@(JSVal p) (Just (IO fin)) = IO $ \s0 -> + case mkWeak# p v fin s0 of (# s1, w #) -> (# s1, Weak w #) -mkWeakJSVal (JSVal _ w _) Nothing = pure $ Weak w +mkWeakJSVal v@(JSVal p) Nothing = IO $ \s0 -> + case mkWeakNoFinalizer# p v s0 of + (# s1, w #) -> (# s1, Weak w #) + +foreign import prim "stg_freeJSVAL" + stg_freeJSVal# :: JSVal# -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) -foreign import javascript unsafe "if (!__ghc_wasm_jsffi_finalization_registry.unregister($1)) { throw new WebAssembly.RuntimeError('js_callback_unregister'); }" +foreign import javascript unsafe "try { __ghc_wasm_jsffi_finalization_registry.unregister($1); } catch {}" js_callback_unregister :: JSVal -> IO () +-- | A 'JSString' represents a JavaScript string. newtype JSString = JSString JSVal +-- | Converts a 'JSString' to a Haskell 'String'. Conversion is done +-- eagerly once the resulting 'String' is forced, and the argument +-- 'JSString' may be explicitly freed if no longer used. fromJSString :: JSString -> String fromJSString s = unsafeDupablePerformIO $ do l <- js_stringLength s @@ -122,15 +197,25 @@ foreign import javascript unsafe "$1.length" foreign import javascript unsafe "(new TextEncoder()).encodeInto($1, new Uint8Array(__exports.memory.buffer, $2, $3)).written" js_encodeInto :: JSString -> Ptr a -> Int -> IO Int +-- | Converts a Haskell 'String' to a 'JSString'. toJSString :: String -> JSString toJSString s = unsafeDupablePerformIO $ withCStringLen utf8 s $ \(buf, len) -> js_toJSString buf len foreign import javascript unsafe "(new TextDecoder('utf-8', {fatal: true})).decode(new Uint8Array(__exports.memory.buffer, $1, $2))" js_toJSString :: Ptr a -> Int -> IO JSString +-- | A 'JSException' represents a JavaScript exception. It is likely +-- but not guaranteed to be an instance of the @Error@ class. When you +-- call an async JSFFI import and the result @Promise@ rejected, the +-- rejection value will be wrapped in a 'JSException' and re-thrown in +-- Haskell once you force the result. newtype JSException = JSException JSVal +-- | If the +-- [@error.stack@](https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/Error/stack) +-- property is present, it will be used to render the 'Show' instance +-- output so you can see the JavaScript stack trace. instance Show JSException where showsPrec p e = showParen (p >= 11) $ showString "JSException " . showsPrec 11 (jsErrorString e) @@ -147,6 +232,24 @@ foreign import javascript unsafe "`${$1.stack ? $1.stack : $1}`" instance Exception JSException +-- | An async JSFFI import returns a thunk that represents a pending +-- JavaScript @Promise@: +-- +-- > foreign import javascript "(await fetch($1)).text()" +-- > js_fetch :: JSString -> IO JSString +-- +-- Forcing that thunk blocks the current Haskell thread until the +-- @Promise@ is fulfilled, but that cannot happen if the Haskell +-- thread is a bound thread created by a JSFFI sync export or a C FFI +-- export! Those Haskell computations are meant to return +-- synchronously, but JavaScript asynchronocity is contagious and +-- there's no escape hatch like @unsafeAwaitPromise at . +-- +-- In such cases, a 'WouldBlockException' exception would be thrown. +-- The 'WouldBlockException' is attached with a diagnostic message +-- generated at compile-time (currently just the JSFFI source snippet +-- of the corresponding async import) to help debugging the +-- exception's cause. newtype WouldBlockException = WouldBlockException String deriving (Show) ===================================== rts/wasm/JSFFI.c ===================================== @@ -70,7 +70,7 @@ __attribute__((constructor(102))) static void __ghc_wasm_jsffi_init(void) { } typedef __externref_t HsJSVal; -typedef StgWord JSValKey; +typedef StgInt JSValKey; extern const StgInfoTable stg_JSVAL_info; extern const StgInfoTable ghczminternal_GHCziInternalziWasmziPrimziTypes_JSVal_con_info; @@ -91,9 +91,10 @@ HaskellObj rts_mkJSVal(Capability*, HsJSVal); HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { JSValKey k = __imported_newJSVal(v); - HaskellObj p = (HaskellObj)allocate(cap, CONSTR_sizeW(0, 1)); + HaskellObj p = (HaskellObj)allocate(cap, CONSTR_sizeW(1, 2)); SET_HDR(p, &stg_JSVAL_info, CCS_SYSTEM); - p->payload[0] = (HaskellObj)k; + p->payload[1] = (HaskellObj)k; + p->payload[2] = NULL; StgCFinalizerList *cfin = (StgCFinalizerList *)allocate(cap, sizeofW(StgCFinalizerList)); @@ -107,6 +108,7 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { SET_HDR(w, &stg_WEAK_info, CCS_SYSTEM); w->cfinalizers = (StgClosure *)cfin; w->key = p; + w->value = Unit_closure; w->finalizer = &stg_NO_FINALIZER_closure; w->link = cap->weak_ptr_list_hd; cap->weak_ptr_list_hd = w; @@ -114,14 +116,13 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) { cap->weak_ptr_list_tl = w; } - HaskellObj box = (HaskellObj)allocate(cap, CONSTR_sizeW(3, 0)); + p->payload[0] = (HaskellObj)w; + + HaskellObj box = (HaskellObj)allocate(cap, CONSTR_sizeW(1, 0)); SET_HDR(box, &ghczminternal_GHCziInternalziWasmziPrimziTypes_JSVal_con_info, CCS_SYSTEM); box->payload[0] = p; - box->payload[1] = (HaskellObj)w; - box->payload[2] = NULL; - w->value = TAG_CLOSURE(1, box); - return w->value; + return TAG_CLOSURE(1, box); } __attribute__((import_module("ghc_wasm_jsffi"), import_name("getJSVal"))) @@ -129,7 +130,7 @@ HsJSVal __imported_getJSVal(JSValKey); STATIC_INLINE HsJSVal rts_getJSValzh(HaskellObj p) { ASSERT(p->header.info == &stg_JSVAL_info); - return __imported_getJSVal((JSValKey)p->payload[0]); + return __imported_getJSVal((JSValKey)p->payload[1]); } HsJSVal rts_getJSVal(HaskellObj); ===================================== rts/wasm/jsval.cmm ===================================== @@ -1,10 +1,33 @@ #include "Cmm.h" -// This defines the unlifted JSVal# type. See Note [JSVal -// representation for wasm] for detailed explanation. +// This defines the unlifted JSVal# type. See +// Note [JSVal representation for wasm] for +// detailed explanation. -INFO_TABLE(stg_JSVAL, 0, 1, PRIM, "JSVAL", "JSVAL") +INFO_TABLE(stg_JSVAL, 1, 2, PRIM, "JSVAL", "JSVAL") (P_ node) { return (node); } + +stg_setJSVALsp (P_ p, W_ sp) +{ + W_[p + SIZEOF_StgHeader + WDS(2)] = sp; + return (); +} + +stg_freeJSVAL (P_ p) +{ + P_ w; + W_ sp; + + w = P_[p + SIZEOF_StgHeader]; + sp = W_[p + SIZEOF_StgHeader + WDS(2)]; + + if (sp != NULL) { + ccall freeStablePtr(sp); + W_[p + SIZEOF_StgHeader + WDS(2)] = NULL; + } + + jump stg_finalizzeWeakzh (w); +} ===================================== testsuite/driver/junit.py ===================================== @@ -19,8 +19,7 @@ def junit(t: TestRun) -> ET.ElementTree: for res_type, group in [('stat failure', t.unexpected_stat_failures), ('unexpected failure', t.unexpected_failures), ('unexpected pass', t.unexpected_passes), - ('fragile failure', t.fragile_failures), - ('fragile pass', t.fragile_passes)]: + ('fragile failure', t.fragile_failures)]: for tr in group: testcase = ET.SubElement(testsuite, 'testcase', classname = tr.way, ===================================== testsuite/tests/jsffi/jsffigc.hs ===================================== @@ -68,7 +68,7 @@ testDynExportGC x y z = do -- Return a continuation to be called after the JavaScript side -- finishes garbage collection. js_mk_cont $ do - -- The JavaScript FinalizerRegistry logic only frees the stable + -- The JavaScript FinalizationRegistry logic only frees the stable -- pointer that pins fn. So we need to invoke Haskell garbage -- collection again. performGC ===================================== utils/jsffi/dyld.mjs ===================================== @@ -1,4 +1,4 @@ -#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --experimental-wasm-type-reflection --max-old-space-size=65536 --no-turbo-fast-api-calls --wasm-lazy-validation +#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --max-old-space-size=65536 --no-turbo-fast-api-calls --wasm-lazy-validation // Note [The Wasm Dynamic Linker] // ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -231,10 +231,7 @@ class DyLD { // memory access near this address will trap immediately. // // In JS API i32 is signed, hence this layer of redirection. - static #poison = new WebAssembly.Global( - { value: "i32", mutable: false }, - 0xffffffff - DyLD.#pageSize - ).value; + static #poison = (0xffffffff - DyLD.#pageSize) | 0; // When processing exports, skip the following ones since they're // generated by wasm-ld. @@ -693,30 +690,15 @@ class DyLD { continue; } - // For lazy GOT.func entries we can do better than poison: - // insert a stub in the table, so we at least get an error - // message that includes the missing function's name, not a - // mysterious table trap. The function type is Cmm function - // type as a best effort guess, if there's a type mismatch - // then call_indirect would trap. - // - // Also set a __poison field since we can't compare value - // against DyLD.#poison. + // Can't find this function, so poison it like GOT.mem. + // TODO: when wasm type reflection is widely available in + // browsers, use the WebAssembly.Function constructor to + // dynamically create a stub function that does better error + // reporting this.#gotFunc[name] = new WebAssembly.Global( { value: "i32", mutable: true }, - this.#table.grow( - 1, - new WebAssembly.Function( - { parameters: [], results: ["i32"] }, - () => { - throw new WebAssembly.RuntimeError( - `non-existent function ${name}` - ); - } - ) - ) + DyLD.#poison ); - this.#gotFunc[name].__poison = true; continue; } @@ -754,8 +736,7 @@ class DyLD { if (this.#gotFunc[k]) { // ghc-prim/ghc-internal may export functions imported by // rts - assert(this.#gotFunc[k].__poison); - delete this.#gotFunc[k].__poison; + assert(this.#gotFunc[k].value === DyLD.#poison); this.#table.set(this.#gotFunc[k].value, v); } continue; @@ -830,7 +811,7 @@ class DyLD { if (this.#gotMem[sym] && this.#gotMem[sym].value !== DyLD.#poison) { return this.#gotMem[sym].value; } - if (this.#gotFunc[sym] && !this.#gotFunc[sym].__poison) { + if (this.#gotFunc[sym] && this.#gotFunc[sym].value !== DyLD.#poison) { return this.#gotFunc[sym].value; } // Not in GOT.func yet, create the entry on demand ===================================== utils/jsffi/prelude.mjs ===================================== @@ -3,29 +3,13 @@ // of one; the post-linker script will copy all contents into a new // ESM module. -// Manage a mapping from unique 32-bit ids to actual JavaScript -// values. +// Manage a mapping from 32-bit ids to actual JavaScript values. export class JSValManager { #lastk = 0; #kv = new Map(); - constructor() {} - - // Maybe just bump this.#lastk? For 64-bit ids that's sufficient, - // but better safe than sorry in the 32-bit case. - #allocKey() { - let k = this.#lastk; - while (true) { - if (!this.#kv.has(k)) { - this.#lastk = k; - return k; - } - k = (k + 1) | 0; - } - } - newJSVal(v) { - const k = this.#allocKey(); + const k = ++this.#lastk; this.#kv.set(k, v); return k; } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/464cda340dffdeaaf2a986f714280acdc79eba6f...2befa653b2d98858f4282a2e33da2d483375682c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/464cda340dffdeaaf2a986f714280acdc79eba6f...2befa653b2d98858f4282a2e33da2d483375682c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/110312b5/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 20:39:56 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Mon, 10 Mar 2025 16:39:56 -0400 Subject: [Git][ghc/ghc][wip/T25647] handle [Naughty quantification candidates] Message-ID: <67cf4e1cde4c2_2ddb5236568c6530@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: def98f3c by Patrick at 2025-03-11T04:39:48+08:00 handle [Naughty quantification candidates] - - - - - 3 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -3459,8 +3459,8 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty -- check there too! -- See Note [Generalising in tcTyFamInstEqnGuts] - ; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty - ; qtvs <- quantifyTyVars' outer_tvs skol_info dvs + ; (dvs, cqdvs) <- candidateQTyVarsWithBinders outer_tvs lhs_ty + ; qtvs <- quantifyTyVarsWithBinders cqdvs skol_info dvs ; let final_tvs = scopedSort qtvs -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -985,7 +985,7 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity = do { traceTc "tcDataFamInstHeader {" (ppr fam_tc <+> ppr hs_pats) ; (tclvl, wanted, (wcs, (outer_bndrs, (stupid_theta, lhs_ty, master_res_kind, instance_res_kind)))) <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $ - bindOuterFamEqnTKBndrs skol_info hs_outer_bndrs $ -- Binds skolem TcTyVars + bindOuterFamEqnTKBndrs skol_info hs_outer_bndrs $ -- Binds skolem TcTyVars or TauVars do { stupid_theta <- tcHsContext hs_ctxt ; (lhs_ty, lhs_kind) <- tcFamTyPats fam_tc hs_pats ; (lhs_applied_ty, lhs_applied_kind) @@ -1029,8 +1029,8 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity ; outer_tvs <- liftZonkM $ zonkTcTyVarsToTcTyVarsMaybe $ outer_tvs ++ wcs -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty - ; qtvs <- quantifyTyVars' outer_tvs skol_info dvs + ; (dvs, cqdvs) <- candidateQTyVarsWithBinders outer_tvs lhs_ty + ; qtvs <- quantifyTyVarsWithBinders cqdvs skol_info dvs -- Have to make a same defaulting choice for reuslt kind here -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -80,7 +80,7 @@ module GHC.Tc.Utils.TcMType ( defaultTyVar, promoteMetaTyVarTo, promoteTyVarSet, quantifyTyVars, doNotQuantifyTyVars, zonkAndSkolemise, skolemiseQuantifiedTyVar, - quantifyTyVars', + quantifyTyVarsWithBinders, candidateQTyVarsOfType, candidateQTyVarsOfKind, candidateQTyVarsOfTypes, candidateQTyVarsOfKinds, @@ -1375,6 +1375,14 @@ delCandidates (DV { dv_kvs = kvs, dv_tvs = tvs, dv_cvs = cvs }) vars , dv_tvs = tvs `delDVarSetList` vars , dv_cvs = cvs `delVarSetList` vars } +boundedCandidates :: CandidatesQTvs -> [Var] -> [Var] +boundedCandidates (DV { dv_kvs = kvs, dv_tvs = tvs, dv_cvs = _cvs }) vars + = dVarSetElems $ + (kvs `intersectDVarSet` dvars) + `unionDVarSet` (tvs `intersectDVarSet` dvars) + where dvars = extendDVarSetList emptyDVarSet vars + + partitionCandidates :: CandidatesQTvs -> (TyVar -> Bool) -> (TyVarSet, CandidatesQTvs) -- The selected TyVars are returned as a non-deterministic TyVarSet partitionCandidates dvs@(DV { dv_kvs = kvs, dv_tvs = tvs }) pred @@ -1384,20 +1392,25 @@ partitionCandidates dvs@(DV { dv_kvs = kvs, dv_tvs = tvs }) pred (extracted_tvs, rest_tvs) = partitionDVarSet pred tvs extracted = dVarSetToVarSet extracted_kvs `unionVarSet` dVarSetToVarSet extracted_tvs -candidateQTyVarsWithBinders :: [TyVar] -> Type -> TcM CandidatesQTvs +candidateQTyVarsWithBinders :: [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar]) -- (candidateQTyVarsWithBinders tvs ty) returns the candidateQTyVars -- of (forall tvs. ty), but do not treat 'tvs' as bound for the purpose -- of Note [Naughty quantification candidates]. Why? -- Because we are going to scoped-sort the quantified variables -- in among the tvs + +-- also return the bound variables that need to be quantified +-- since they can be come from implicit binders and wildcards +-- See Note [Type variables in type families instance decl] candidateQTyVarsWithBinders bound_tvs ty = do { kvs <- candidateQTyVarsOfKinds (map tyVarKind bound_tvs) ; cur_lvl <- getTcLevel ; all_tvs <- collect_cand_qtvs ty False cur_lvl emptyVarSet kvs ty - ; return (all_tvs `delCandidates` bound_tvs) } + ; return (all_tvs `delCandidates` bound_tvs, boundedCandidates all_tvs bound_tvs) } + -- | Gathers free variables to use as quantification candidates (in --- 'quantifyTyVars'). This might output the same var +-- 'quantifyTyVarsWithBinders). This might output the same var -- in both sets, if it's used in both a type and a kind. -- The variables to quantify must have a TcLevel strictly greater than -- the ambient level. (See Wrinkle in Note [Naughty quantification candidates]) @@ -1744,9 +1757,9 @@ quantifyTyVars :: SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] -- Already zonked -> TcM [TcTyVar] -quantifyTyVars = quantifyTyVars' [] +quantifyTyVars = quantifyTyVarsWithBinders [] -quantifyTyVars' :: +quantifyTyVarsWithBinders :: [TcTyVar] -> SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] @@ -1759,7 +1772,7 @@ quantifyTyVars' :: -- invariants on CandidateQTvs, we do not have to filter out variables -- free in the environment here. Just quantify unconditionally, subject -- to the restrictions in Note [quantifyTyVars]. -quantifyTyVars' cvs skol_info dvs +quantifyTyVarsWithBinders cvs skol_info dvs -- short-circuit common case | isEmptyCandidates dvs && null cvs = do { traceTc "quantifyTyVars has nothing to quantify" empty @@ -1767,7 +1780,10 @@ quantifyTyVars' cvs skol_info dvs | otherwise = do { traceTc "quantifyTyVars {" - ( vcat [ text "dvs =" <+> ppr dvs ]) + ( vcat [ + text "dvs =" <+> ppr dvs, + text "cvs =" <+> ppr cvs + ]) ; undefaulted <- defaultTyVars dvs ; final_qtvs <- liftZonkM $ mapMaybeM zonk_quant (undefaulted++cvs) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/def98f3c43922ad48d8e49b409033aa5e07b2821 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/def98f3c43922ad48d8e49b409033aa5e07b2821 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/145122ce/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 22:45:42 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 10 Mar 2025 18:45:42 -0400 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] remove special case of tcbody from tcLambdaMatches Message-ID: <67cf6b9629cb5_30624a3b54fc4155@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 4f8e1bd7 by Apoorv Ingle at 2025-03-10T17:44:52-05:00 remove special case of tcbody from tcLambdaMatches - - - - - 5 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Types/Origin.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -531,13 +531,6 @@ type instance XXExpr GhcTc = XXExprGhcTc data HsThingRn = OrigExpr (HsExpr GhcRn) -- ^ The source, user written, expression | OrigStmt (ExprLStmt GhcRn) HsDoFlavour -- ^ which kind of do-block did this statement come from -isHsThingRnExpr, isHsThingRnStmt :: HsThingRn -> Bool -isHsThingRnExpr (OrigExpr{}) = True -isHsThingRnExpr _ = False - -isHsThingRnStmt (OrigStmt{}) = True -isHsThingRnStmt _ = False - data XXExprGhcRn = ExpandedThingRn { xrn_orig :: HsThingRn -- The original source thing to be used for error messages , xrn_expanded :: HsExpr GhcRn -- The compiler generated expanded thing ===================================== compiler/GHC/HsToCore/Match.hs ===================================== @@ -1172,9 +1172,7 @@ viewLExprEq (e1,_) (e2,_) = lexp e1 e2 -- we have to compare the wrappers exp (XExpr (WrapExpr h e)) (XExpr (WrapExpr h' e')) = wrap h h' && exp e e' - exp (XExpr (ExpandedThingTc o x)) (XExpr (ExpandedThingTc o' x')) - | isHsThingRnExpr o - , isHsThingRnExpr o' + exp (XExpr (ExpandedThingTc _ x)) (XExpr (ExpandedThingTc _ x')) = exp x x' exp (HsVar _ i) (HsVar _ i') = i == i' exp (XExpr (ConLikeTc c _ _)) (XExpr (ConLikeTc c' _ _)) = c == c' ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -1252,5 +1252,4 @@ addExprCtxt e thing_inside -- when we don't want to say "In the expression: _", -- because it is mentioned in the error message itself HsUnboundVar {} -> thing_inside - XExpr (ExpandedThingRn {}) -> thing_inside _ -> addErrCtxt (ExprCtxt e) thing_inside ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -79,7 +79,7 @@ import GHC.Types.Name import GHC.Types.Name.Reader (LocalRdrEnv) import GHC.Types.Id import GHC.Types.SrcLoc -import GHC.Types.Basic( VisArity, isDoExpansionGenerated ) +import GHC.Types.Basic( VisArity ) import qualified GHC.Data.List.NonEmpty as NE @@ -155,21 +155,13 @@ tcLambdaMatches e lam_variant matches invis_pat_tys res_ty ; (wrapper, r) <- matchExpectedFunTys herald GenSigCtxt arity res_ty $ \ pat_tys rhs_ty -> - tcMatches tc_body (invis_pat_tys ++ pat_tys) rhs_ty matches + tcMatches tcBody (invis_pat_tys ++ pat_tys) rhs_ty matches ; return (wrapper, r) } where herald = ExpectedFunTyLam lam_variant e -- See Note [Herald for matchExpectedFunTys] in GHC.Tc.Utils.Unify - tc_body | isDoExpansionGenerated (mg_ext matches) - -- See Part 3. B. of Note [Expanding HsDo with XXExprGhcRn] in - -- `GHC.Tc.Gen.Do`. Testcase: Typeable1 - = tcBodyNC -- NB: Do not add any error contexts - -- It has already been done - | otherwise - = tcBody - {- @tcCaseMatches@ doesn't do the argument-count check because the parser guarantees that each equation has exactly one argument. @@ -371,12 +363,6 @@ tcBody body res_ty ; tcPolyLExpr body res_ty } -tcBodyNC :: LHsExpr GhcRn -> ExpRhoType -> TcM (LHsExpr GhcTc) -tcBodyNC body res_ty - = do { traceTc "tcBodyNC" (ppr res_ty) - ; tcMonoExprNC body res_ty - } - {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -755,8 +755,7 @@ exprCtOrigin (HsEmbTy {}) = Shouldn'tHappenOrigin "type expression" exprCtOrigin (HsForAll {}) = Shouldn'tHappenOrigin "forall telescope" -- See Note [Types in terms] exprCtOrigin (HsQual {}) = Shouldn'tHappenOrigin "constraint context" -- See Note [Types in terms] exprCtOrigin (HsFunArr {}) = Shouldn'tHappenOrigin "function arrow" -- See Note [Types in terms] -exprCtOrigin (XExpr (ExpandedThingRn thing _)) | OrigExpr a <- thing = exprCtOrigin a - | OrigStmt _ _ <- thing = DoOrigin +exprCtOrigin (XExpr (ExpandedThingRn{})) = Shouldn'tHappenOrigin "XExpr ExpandedThingRn" exprCtOrigin (XExpr (PopErrCtxt {})) = Shouldn'tHappenOrigin "PopErrCtxt" exprCtOrigin (XExpr (HsRecSelRn f)) = OccurrenceOfRecSel (foExt f) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4f8e1bd782203b0d11a25d2536103fa0c3c53395 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4f8e1bd782203b0d11a25d2536103fa0c3c53395 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/bfd536fd/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 23:35:52 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 10 Mar 2025 19:35:52 -0400 Subject: [Git][ghc/ghc][wip/T25365] 355 commits: Add regression test for #16234 Message-ID: <67cf7758ee56b_32071f17fae837743@gitlab.mail> Ben Gamari pushed to branch wip/T25365 at Glasgow Haskell Compiler / GHC Commits: fa66fa64 by Ryan Scott at 2024-11-14T19:05:00-05:00 Add regression test for #16234 Issue #16234 was likely fixed by !9765. This adds a regression test to ensure that it remains fixed. Fixes #16234. - - - - - bfe64df8 by Matthew Pickering at 2024-11-14T19:05:36-05:00 ghc-internal: Update to Unicode 16 This patch updates the automatically generated code for querying unicode properties to unicode 16. Fixes #25402 - - - - - 1fd83f86 by Ben Gamari at 2024-11-14T19:06:13-05:00 configure: Accept happy-2.1.2 happy-2.1 was released in late Oct 2024. I have confirmed that master bootstraps with it. Here we teach configure to accept this tool. Fixes #25438. - - - - - aa58fc5b by Ben Gamari at 2024-11-14T19:06:49-05:00 rts: Tighten up invariants of PACK - - - - - 8aa4c10a by Ben Gamari at 2024-11-14T19:06:49-05:00 testsuite: Fix badly escaped literals Use raw string literals to ensure that `\s` is correctly interpreted as a character class. - - - - - 0e084029 by Ben Gamari at 2024-11-14T19:06:49-05:00 rts: Improve documentation of SLIDE bytecode instruction - - - - - 9bf3663b by Ben Gamari at 2024-11-14T19:06:49-05:00 rts/Interpreter: Assert that TEST*_P discriminators are valid - - - - - 1f668511 by Ben Gamari at 2024-11-14T19:06:49-05:00 rts/Interpreter: Improve documentation of TEST*_P instructions - - - - - 59e0a770 by Cheng Shao at 2024-11-14T19:07:25-05:00 misc: improve clangd compile_flags.txt flags This patch improves the compile_flags.txt config used to power clangd for the rts C codebase. The flags in the file are sampled & deduped from a real stage1 build with clang-19 and vastly improves the IDE accuracy when hacking the rts. For maximum code coverage under the default settings, compile_flags.txt defaults to threaded+profiled+dynamic+debug way. This does not mean profdyn needs to be actually built in _build/stage1 for IDE to work. To activate IDE for other RTS ways, simply remove one of the -D flags at the end of compile_flags.txt and restart clangd. - - - - - c2c562e0 by Ben Gamari at 2024-11-14T19:08:01-05:00 testsuite: Don't consider untracked files in dirtiness check Considering trees containing untracked files as dirty is a bridge too far. The chance of an untracked file significantly affecting measured performanced metrics is quite small whereas not collecting measurements is quite inconvenient for some workflows. We now ignore untracked files in the dirtiness check. Fixes #25471. - - - - - ed2ed6c5 by Cheng Shao at 2024-11-14T19:08:37-05:00 testsuite: add regression test T25473 This commit adds regression test T25473 marked as broken due to #25473. It will be fixed in the subsequent commit. - - - - - bd0a8b7e by Cheng Shao at 2024-11-14T19:08:37-05:00 wasm: fix foreign import javascript "wrapper" in TH/ghci This patch fixes foreign import javascript "wrapper" in wasm backend's TH/ghci by fixing the handling of dyld/finalization_registry magic variables. Fixes T25473 and closes #25473. - - - - - f1b0bc32 by Ben Gamari at 2024-11-14T19:09:13-05:00 rts/linker: Make FreeBSD declarations proper prototypes The iconv declarations for FreeBSD were previously not prototypes, leading to warnings. - - - - - 086cbbc1 by Ben Gamari at 2024-11-14T19:09:13-05:00 base: Drop redundant import in FreeBSD ExecutablePath implementation - - - - - 79ecd199 by Ben Gamari at 2024-11-14T19:09:13-05:00 compiler: Fix partial selector warnings in GHC.Runtime.Heap.Inspect - - - - - 1acb73bf by Andrew Lelechenko at 2024-11-15T06:10:47-05:00 gitlab: mention CLC in MR template - - - - - 8f2e0832 by Ben Gamari at 2024-11-15T06:11:24-05:00 rts: Allow use of GNU-stack notes on FreeBSD Previously we gated use of GNU-style non-executable stack notes to only apply on Linux. However, these are also supported by FreeBSD, which also uses ELF. Fix this. Fixes #25475. - - - - - 2c427cb0 by Ben Gamari at 2024-11-16T05:27:40-05:00 rts: Fix EINTR check in timerfd ticker When `poll` failed we previously checked that `errno == -EINTR` to silence the failure warning. However, this is wrong as `errno` values are generally not negated error codes (in contrast to many system call results, which is likely what the original author had in mind). Fixes #25477. - - - - - a0fa4941 by Ben Gamari at 2024-11-16T05:28:16-05:00 rts: Increase gen_workspace alignment to 128 bytes on AArch64 Increase to match the 128-byte cache-line size of Apple's ARMv8 implementation. Closes #25459. - - - - - 142d8afa by Ben Gamari at 2024-11-16T16:20:47-05:00 rts/RtsFlags: Refactor size parsing This makes a number of improvements mentioned in #20201: * fail if the argument cannot be parsed as a number (`-Mturtles`) * fail if an unrecognized unit is given (e.g. `-M1x`) - - - - - b7a146e5 by Ben Gamari at 2024-11-16T16:20:47-05:00 testsuite: Add tests for RTS flag parsing error handling See #20201. - - - - - ddb7afa6 by Ben Gamari at 2024-11-16T16:21:23-05:00 users guide: Mention language extensions in equality constraints discussion As suggested in #24127, mention the language extensions necessary for usage of equality constriants in their documentation. Closes #24127. - - - - - 36133dac by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide/9.14.1-notes: Fix list syntax - - - - - 888de658 by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide/debug-info: Fix duplicate flag descriptions - - - - - f120e427 by Ben Gamari at 2024-11-16T16:21:23-05:00 users-guide: Fix reference to 9.14.1 release notes - - - - - 8e975032 by Ben Gamari at 2024-11-16T16:21:59-05:00 Introduce GHC.Tc.Plugin.lookupTHName This makes it significantly more convenient (and less GHC-version-dependent) to resolve a template-haskell name into a GHC Name. As proposed in #24741. - - - - - a0e168ec by ARATA Mizuki at 2024-11-16T16:22:40-05:00 x86 NCG SIMD: Lower packFloatX4#, insertFloatX4# and broadcastFloatX4# to SSE1 instructions Fixes #25441 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 3936bf1b by sheaf at 2024-11-16T16:23:22-05:00 X86 NCG: allow VXOR at scalar floating-point types The NCG can emit VXOR instructions at scalar floating-point types, but the pretty-printer would panic instead of emitting the appropriate VXORPS/VXORPD instructions. This patch rectifies that oversight. Fixes #25455 - - - - - d9dff93a by Ben Gamari at 2024-11-16T16:23:58-05:00 rts: Fix platform-dependent pointer casts Previously we had unnecessary (and incorrect) platform-dependent casts to turn `OSThreadIds`s into a integer. We now just uniformly cast first to a `uintptr_t` (which is always safe, regardless of whether `OSThreadId` is a pointer), and then cast to the desired integral type. This fixes a warning on musl platforms. - - - - - 6d95cdb8 by Ben Gamari at 2024-11-16T16:24:34-05:00 testsuite: Mark encoding004 as broken on FreeBSD Due to #22003, CP936 fails to roundtrip: ```diff == CP936 +Failed to roundtrip given mutant byte at index 891 (251 /= 123 at index 891) +Failed to roundtrip given mutant byte at index 1605 (197 /= 69 at index 1605) +Failed to roundtrip given mutant byte at index 2411 (235 /= 107 at index 2411) +Failed to roundtrip given mutant byte at index 6480 (208 /= 80 at index 6480) +Failed to roundtrip given mutant byte at index 6482 (210 /= 82 at index 6482) +Failed to roundtrip given mutant byte at index 6484 (212 /= 84 at index 6484) +Failed to roundtrip given mutant byte at index 6496 (224 /= 96 at index 6496) +Failed to roundtrip given mutant byte at index 7243 (203 /= 75 at index 7243) +Failed to roundtrip given mutant byte at index 7277 (237 /= 109 at index 7277) +Failed to roundtrip given mutant byte at index 8027 (219 /= 91 at index 8027) +Failed to roundtrip given mutant byte at index 8801 (225 /= 97 at index 8801) ``` - - - - - 26e86984 by Ben Gamari at 2024-11-18T04:05:31-05:00 hadrian: Allow haddock options to be passed via key-value settings - - - - - 6e68b117 by Matthew Pickering at 2024-11-18T04:06:07-05:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - a4e0d235 by Rodrigo Mesquita at 2024-11-18T04:06:07-05:00 exceptions: Improve the message layout as per #285 This commit fixes the layout of the additional information included when displaying an exception, namely the type of the exception. It also fixes the default handler's heading message to work well together with the improved display message of SomeException. CLC proposal#285 - - - - - 284ffab3 by Rodrigo Mesquita at 2024-11-18T04:06:07-05:00 Display type and callstack of exception on handler This commit changes the Exception instance of SomeException to *simply* display the underlying exception in `displayException`. The augmented exception message that included the type and backtrace of the exception are now only printed on a call to `displayExceptionWithInfo`. At a surface level, existing programs should behave the same since the `uncaughtExceptionHandler`, which is responsible for printing out uncaught exceptions to the user, will use `displayExceptionWithInfo` by default. However, unlike the instance's `displayException` method, the `uncaughtExceptionHandler` can be overriden with `setUncaughtExceptionHandler`. This makes the extra information opt-in without fixing it the instance, which can be valuable if your program wants to display uncaught exceptions to users in a user-facing way (ie without backtraces). This is what was originally agreed for CLC#231 or CLC#261 with regard to the type of the exception information. The call stack also becoming part of the default handler rather than the Exception instance is an ammendment to CLC#164. Discussion of the ammendment is part of CLC#285. - - - - - 36cddd2c by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Remove redundant CallStack from exceptions Before the exception backtraces proposal was implemented, ErrorCall accumulated its own callstack via HasCallStack constraints, but ExceptionContext is now accumulated automatically. The original ErrorCall mechanism is now redundant and we get a duplicate CallStack Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall CLC proposal#285 Fixes #25283 - - - - - 7a74330b by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Freeze call stack in error throwing functions CLC proposal#285 - - - - - 3abf31a4 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 De-duplicate displayContext and displayExceptionContext The former was unused except for one module where it was essentially re-defining displayExceptionContext. Moreover, this commit extends the fix from bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too, which was missing. - - - - - c0d783f8 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Re-export NoBacktrace from Control.Exception This was originally proposed and accepted in section "2.7 Capturing Backtraces on Exceptions" of the CLC proposal for exception backtraces. However, the implementation missed this re-export, which this commit now fixes. - - - - - 802b5c3e by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Fix exception backtraces from GHCi When running the program with `runhaskell`/`runghc` the backtrace should match the backtrace one would get by compiling and running the program. But currently, an exception thrown in a program interpreted with `runhaskell` will: * Not include the original exception backtrace at all * Include the backtrace from the internal GHCi/ghc rethrowing of the original exception This commit fixes this divergence by not annotating the ghc(i) backtrace (with NoBacktrace) and making sure that the backtrace of the original exception is serialized across the boundary and rethrown with the appropriate context. Fixes #25116 The !13301 MR (not this commit in particular) improves performance of MultiLayerModules. Unfortunately, T3294 regresses on aarch64-linux-deb12 by 1% allocations. Since this patch must be merged for 9.12 ASAP, we will not be able to investigate the slight regression on this platform in time. ------------------------- Metric Decrease: MultiLayerModulesRecomp MultiLayerModulesTH_OneShot Metric Increase: T3294 ------------------------- - - - - - 3e89eb65 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 base: Add to changelog.md CLC #285 - - - - - d9326a48 by Rodrigo Mesquita at 2024-11-18T04:06:08-05:00 Bump array and stm submodules for testsuite The testsuites of array and stm had to be updated according to !13301. Updates submodule array and stm. - - - - - 325fcb5d by Ben Gamari at 2024-11-18T04:06:45-05:00 rts/adjustor: Clean up code style of Nativei386 adjustor - - - - - 39bb6e58 by Ben Gamari at 2024-11-18T04:06:45-05:00 rts/adjustor: Fix stack overrun error in Nativei386 adjustor We were reserving the wrong kind of adjustor context (the generic `AdjustorContext` used by other adjustor implementations, rather than the i386-specific `CCallContext`) to return the adjustor context while freeing, resulting in #25485. Fixes #25485. - - - - - 831aab22 by sheaf at 2024-11-18T21:22:36-05:00 Include diagnostic reason in -fdiagnostics-as-json This commit ensures that the -fdiagnostics-as-json output includes the diagnostic reason. This allows the full error message produced by GHC to be re-constructed from the JSON output. Fixes #25403 - - - - - 3e5bfdd3 by Ben Gamari at 2024-11-18T21:23:12-05:00 rts: Introduce printIPE This is a convenience utility for use in GDB. - - - - - 44d909a3 by Sjoerd Visscher at 2024-11-19T14:38:24-05:00 Don't store boot locations in finder cache Partially reverts commit fff55592a7b Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache. Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for. - - - - - 64c95292 by Sjoerd Visscher at 2024-11-19T14:38:24-05:00 Concentrate boot extension logic in Finder With new mkHomeModLocation that takes an extra HscSource to add boot extensions if required. - - - - - 11bad98d by ARATA Mizuki at 2024-11-19T14:39:08-05:00 Better documentation for floating-point min/max and SIMD primitives See #25350 for floating-point min/max Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 791a47b2 by Arnaud Spiwack at 2024-11-20T14:00:05+00:00 Add test for #25185 - - - - - 374e18e5 by Arnaud Spiwack at 2024-11-20T14:09:30+00:00 Quick look: emit the multiplicity of app heads in tcValArgs Otherwise it's not scaled properly by the context, allowing unsound expressions. Fixes #25185. - - - - - 1fc02399 by sheaf at 2024-11-20T18:11:03-05:00 x86 NCG: fix regUsageOfInstr for VMOVU & friends This commit fixes the implementation of 'regUsageOfInstr' for vector operations that take an 'Operand' as the destination, by ensuring that when the destination is an address then the address should be *READ*, and not *WRITTEN*. Getting this wrong is a disaster, as it means the register allocator has incorrect information, which can lead to it discard stores to registers, segfaults ensuing. Fixes #25486 - - - - - 7bd407a6 by Brandon Chinn at 2024-11-21T14:08:15-05:00 Fix CRLF in multiline strings (#25375) - - - - - 7575709b by Rodrigo Mesquita at 2024-11-21T14:08:52-05:00 Improve reachability queries on ModuleGraph Introduces `ReachabilityIndex`, an index constructed from a `GHC.Data.Graph.Directed` `Graph` that supports fast reachability queries (in $O(1)$). This abstract data structure is exposed from `GHC.Data.Graph.Directed.Reachability`. This index is constructed from the module graph nodes and cached in `ModuleGraph`, enabling efficient reachability queries on the module graph. Previously, we'd construct a Map of Set of ModuleGraph nodes which used a lot of memory (`O(n^2)` in the number of nodes) and cache that in the `ModuleGraph`. By using the reachability index we get rid of this space leak in the module graph -- even though the index is still quadratic in the number of modules, it is much, much more space efficient due to its representation using an IntMap of IntSet as opposed to the transitive closure we previously cached. In a memory profile of MultiLayerModules with 100x100 modules, memory usage improved from 6GB residency to 2.8GB, out of which roughly 1.8GB are caused by a second space leak related to ModuleGraph. On the same program, it brings compile time from 7.5s to 5.5s. Note how we simplify `checkHomeUnitsClosed` in terms of `isReachableMany` and by avoiding constructing a second graph with the full transitive closure -- it suffices to answer the reachability query on the full graph without collapsing the transitive closure completely into nodes. Unfortunately, solving this leak means we have to do a little bit more work since we can no longer cache the result of turning vertex indices into nodes. This results in a slight regression in MultiLayerModulesTH_Make, but results in large performance and memory wins when compiling large amounts of modules. ------------------------- Metric Decrease: mhu-perf Metric Increase: MultiLayerModulesTH_Make ------------------------- - - - - - bcbcdaaf by Cheng Shao at 2024-11-21T14:09:28-05:00 driver: fix hpc undefined symbol issue in TH with -fprefer-byte-code This commit fixes an undefined symbol error in RTS linker when attempting to compile home modules with -fhpc and -fbyte-code-and-object-code/-fprefer-byte-code, see #25510 for detailed description and analysis of the bug. Also adds T25510/T25510c regression tests to test make mode/oneshot mode of the bug. - - - - - 970ada5a by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Bump ci-images For introduction of Alpine/i386 image. Thanks to Julian for the base image. Co-Authored-By: Julian Ospald <hasufell at hasufell.de> - - - - - 8115abc2 by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Add release job for i386/Alpine As requested by Mikolaj and started by Julian. Co-Authored-By: Julian Ospald <hasufell at hasufell.de> - - - - - 639f0149 by Ben Gamari at 2024-11-22T23:32:06-05:00 rts/linker/Elf: Resolve _GLOBAL_OFFSET_TABLE_ - - - - - 490d4d0a by Ben Gamari at 2024-11-22T23:32:06-05:00 gitlab-ci: Mark i386 Alpine test breakages Marks the following tests as broken on i386/Alpine: * T22033 due to #25497 * simd009, T25062_V16, T25169, T22187_run due to #25498 - - - - - 536cdf09 by Cheng Shao at 2024-11-22T23:32:42-05:00 compiler: remove unused GHC.Linker.Loader.loadExpr This patch removes the unused `GHC.Linker.Loader.loadExpr` function. It was moved from `GHC.Runtime.Linker.linkExpr` in `ghc-9.0` to `GHC.Linker.Loader.loadExpr` in `ghc-9.2`, and remain completely unused and untested ever since. There's also no third party user of this function to my best knowledge, so let's remove this. Anyone who wants to write their own GHC API function to load bytecode can consult the source code in older release branches. - - - - - 6ee35024 by Drew Fenwick at 2024-11-22T23:33:26-05:00 Fix a non-compiling example in the type abstractions docs This patch adds a missing Show constraint to a code example in the User Guide's type abstractions docs to fix issue #25422. - - - - - d1172e20 by Rodrigo Mesquita at 2024-11-22T23:34:02-05:00 Re-introduce ErrorCallWithLocation with a deprecation pragma With the removal of the duplicate backtrace, part of CLC proposal #285, the constructor `ErrorCallWithLocation` was removed from base. This commit re-introduces it with a deprecation. - - - - - 1187a60a by Ben Gamari at 2024-11-22T23:34:39-05:00 testsuite: Skip tests requiring Hadrian deps in out-of-tree testsuite runs Some testsuite tests require specific tools (e.g. `check-ppr` and `check-exact`) beyond those shipped in the binary distribution. Skip these tests. Fixes #13897. - - - - - c37d7a2e by Ben Gamari at 2024-11-22T23:34:39-05:00 testsuite: Declare exactprint tests' dependency on check-exact - - - - - 454ce957 by Ben Gamari at 2024-11-22T23:35:15-05:00 ghc-internal: Fix a few cases of missing Haddock markup - - - - - a249649b by Ben Gamari at 2024-11-22T23:35:51-05:00 testsuite/GHCiPrimCall : Add missing Makefile includes - - - - - a021a493 by Ben Gamari at 2024-11-22T23:35:51-05:00 testsuite/IpeStats: Use Make rather than shell interpolation - - - - - 6e1fbda7 by Ben Gamari at 2024-11-25T03:55:44-05:00 hadrian-ghci-multi: Pass -this-package-name in unit response files As noted in #25509, the `-this-package-name` must be passed for each package to ensure that GHC can response references to the packages' exposed modules via package-qualified imports. Fix this. Closes #25509. - - - - - a05e4a9b by Simon Hengel at 2024-11-25T03:56:33-05:00 Refactoring: Use `OnOff` more consistently for `Extension` - - - - - 7536181d by Matthew Pickering at 2024-11-25T14:00:07-05:00 driver: Always link against "base" package when one shot linking The default value for base-unit-id is stored in the settings file. At install time, this can be set by using the BASE_UNIT_ID environment variable. At runtime, the value can be set by `-base-unit-id` flag. For whether all this is a good idea, see #25382 Fixes #25382 - - - - - 7f90f319 by Andreas Klebinger at 2024-11-25T14:00:44-05:00 Compacting GC: Handle black holes in large objects. As #14497 showed black holes can appear inside large objects when we capture a computation and later blackhole it like we do for AP_STACK closures. Fixes #24791 - - - - - 291388e1 by Cheng Shao at 2024-11-25T14:01:19-05:00 ci: minor nix-in-docker improvements This patch makes some minor improvements re nix-in-docker logic in the ci configuration: - Update `nixos/nix` to the latest version - Apply $CPUS to `cores`/`max-jobs` to avoid oversubscribing while allowing a reasonable degree of parallelism - Remove redundant `--extra-experimental-features nix-command` in later `nix shell` invocations, it's already configured in `/etc/nix/nix.conf` - - - - - e684c406 by Cheng Shao at 2024-11-25T14:01:57-05:00 ci: avoid depending on stack job for test-bootstrap jobs This patch makes test-bootstrap related ci jobs only depend on hadrian-ghc-in-ghci job to finish, consistent with other jobs in the full-build stage generated by gen_ci.hs. This allows the jobs to be spawned earlier and improve overall pipeline parallelism. - - - - - caaf5388 by Simon Hengel at 2024-11-25T14:02:41-05:00 Refactoring: Remove `pSupportedExts` from `ParserOpts` This is never used for lexing / parsing. It is only used by `GHC.Parser.Header.getOptions`. - - - - - 41f8365c by Arnaud Spiwack at 2024-11-25T14:03:23-05:00 Add test for #25515 - - - - - 9279619f by Arnaud Spiwack at 2024-11-25T14:03:23-05:00 Desugar record notation with correct multiplicities Simply uses the multiplicity as stored in the field. As I'm writing this commit, the only possible multiplicity is 1, but !13525 is changing this. It's actually easier to take !13525 into account. Fixes #25515. - - - - - fcc3ae6e by Andreas Klebinger at 2024-11-26T08:24:58-05:00 Clarify INLINE unfolding optimization docs. Fixes #24660 - - - - - 88c4fe1d by Cheng Shao at 2024-11-26T08:25:34-05:00 rts: remove -Wl,-U,___darwin_check_fd_set_overflow hack This patch bumps macOS minimum SDK version to 11.0 for x86_64-darwin to align it with aarch64-darwin. This allows us to get rid of the horrible -Wl,-U,___darwin_check_fd_set_overflow hack, which is causing linker warnings and testsuite failures on macOS 15. Fixes #25504. - - - - - 53f978c0 by doyougnu at 2024-11-26T16:07:26-05:00 ghc-experimental: expose GHC.RTS.Flags, GHC.Stats See this CLC proposal: - https://github.com/haskell/core-libraries-committee/issues/289 and this CLC proposal for background: - https://github.com/haskell/core-libraries-committee/issues/288 Metric Decrease: MultiLayerModulesTH_OneShot - - - - - e70d4140 by Wang Xin at 2024-11-26T16:08:10-05:00 Add -mcmodel=medium moduleflag to generated LLVM IR on LoongArch platform With the Medium code model, the jump range of the generated jump instruction is larger than that of the Small code model. It's a temporary fix of the problem descriped in https://gitlab.haskell .org/ghc/ghc/-/issues/25495. This commit requires that the LLVM used contains the code of commit 9dd1d451d9719aa91b3bdd59c0c6679 83e1baf05, i.e., version 8.0 and later. Actually we should not rely on LLVM, so the only way to solve this problem is to implement the LoongArch backend. Add new type for codemodel - - - - - df42ba16 by Andreas Klebinger at 2024-11-27T11:40:49-05:00 Cmm constant folding: Narrow results to operations bitwidth. When constant folding ensure the result is still within bounds for the given type by explicitly narrowing the results. Not doing so results in a lot of spurious assembler warnings especially when testing primops. - - - - - bf3db97e by Ben Gamari at 2024-11-27T11:41:26-05:00 ghc-toolchain: Introduce basic flag validation We verify that required flags (currently `--output` and `--triple`) are provided. The implementation is truly awful, but so is getopt. Begins to address #25500. - - - - - a104508d by Ben Gamari at 2024-11-27T11:42:03-05:00 rts: Allow ExecPage to allocate anywhere in address space Currently the ExecPage facility has two users: * GHCi, for constructing info tables, and * the adjustor allocation path Despite neither of these have any spatial locality constraints ExecPage was using the linker's `mmapAnonForLinker`, which tries hard to ensure that mappings end up nearby the executable image. This makes adjustor allocation needlessly subject to fragmentation concerns. We now instead return less constrained mappings, improving the robustness of the mechanism. Addresses #25503. - - - - - c3fc9b86 by Ben Gamari at 2024-11-27T11:42:39-05:00 base: Fix incorrect mentions of GHC.Internal.Numeric These were incorrectly changed by the automated refactoring of the `ghc-internal` migration. Fixes #25521. - - - - - a362b943 by sheaf at 2024-11-27T23:44:28-05:00 Add checkExact to toolTargets This change means that the Hadrian multi target will include exactprint. In particular, this means that HLS will work on exactprint inside the GHC tree. - - - - - e6c957e4 by Arnaud Spiwack at 2024-11-27T23:45:09-05:00 Add test for #25428 - - - - - 52d97f4e by Arnaud Spiwack at 2024-11-27T23:45:09-05:00 Don't bypass MonoLocalBind in empty patterns Fixes #25428 - - - - - 7890f2d8 by Ben Gamari at 2024-11-28T10:26:46-05:00 hadrian: Bump directory bound to >=1.3.9 Earlier versions of `directory` are racy on Windows due to #24382. Also includes necessary Hadrian bootstrap plan bump. Fixes #24382. - - - - - 0fd43ea6 by Adam Sandberg Ericsson at 2024-11-28T10:27:22-05:00 mention -Iw in +RTS -? - - - - - 6cf579b9 by Ben Gamari at 2024-11-28T10:27:59-05:00 gitlab-ci: Set GIT_SUBMODULE_FORCE_HTTPS GitLab recommends using `https://` to clone submodules and provides the `GIT_SUBMODULE_FORCE_HTTPS` variable to force this. Fixes #25528. - - - - - 5b4774f9 by sheaf at 2024-12-03T15:22:07+01:00 Remove TcRnDeprecatedInvisTyArgInConPat mechanism The combination of ScopedTypeVariables + TypeApplications now no longer enables the use of type applications in constructor patterns, as per GHC proposal #448. This completes the deprecation that begun with GHC 9.8. We also remove the -Wdeprecated-type-abstractions flag, which was introduced in GHC 9.10. - - - - - f813c8d7 by sheaf at 2024-12-03T17:10:15-05:00 Hadrian: use / when making filepaths absolute In Hadrian, we are careful to use -/- rather than </>, in order to use / instead of \ in filepaths. However, this gets ruined by the use of makeAbsolute from System.Directory, which, on Windows, changes back forward slashes to backslashes. - - - - - 292ed74e by Ben Gamari at 2024-12-03T17:10:52-05:00 rts/linker: Fix out-of-bounds mapping logic Previously the structure of `mmapInRegion` concealed a subtle bug concerning handling of `mmap` returning mappings below the beginning of the desired region. Specifically, we would reset `p = result + bytes` and then again reset `p = region->start` before looping around for another iteration. This resulted in an infinite loop on FreeBSD. Fixes #25492. - - - - - 20912f5b by Ben Gamari at 2024-12-03T17:10:52-05:00 rts/linker: Clarify debug output - - - - - f98b3ac0 by Simon Hengel at 2024-12-03T17:11:30-05:00 SysTools: Avoid race conditions when processing output (fixes #16450) - - - - - 03851b64 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 mg: Drop unnecessary HasCallStack This HasCallStack was a debugging artifact from a previous commit. - - - - - 01d213b5 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 Improve haddock of graphReachabilityCyclic - - - - - f7cbffe2 by Rodrigo Mesquita at 2024-12-03T17:12:06-05:00 Refactor ModuleGraph interface The 'ModuleGraph' abstraction represents the relationship and strucutre of the modules being compiled. This structure is meant to be constructed once at the start of compilation, and never changed again. However, it's exposed interface was confusing and exposed too many footguns which led to inneficient usages of the ModuleGraph. This commit improves significantly the exported interface of ModuleGraph, taking into consideration the recent improvements around reachability queries. Since the ModuleGraph graphs and related structures (HPT, EPS) are performance critical in the sense that somewhat simple mistakes can cause bad leaks and non-linear memory usage, we want to have proper APIs that guide efficient usage. This is a good step in that direction. - - - - - b69a7f3c by David Binder at 2024-12-04T18:37:42-05:00 Use consistent capitalization for "GHC Proposal" in user guide - - - - - 18d9500d by David Binder at 2024-12-04T18:37:42-05:00 Fix reference to GHC proposal 193 in user guide - - - - - dd959406 by Ben Gamari at 2024-12-04T18:38:18-05:00 Revert "rts/Interpreter: Assert that TEST*_P discriminators are valid" This assertion was based on the misconception that `GET_TAG` was returning the pointer tag whereas it is actually returning the constructor tag. This reverts commit 9bf3663b9970851e7b5701d68147450272823197. Fixes #25527. - - - - - cad6fede by Ben Gamari at 2024-12-04T18:38:54-05:00 rts/IOManager: Drop dead code This assignment is dead code as it occurs after all branches have returned. Moreover, it can't possibly be relevant since the "available" branch already sets `flag`. Potentially fixes #25542. - - - - - 55d8304e by Ben Gamari at 2024-12-06T16:56:00-05:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - 56b9f484 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 336d392e by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - dd7ca939 by Ben Gamari at 2024-12-06T16:56:00-05:00 base: Mention incorrect Data.Enum addition in changelog - - - - - dfd1db48 by Ben Gamari at 2024-12-06T16:56:36-05:00 base: Reintroduce {Show,Enum} IoSubSystem These instances were dropped in !9676 but not approved by the CLC. Addresses #25549. - - - - - 090fc7c1 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements on T25240 T25240 doesn't need RTS linker, GHCi is sufficient and GHCi can also be dynamically linked. - - - - - 3fb5d399 by Peter Trommler at 2024-12-07T03:41:21-05:00 Fix requirements for T25155 Loading C objects requires RTS linker. - - - - - 4c58bdf6 by Leary at 2024-12-07T03:42:07-05:00 TH: Add typed variants of dataToExpQ and liftData This commit introduces to template-haskell (via ghc-internal) two functions `dataToCodeQ` and `liftDataTyped`, typed variants of `dataToExpQ` and `liftData` respectively. Tested in: `dataToCodeQUnit`. - - - - - 63027593 by Serge S. Gulin at 2024-12-08T13:52:05+03:00 JS: Basic cleanup for unused stuff to simplify things. 1. Make `staticInitStat`, `staticDeclStat`, `allocUnboxedConStatic`, `allocateStaticList`, `jsStaticArg` local to modules. 2. Remove unused `hdRawStr`, `hdStrStr` from Haskell and JavaScript (`h$pstr`, `h$rstr`, `h$str`). 3. Introduce a special type `StaticAppKind` enumeration and `StaticApp` to represent boxed scalar static applications. Originally, StaticThunk supported to pass Maybe when it became Nothing for initializied thunks in an alternatie way but it is not used anymore. - - - - - a9f8f1fb by Serge S. Gulin at 2024-12-08T14:10:45+03:00 JS: Add trivial optimizations for `unpackCString` and `unpackCStringUtf8`. It became possible due of introduction strings unfloating at Sinker pass (#13185). Earns few more bytes at optimizations. - - - - - b519c06b by Serge S. Gulin at 2024-12-08T15:50:26+03:00 JS: Specialize unpackCString# CAFs (fixes #24744) Code analysis shown that such optimization would be possible out of the box if `cachedIdentForId` allowed to do that for Haskell `Id`s which are represented by few JavaScript `Ident`s. It is a usual for strings which are represented at JavaScript as a pair of 2 values: the string content and the offset where to start reading actual string from the full content. Usually offset is 0 but technically we need to allow such complex structures to be treated as "global". Enabling it there shown that `genToplevelRhs` and `globalOccs` had inaccuracies in their implementations: 1. `globalOccs` operated over JavaScript's `Ident`s but for complex structures it didn't pay attention to the fact that different Idents actually could be pointed to same Id. Now the algo is changed to calculate occurencies for Ids. 2. `genToplevelRhs` didn't assume that different Idents pointed to same Id can have mixed order of occurence. But actually the order is important. Strings are encoded into 2 variables where first is content and second is offset and their order are not interchangeable. It is fixed by regeneration Idents from collected Ids which is fine because all Idents generation is passed through the Cache and they are quasi-stable. - - - - - a8ceccf3 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Fix panic in multiline string with unterminated gap (#25530) - - - - - 9e464ad0 by Brandon Chinn at 2024-12-09T16:25:43-05:00 Add test case for unterminated multiline string - - - - - ed1ed5c6 by Rodrigo Mesquita at 2024-12-09T16:26:19-05:00 Revert mapMG renaming We had previously renamed this function for consistency, but that caused unnecessary breakage - - - - - 158261f7 by Sylvain Henry at 2024-12-09T16:27:01-05:00 RTS: make Cabal flags manual Cabal shouldn't automatically try to set them. We set them explicitly. - - - - - a83b7ed6 by Matthew Stephenson at 2024-12-10T14:01:22-05:00 Add missing @since documentation for (!?) function - - - - - e745e3a3 by Ben Gamari at 2024-12-10T14:01:59-05:00 compiler: Don't attempt to TSAN-instrument SIMD operations TSAN only provides instrumentation for 8, 16, 32, and 64-bit memory loads/stores. Don't attempt to instrument wider operations. Fixes #25563. - - - - - 684c0018 by Ben Gamari at 2024-12-10T14:02:35-05:00 gitlab/ci: Don't clobber RUNTEST_ARGS Previously the logic handling `IGNORE_PERF_FAILURES` clobbered the user's `RUNTEST_ARGS`. Fix this. - - - - - 41dae5b8 by Ben Gamari at 2024-12-10T14:03:11-05:00 hadrian: Mitigate mktexfmt race At least some versions of Texlive's `mktexfmt` utility cannot be invoked concurrently in their initial run since they fail to handle failure of `mkdir` due to racing. Specifically, we see ``` | Run Xelatex: users_guide.tex => /tmp/extra-dir-9616886274866 | Run Xelatex: Haddock.tex => /tmp/extra-dir-9616886274869 This is XeTeX, Version 3.14159265-2.6-0.999992 (TeX Live 2020) (preloaded format=xelatex) restricted \write18 enabled. kpathsea: Running mktexfmt xelatex.fmt mktexfmt: mktexfmt is using the following fmtutil.cnf files (in precedence order): mktexfmt: /usr/share/texlive/texmf-dist/web2c/fmtutil.cnf mktexfmt: mktexfmt is using the following fmtutil.cnf file for writing changes: mktexfmt: /builds/ghc/ghc/tmp-home/.texlive2020/texmf-config/web2c/fmtutil.cnf /usr/bin/mktexfmt: mkdir(/builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c/) failed for tree /builds/ghc/ghc/tmp-home/.texlive2020/texmf-var/web2c: File exists at /usr/share/texlive/tlpkg/TeXLive/TLUtils.pm line 937. I can't find the format file `xelatex.fmt'! ``` That is two `mktexfmt` invocations (for the user's guide and haddock builds) attempted to create `$HOME/texlive2020/texmf-var/web2c` and raced. One of the two `mkdir`'s consequently failed, bringing down the entire build. We avoid this by ensuring that the first `xelatex` invocation is always performed serially. Fixes #25564. - - - - - 9efbc51f by Ben Gamari at 2024-12-10T14:03:48-05:00 rts/CheckUnload: Reset old_objects if unload is skipped Previously `checkUnload` failed to reset `old_objects` when it decided not to unload (e.g. due to heap profiling being enabled). Fixes #24935. - - - - - 5192a75f by Ben Gamari at 2024-12-11T04:28:11-05:00 rts: Annotate BCOs with their Name This introduces a new bytecode instruction, `BCO_NAME`, to aid in debugging bytecode execution. This instruction is injected by `mkProtoBCO` and captures the Haskell name of the BCO. It is then printed by the disassembler, allowing ready correlation with STG dumps. - - - - - 99225996 by Ben Gamari at 2024-12-11T04:28:48-05:00 configure: Implement ld override whitelist Bring `configure` into alignment with `ghc-toolchain`, ensuring that the ld-override logic will only take effect on Linux and Windows. Fixes #25501. - - - - - 4a8fc928 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Unmark T14028 as broken on FreeBSD This now appears to pass on FreeBSD 14. Closes #19723. - - - - - d7c0eb5a by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Migrate FreeBSD runner tag to FreeBSD 14 - - - - - 7246dacc by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Reintroduce FreeBSD 14 job - - - - - 4af936da by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Allow use of newer cabal-install bindists Newer cabal-install bindists have internal directory structure. Here we detect and account for the presence of such structure. - - - - - cbf38c1b by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Enable documentation build on FreeBSD 14 - - - - - d68107fb by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Use system libffi on FreeBSD - - - - - fea3b590 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark linker_unload as broken on FreeeBSD Due to #25491. - - - - - ccf171ee by Ben Gamari at 2024-12-11T12:33:42+00:00 gitlab-ci: Prefer system toolchain on FreeBSD It's not uncommon to find machines with gcc installed via ports. We should be using the system's default clang-based toolchain instead. - - - - - cfb34738 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T21969 as broken on FreeBSD Due to #25512. - - - - - 0b64e37c by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark RestartEventLogging as broken on FreeBSD I am seeing this fail quite reproducibly. Due to #19724. - - - - - 3b412019 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Mark T16180 as "broken" on FreeBSD Sadly we in fact need to skip it as it merely times out during compilation. See #14012. - - - - - 57e3cab5 by Ben Gamari at 2024-12-11T12:33:42+00:00 testsuite: Skip T16992 unless in slow speed This test has extraordinary memory requirements and tests a rather niche aspect of the compact region mechanism. It has been suggested multiple times that we shouldn't run it in the default testsuite configuration. Finally implement this. See #21890. See #21892. - - - - - f08a72eb by Ben Gamari at 2024-12-11T19:30:54-05:00 rts(setNumCapabilities): Assert that n_caps < MAX_N_CAPS It was noticed in #25560 that this would previously be allowed, resulting in a segfault. I will add a proper exception in `base` in a future commit. - - - - - e10d31ad by Ben Gamari at 2024-12-11T19:30:55-05:00 ghc-internal: Fix inconsistent FFI import types The foreign imports of `enabled_capabilities` and `getNumberOfProcessors` were declared as `CInt` whereas they are defined as `uint32_t`. - - - - - 06265655 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Mention maximum capability count in users guide Addresses #25560. - - - - - d488470b by Ben Gamari at 2024-12-11T19:30:55-05:00 rts/Capability: Move induction variable declaration into `for`s Just a stylistic change. - - - - - 71f050b7 by Ben Gamari at 2024-12-11T19:30:55-05:00 rts: Determine max_n_capabilities at RTS startup Previously the maximum number of capabilities supported by the RTS was statically capped at 256. However, this bound is uncomfortably low given the size of today's machine. While supporting unbounded, fully-dynamic adjustment would be nice, it is complex and so instead we do something simpler: Probe the logical core count at RTS startup and use this as the static bound for the rest of our execution. This should avoid users running into the capability limit on large machines while avoiding wasting memory on a large capabilities array for most users and keeping complexity at bay. Addresses #25560. - - - - - 1e84b411 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Introduce req_c_rts As suggested by @hsyl20, this is intended to mark tests that rely on the behavior of the C RTS. - - - - - 683115a4 by Ben Gamari at 2024-12-11T19:30:55-05:00 testsuite: Add test for #25560 - - - - - ef2052a8 by Ben Gamari at 2024-12-12T04:42:32-05:00 testsuite: Only run T14497_compact in normal way This test targets the compacting GC so it makes little sense to run it across all ways. Moreover, it outright conflicts with the `nonmoving` way. - - - - - 34d3e8e6 by Ben Gamari at 2024-12-12T04:43:08-05:00 rts/CheckUnload: Don't prepare to unload if we can't unload Previously `prepareUnloadCheck` would move the `objects` list to `old_objects` even when profiling (where we cannot unload). This caused us to vacate the `objects` list during major GCs, losing track of loaded objects. Fix this by ensuring that `prepareUnloadCheck` and `checkUnload` both use the same short-cutting logic. - - - - - 9c53489d by Andrei Borzenkov at 2024-12-12T15:06:42-05:00 Update GHCi :info type declaration printing (#24459) - Do not print result's kind in type families because we have full kind in SAKS and we display invisible arity using @-binders - Do not suppress significant invisible binders An invisible binder is considered significant when it meets at least one of the following two criteria: - It visibly occurs in the declaration's body - It is followed by a significant binder, so it affects positioning For non-generative type declarations (type synonyms and type families) there is one additional criterion: - It is not followed by a visible binder, so it affects the arity of a type synonym See Note [Print invisible binders in interface declarations] for more information about what is "visibly occurs" - - - - - 13fe48d4 by Matthew Pickering at 2024-12-12T15:07:19-05:00 typechecker: Perform type family consistency checks in topological order Consider a module M importing modules A, B and C. We can waste a lot of work depending on the order that the modules are checked for family consistency. Consider that C imports A and B. When compiling C we must have already checked A and B for consistency, therefore if C is processed first then A and B will not need to be checked for consistency again. If A and B are compared first, then the consistency checks will be performed against (wasted as we already performed them for C). At the moment the order which modules are checked is non-deterministic. Clearly we should engineer that C is checked before B and A, but by what scheme? A simple one is to observe that if a module M is in the transitive closure of X then the size of the consistent family set of M is less than or equal to size of the consistent family set of X. Therefore by sorting the imports by the size of the consistent family set and processing the largest first, you make sure to process modules in topological order. In practice we have observed that this strategy has reduced the amount of consistency checks performed. One solution to #25554 - - - - - 62a2b25f by Sylvain Henry at 2024-12-14T04:31:09-05:00 TNTC: set CmmProc entry_label properly (#25565) Before this patch we were renaming the entry label of a CmmProc late in the CmmToAsm pass. It led to inconsistencies and to some labels being used in info tables but not being emitted (#25565). Now we set the CmmProc entry label earlier in the StgToCmm monad and we don't renamed it afterwards. - - - - - b339e7c3 by Simon Hengel at 2024-12-14T04:31:47-05:00 Make filter functionality for system tools line-based This is more efficient as: - All existing filter functions were line-based anyway. They broke up the input into lines and then joined it back together. - We already break up the output from system tools into lines when processing it. Splitting up the output of system tools once and then filtering and processing it reduces both code and runtime complexity. - - - - - 39669077 by Simon Hengel at 2024-12-14T04:31:47-05:00 Refactoring: Don't use a `Chan` when parsing SysTools output - - - - - 64756530 by Simon Peyton Jones at 2024-12-14T22:28:04-05:00 Tidy up the handling of `assert` Fixes #25493 - - - - - 8658fbc1 by Rodrigo Mesquita at 2024-12-14T22:28:41-05:00 base: displayException for SomeAsyncException Provide a better implementation of `SomeException` for `SomeAsyncException`. The previous, implicit, implementation, would not use the `displayException` of the exception wrapped by `SomeAsyncException`. Implements CLC-Proposal#309 Closes #25513 - - - - - 2d3a0a70 by ARATA Mizuki at 2024-12-15T18:35:30-05:00 LLVM: When emitting a vector literal with ppTypeLit, include the type information Fixes #25561 - - - - - bfacc086 by Simon Peyton Jones at 2024-12-15T18:36:05-05:00 Fix signature lookup in instance declarations This fixes a bug introduced by the fix to #16610 - - - - - 80f0e02d by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Improve GHC build times Two small changes * In GHC.Data.Unboxed, never omit interface pragmas. In "fast builds" one might omit them generally, but doing so gives very bad performance for code that imports this module. * In GHC.Hs.Dump don't do type-class specialisation. For some reason it goes mad and generates vast amounts of useless code. See #25463. - - - - - 175a1355 by Simon Peyton Jones at 2024-12-16T17:13:52+00:00 Refactor Lint Refactor Lint for two reasons: * To improve performance * To prepare for type-lets The big changes are all in GHC.Core.Lint: * Change the main APIs: * `lintType` returns nothing rather than returning a `LintedType`; * `lintCoercion` return nothing rather than returning a `LintedCoercion` Reason: these functions did a lot of allocation to return a substituted type/coercion that was often discarded, or used only to extract its kind. Instead we now return nothing, and, when needed, extract the kind and substitute. * Applications are treated as a whole, by `lintApp`. By treating multiple arguments all at once we avoid performing multiple substitutions, each substituting a single type variable. This can make an absolutely huge difference. Overall this led to a pretty massive rewrite of Lint, with many smaller changes. Smaller chnages elsewhere * Rename `GHC.Core.TyCo.Subst.getSubstInScope` to `substInScopeSet` for consistency * Define and use `GHC.Core.Type.liftedTypeOrConstraintKind` Performance. This MR someimtes gives gives a very large improvement in compile time, when Lint is on. here is a selection of changes over 5% in perf/compiler (with -dcore-lint) T25196 -97.0% T14766 -89.7% T14683 -74.4% T5631 -60.9% T20261 -56.7% T18923 -17.6% T13035 -15.8% T6048 -15.8% CoOpt_Read -14.4% T9630 -10.9% T5642 -7.3% Eliminating the egregious offenders is a big win. However, in some cases the compiler allocation /increases/. Here ae the changes over 1%: T9961 1.5% T8095 2.8% T14052 3.9% T12545 4.5% T14052Type 5.5% T5030 8.0% T5321Fun 8.3% T3064 12.7% CoOpt_Singletons 15.6% T9198 16.0% LargeRecord 18.1% I looked at the two biggest increases in compile-time bytes allocated. Interestingly, they both show substantial *decreases* in actual compile time, due to much smaller GC times. I'm honestly not sure either why the allocation increases, or why the GC time decreases; but I'm going to take the win! T9198 Baseline With patch No Lint Alloc 44.6M 44.6M Mut time 0.23s 0.22s GC time 0.21s 0.21s With Lint Alloc 309M 360M Mut time 1.51s 0.85s GC time 2.97s 0.25s ------------------- LargeRecord Baseline With patch No Lint Alloc 1.37G 1.37G Mut time 2.33s 2.33s GC time 2.40s 2.42s With Lint Alloc 3.4G 4.0G Mut time 6.02s 5.68s GC time 3.67s 3.03s IMPORTANT NOTE: These changes don't show up in CI because in CI the tests in perf/compiler are all run with -dcore-lint switched off. I gathered this data with some manual runs. - - - - - 8ef2dad6 by Simon Peyton Jones at 2024-12-17T02:48:09-05:00 Add Note [Typechecking overloaded literals] See #25494. - - - - - e86b1b20 by Ben Gamari at 2024-12-17T13:51:39-05:00 testsuite: Use math.inf instead of division-by-zero This both more directly captures the intent and also fixes #25580. - - - - - 430d965a by Ben Gamari at 2024-12-17T13:52:15-05:00 rts: Fix incorrect format specifiers in era profiling Fixes #25581. - - - - - 267098ad by Andreas Klebinger at 2024-12-18T23:43:13-05:00 Document `-prof` and non `-prof` code being incompatible. Fixes #25518. - - - - - 04433916 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: output metadata fragment in CI (cherry picked from commit 52b58a660e735b20961d792d8fa9267f01247a50) - - - - - 7c78804e by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metatdata: use fedora33 for redhat Redhat 9 doesn't have libtinfo.so.5 anymore (cherry picked from commit dc86785eb43afd1bd292287c064fb5ad94fe8c7f) - - - - - 1d72cfb2 by Zubin Duggal at 2024-12-18T23:43:50-05:00 ghcup metadata: still use centos for redhat <9 - - - - - 3f7ebc58 by Sylvain Henry at 2024-12-19T20:40:14-05:00 Merge ghc-bignum into ghc-internal (#24453) First step towards merging ghc-bignum and ghc-prim into ghc-internal. After this patch, ghc-bignum is deprecated and is just a shallow package reexporting modules from ghc-internal and base. Use those directly instead. Move `gmp` submodule into ghc-internal directory. - - - - - ee0150c2 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Improve performance of deriving Show Significantly improves performance of deriving Show instances by avoiding using the very polymorphic `.` operator in favour of inlining its definition. We were generating tons of applications of it, each which had 3 type arguments! Improves on #9557 ------------------------- Metric Decrease: InstanceMatching T12707 T3294 ------------------------ - - - - - 8b266671 by Rodrigo Mesquita at 2024-12-19T20:40:51-05:00 Don't eta expand cons when deriving Data This eta expansion was introduced with the initial commit for Linear types. I believe this isn't needed any longer. My guess is it is an artifact from the initial linear types implementation: data constructors are linear, but they shouldn't need to be eta expanded to be used as higher order functions. I suppose in the early days this wasn't true. For instance, this works now: data T x = T x f = \(x :: forall y. y -> T y) -> x True f T -- ok! T is linear, but can be passed where an unrestricted higher order function is expected. I recall there being some magic around to make this work for data constructors... Since this works, there's no need to eta_expand the data constructors in the derived Data instances. - - - - - 1f67ad21 by Andrei Borzenkov at 2024-12-25T01:42:31-05:00 Flip the order of arguments of setField (#24668) GHC Proposal 583 "HasField redesign" specifies the following order of a setField function arguments as this: setField :: forall fld a b. SetField fld a b. b -> a -> a This patch flips the application order to match the spec. - - - - - 3e0c948d by Ben Gamari at 2024-12-25T01:43:08-05:00 rel-eng/upload: Add set_symlink mode This slightly eases updating of the `latest` symlinks. - - - - - 63d63f9d by Simon Peyton Jones at 2024-12-25T01:43:45-05:00 Preserve orientation when unifying kinds This MR fixes yet another manifestation of the trickiness caused by Note [Fundeps with instances, and equality orientation]. I wish there was a more robust way to do this, but this fix is a definite improvement. Fixes #25597 - - - - - 94ba9a6a by ARATA Mizuki at 2024-12-26T10:47:57-05:00 x86 NCG SIMD: Support pack/insert/broadcast/unpack of 128-bit integer vectors - - - - - 6bf0d587 by Andrew Lelechenko at 2024-12-26T10:48:33-05:00 docs: fix haddock formatting in Control.Monad.Fix - - - - - feb14af1 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Remove unnecessary irrefutable patterns from NonEmpty functions Implementation of https://github.com/haskell/core-libraries-committee/issues/107 - - - - - 6a0d91b4 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Make cons, Semigroup, IsList, and Monad instances stricter - - - - - 1249e597 by Sergey Vinokurov at 2024-12-27T15:06:28+00:00 Restore some laziness in <| and Semigroup instance, improve Monad instance The Monad instance shouldn't produce the outer :| unless f a reduces to WHNF. (Notice that the b :| bs match is implicitly lazy.) - - - - - 8699d826 by Sergey Vinokurov at 2024-12-27T15:12:30+00:00 Add comment outlining Data.List.NonEmpty implementation guiding principles - - - - - 7febe00e by Sergey Vinokurov at 2024-12-27T22:24:43+00:00 Fix tests since location of ‘>>=’ changed - - - - - a928c326 by ARATA Mizuki at 2024-12-28T03:06:14-05:00 Fix LLVM version detection With a recent LLVM, `llc -version` emits the version on the first line if the vendor is set. It emits the version on the second line otherwise. Therefore, we need to check the both lines to detect the version. GHC now emits a warning if it fails to detect the LLVM version, so we can notice if the output of `llc -version` changes in the future. Also, the warning for using LLVM < 10 on s390x is removed, because we assume LLVM >= 13 now. This fixes the definition of __GLASGOW_HASKELL_LLVM__ macro. Fixes #25606 - - - - - 7f79257a by Zubin Duggal at 2024-12-29T13:04:35+00:00 Bump base, ghc-prim and template-haskell versions for 9.12 Also bump various submodules. (cherry picked from commit 6fc1fa3bdc8f53acdb19e47145789274060e498f) Bump base bound to 4.21 for GHC 9.12 (cherry picked from commit 473a201c6b55aea5bf9c9db0836a66ea1b657e04) Bump binary submodule to 0.8.9.2 (cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20) (cherry picked from commit ec2f40b45c1a3d82d17a2fc07e9ddb9218bc3940) Bump exceptions submodule to 0.10.9 (cherry picked from commit f5b5d1dc2d326368e5b173d622630d77f019b629) Bump file-io submodule to 0.1.4 (cherry picked from commit ba786681de6ac5fa49938e2cd71a5988f0f40d1f) bump os-string submodule to 2.0.6 (cherry picked from commit 3a7ffdbb832c045a55fd1ef24f546abdd9d9e30f) bump transformers submodule to 0.6.1.2 (cherry picked from commit 53b46fd437421b9e5a001edc6d1c427439d7714f) Bump directory submodule to v1.3.9.0 (cherry picked from commit 27dc2664c5404bb462092bb216c2c37b418fd1f8) Bump Win32 submodule to v2.14.1.0 (cherry picked from commit 80df88086180f5e39212b2feacf70a9d2b263c6c) Bump filepath submodule to 1.5.3.0 (cherry picked from commit 29bfae2c58a7303a081a6e7956b9f55e5faf3eeb) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 97b0dff223a6c4cc003adec448104c277f214645) Bump unix submodule to 2.8.6.0 (cherry picked from commit a1f56d6d6a99c100f88ef0a8b4d51298cf24a42d) Bump os-string submodule to 2.0.8 (cherry picked from commit 0121b76fd52ea0c0ce5d07085bc195666b63c625) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 962ceb50c8a6fc370e1c0a267f5cd5562a8cf759) Bump filepath submodule to 1.5.4.0 (cherry picked from commit 7bc6877fd5d41c6d5900678ad5e73ed30f366569) Bump file-io submodule to 0.1.5 (cherry picked from commit 9478b5aefe2877d58baf527edcf936dddbb955b7) Bump Cabal submodule to 3.14.1.0 (cherry picked from commit 5c9c3e3f79a79bb6d9a77a17c716dc3a0bcbd2aa) Bump directory submodule to 0.12.2.0 (cherry picked from commit 897906265db37af34ae2aaa016cec417f263407b) Bump array submodule for base bump Bump stm submodule for base bump Bump process submodule for base bump - - - - - f6079408 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix ghc-e005 after HasCallstack changes (cherry picked from commit 77f340a24561cea8a6f2ada296b3ea356ab1823c) - - - - - 3e10fa75 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Add haskeline to stage0Packages Otherwise we link against boot inplace and boot unix as boot haskeline depends on boot unix. (cherry picked from commit 90b493769ebdf3cd7be404d18462dc20ac1044df) - - - - - 4ad6aec4 by Zubin Duggal at 2024-12-29T13:04:35+00:00 Fix TH changelog - - - - - ea3f7fd5 by Zubin Duggal at 2024-12-29T13:04:35+00:00 release: copy index.html from correct directory (cherry picked from commit cbfd0829cd61928976c9eb17ba4af18272466063) - - - - - fafb70db by Zubin Duggal at 2024-12-29T13:04:35+00:00 hadrian-multi: warn on unused imports os-string has redundant imports (cherry picked from commit dde3796be689ea57543936e22aa5ea4ef7ed995e) - - - - - c02b1e46 by Simon Peyton Jones at 2024-12-29T17:04:30-05:00 Fix in-scope set for CSE Ticket #25468 showed an assertion failure in CSE because a top-level Id was being used before it was defined. Reason: Note [Glomming] in GHC.Core.Opt.OccurAnal. Solution (used in many places): just put all the top-level bindings in scope at the beginning of CSE. Compile-time allocation wobbles up and down a tiny bit; geo mean is zero. But MultiLayerModulesTH_OneShot and hard_hole_fits increase (on some architectures only) by a bit oever 2% . I think these are just a random fluctuations. Metric Increase: MultiLayerModulesTH_OneShot hard_hole_fits - - - - - 559d4f84 by Krzysztof Gogolewski at 2024-12-30T11:53:19-05:00 Add tests for #23883 The issue has been fixed by commit f5d3e03c56ffc63. Only T23883a is the actual regression test, the remaining ones are tricky cases found during development of an independent fix !11313. - - - - - 278a53ee by Sergey Vinokurov at 2024-12-30T11:53:59-05:00 Update changelog for CLC proposal #107 (NonEmpty laziness) - - - - - f56558be by Matthew Pickering at 2025-01-07T13:53:03-05:00 warnings: Find out if a qualified name is in the interactive scope directly There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600 - - - - - 84155cdb by Simon Peyton Jones at 2025-01-07T13:53:40-05:00 Tidy up kcConDecls Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types - - - - - 6c12b6cf by Bryan Richter at 2025-01-07T18:15:02-05:00 Remove tmp files after toolchain check Fixes #25620 - - - - - 42826a89 by Cheng Shao at 2025-01-07T18:15:39-05:00 xxhash: bump to v0.8.3 - - - - - 185f17e4 by sheaf at 2025-01-07T18:16:15-05:00 Fix typo in GHC.Tc.Solver.Solve.runTcPluginsWanted - - - - - 23099752 by Luite Stegeman at 2025-01-08T00:33:33+01:00 Add flags for switching off speculative evaluation. We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284 - - - - - 0161badc by Ben Gamari at 2025-01-09T17:30:05-05:00 rts/printClosure: Print IPE information for thunks and functions This makes it considerably easier to grok the structure of the heap when IPE information is available. - - - - - 023f36f5 by Rodrigo Mesquita at 2025-01-10T14:57:48-05:00 user_guide: Note -pgmP/-optP are for /Haskell/-CPP Fixes #25574 - - - - - e1c133f2 by Ben Gamari at 2025-01-10T14:58:25-05:00 dump-decls: Suppress unit-ids While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334. - - - - - 2e7bf446 by sheaf at 2025-01-13T10:55:26+01:00 Remove SDocs from ErrCtxt & ErrInfo This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436 - - - - - 2d62b970 by Mike Pilgrem at 2025-01-13T12:59:10-05:00 Re CLC #300 - Specify fmap for NonEmpty as map See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also. - - - - - ab3ab3e3 by Luite Stegeman at 2025-01-13T12:59:58-05:00 compiler/coreprep: Turn off dictionary speculation by default Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284 - - - - - 3d9cacd5 by Patrick at 2025-01-14T02:34:46+08:00 Enhance kind inference for data family instances This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by: default avatarSimon Peyton Jones <simon.peytonjones at gmail.com> - - - - - f6493dbc by amesgen at 2025-01-15T18:47:23-05:00 wasm: prevent bundlers from resolving import("node:timers") This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`. - - - - - 87e82e2e by sheaf at 2025-01-16T14:51:45+01:00 Use checkTyEqRhs to make types concrete This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883. - - - - - 5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00 x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2# MOVD takes the input format. Fixes #25658 - - - - - 14f8a7ec by Mateusz Goślinowski at 2025-01-17T22:49:09+00:00 Allow multiline strings in JS FFI (#25633) - - - - - 854c2f75 by Simon Peyton Jones at 2025-01-18T02:54:08-05:00 Fix a buglet in tcSplitForAllTyVarsReqTVBindersN The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661. - - - - - 264a1186 by sheaf at 2025-01-18T10:05:56+00:00 Generalise GHC diagnostic code infrastructure This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages. - - - - - bf4f5ad3 by Jade at 2025-01-18T10:05:56+00:00 Add structured errors to GHCi (#23338) This patch creates the 'GhciCommandErrorMessage' data type which implents the 'Diagnostic' class and also provides error code for these error conditions. - - - - - b6f54188 by Ben Gamari at 2025-01-18T12:38:46-05:00 Revert "Division by constants optimization" This appears to be responsible for the regression described in #25653. This reverts commit daff1e30219d136977c71f42e82ccc58c9013cfb. - - - - - 0fd90de8 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Introduce div2 test This is a useful test from !8392 which is worth keeping around. - - - - - 32680979 by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Test shift correctness in mul2 test - - - - - 163aa50a by Ben Gamari at 2025-01-18T12:38:46-05:00 testsuite: Add regression test for #25653 - - - - - 44778963 by Matthew Pickering at 2025-01-20T11:23:08+00:00 driver: Store an ExternalModuleGraph in the EPS We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - b3c0acfc by Cheng Shao at 2025-01-20T11:53:10-05:00 hie: fix hie.yaml to use default hie-bios script !13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change. - - - - - 595013d4 by Ben Gamari at 2025-01-21T09:57:23-05:00 compiler: Fix CPP guards around ghc_unique_counter64 The `ghc_unique_counter64` symbol was introduced in the RTS in the 64-bit unique refactor (!10568) which has been backported to %9.6.7 and %9.8.4. Update the CPP to reflect this. Fixes #25576. - - - - - 09ee3247 by Ryan Scott at 2025-01-21T09:58:00-05:00 Fix :info pretty-printing of UNPACKed fields This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651. - - - - - 6b7ea592 by Rodrigo Mesquita at 2025-01-21T16:10:35-05:00 driver: Store the HomePackageTable in a mutable reference This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp ------------------------- - - - - - f983a00f by Jens Petersen at 2025-01-21T16:11:12-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ``` - - - - - 51e3ec83 by Vladislav Zavialov at 2025-01-22T20:41:32+03:00 Rework built-in and punned names (#25174, #25179, #25180, #25182) This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests. - - - - - 85c60aea by Teo Camarasu at 2025-01-23T18:06:21-05:00 doc: Add documentation for -XDoAndIfThenElse Resolves #18631 Co-authored-by: Richard Eisenberg <rae at cs.brynmawr.edu> - - - - - 4495e48f by Brandon Chinn at 2025-01-24T11:54:24-05:00 Break out GHC.Parser.Lexer.Interface - - - - - 4f8fc11e by Brandon Chinn at 2025-01-24T11:54:24-05:00 Fix lexing comments in multiline strings (#25609) Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - e7ab778f by Matthew Pickering at 2025-01-24T11:55:01-05:00 testsuite: Pass TEST_HC_OPTS to many more tests This passes `-dno-debug-output` to the test and `-dlint. - - - - - c3593101 by Sylvain Henry at 2025-01-24T23:12:20-05:00 Merge ghc-prim's modules into ghc-internal (#24453) ghc-internal becomes the only wired-in package exposing primitives. There are some minor GHC allocation regressions, but they barely cross the thresholds and only with the wasm backend. They're likely due to longer symbols (ghc-internal vs ghc-prim, GHC.Internal.X vs GHC.X). Metric Increase: T13035 T1969 T4801 T9961 - - - - - 70f7741a by Jens Petersen at 2025-01-24T23:12:58-05:00 hp2ps/Utilities.c: add extern parameter types for malloc and realloc for C23 use portable C types! - - - - - a1d92378 by Brandon Chinn at 2025-01-25T15:11:54-08:00 Fix for alex-3.5.2.0 (#25623) This INLINE pragma for alexScanUser was added in 9.12, but then I ported the change to alex in 3.5.2.0 (https://github.com/haskell/alex/pull/262). I didn't realize that GHC errors on duplicate INLINE pragmas, so this ended up being a breaking change. This change should be backported into 9.12 - - - - - 62760367 by ARATA Mizuki at 2025-01-27T16:23:06-05:00 x86 NCG: Make MOVD's output format explicit The old design led to inference of a wrong format, losing upper bits of a vector register. Fixes #25659 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - f19ab490 by Simon Hengel at 2025-01-27T16:23:45-05:00 doc: Correct JSON schema for `-fdiagnostics-as-json` (fixes #25393) - - - - - e16eae65 by Cheng Shao at 2025-01-27T21:41:39+00:00 hadrian: fix bootstrap with 9.12.1 This patch bumps hadrian index-state to fix bootstrap with 9.12.1. - - - - - 8071bad8 by Jeffrey Young at 2025-01-28T21:45:32-05:00 base: add SrcLoc changes to changelog, 4.21.0.0 I accidentally dropped this in !13381 - closes #25614 See: - ea4587794b9e3a098f9c02bd6cea2294af2539ce (the 13381 commit) - Issue #25614 - - - - - 9dcc7e28 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Rename `cloneBndrs` and such — now all the monadic ones have an `M` suffix. We now have `cloneBndrs` and `cloneRecIdBndrs` which take a `UniqSupply` argument, and `cloneBndrsM` and `cloneRecIdBndrsM` which rather have a `MonadUnique` constraint. - - - - - 643dd3d8 by Matthew Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in unique generation, and clean up some other partial uni patterns as well. Also drop the losing `instance MonadFail UniqSM`. We redefine `getUniquesM` in terms of `Infinite` rather than `[]`, and define another method `getUniqueListM` for the use sites where we actually want a `[]`. Thus, at many sites, we can avoid the partiality of the empty list case. We also define `withUniques`, `withUniquesM`, and `withUniquesM'`, which traverse an arbitrary `Traversable` structure and introduce a `Unique` for each element. This allows us to redefine various functions to operate on more appropriate types than `[]` and avoid further partiality (in the form of incomplete-uni-patterns). - - - - - dd0acc3c by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Tc.Deriv.Functor`. Make the list of variables to use in generated code `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - 4e9adedf by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Use `Infinite` in `GHC.Runtime.Debugger`. Make the list of available names `Infinite`, to avoid panicking on the (now impossible) empty list case. - - - - - bed812b7 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Cmm.DebugBlock`. We do so by changing the type of `BlockContext` to statically (in GHC) exclude the possibility of Cmm statics, and using `NonEmpty` lists of `BlockContext`s in `cmmDebugGen`. - - - - - 27587df3 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.Types.Literal`. We do so by introducing `mkLitNumberWrap'` whose ultimate codomain is `Integer` rather than `Literal`, and then use that rather than `mkLitNumberWrap` where we just need the number rather than the `Literal`. - - - - - 138de0ff by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Avoid incomplete-uni-patterns in `GHC.CmmToAsm.X86.CodeGen`. - Match the vector element list only once in `shuffleInstructions`. - Define `isSuitableFloatingPointLit_maybe` which returns `Just` the width if the lit is indeed suitable. - - - - - d8cb3d36 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Clean up more incomplete uni patterns. At some sites, we merely panic if the `[]` or `Maybe` is empty when we convert to `NonEmpty` or `Identity`, but at least now we make it explicit. At other sites, we are able to use more precise types and avoid the partiality altogether. To do so, we redefine various functions to operate over `Traversable` arguments, so we can use the appropriate shape where known. - - - - - f251bd22 by M Farkas-Dyck at 2025-01-29T02:27:48-05:00 Outline `expectJustPanic`. - - - - - a963a1a5 by Marc Scholten at 2025-01-29T02:28:35-05:00 base: Introduce Data.Enum.enumerate (CLC #306) https://github.com/haskell/core-libraries-committee/issues/306 - - - - - 944712da by Ben Gamari at 2025-01-29T02:29:13-05:00 base: Update description of locking behavior - - - - - 85abc69c by Ben Gamari at 2025-01-29T02:29:51-05:00 base: Fix @since annotation of Data.Bounded Fixes #25615. - - - - - 2ca41c62 by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Fix overly-broad handling of Addr# literals Previously we assumed that all unlifted types were `Addr#` but this isn't true. As noted in #25638, unlifted nullary data constructor workers can also appear at the top-level and are obviously not of type `Addr#`. Note that there is more work to be done to properly handle unlifted data constructors (especially nullary; see #25636). However, this is a small step in the right direction. Closes #25641. - - - - - ec26c54d by Ben Gamari at 2025-01-29T02:30:29-05:00 StgToByteCode: Assert that PUSH_G'd values are lifted We currently do not support top-level unlifted data constructor applications, therefore this is a safe assertion. Pointed out by @sheaf. - - - - - 8847125f by Ben Gamari at 2025-01-29T02:31:07-05:00 gitlab-ci: Run test-primops testsuite in ~"full-ci" pipeline Closes #25654. - - - - - bf8c7d6e by Matthew Pickering at 2025-01-29T02:31:44-05:00 bytecode: Do not generate `SLIDE x 0` instructions SLIDE x 0 is a no-op as it means to shift x elements of the stack by no spaces. In the interpreter, this results in a loop which copies an array element into the same place. I have instrumented GHCi to count how many of these instructions are interpreted. The workload was `ghc` compiling two simple modules. Total no-op slides: 7793476 Total slides: 11413289 Percentage useless (slides): 68% Percentage uselss of total instructions: 9% - - - - - 7bfc93a7 by Zubin Duggal at 2025-01-29T21:41:17-05:00 hackage-doc-tarball: Allow ghc-boot-th to be uploaded to hackage It can't refer to files outside its source directory, so patch that part out. This is OK because those files are only used while bootstrapping. Also add ghci to the list of packages to be uploaded Fixes #25687 - - - - - 704eeb02 by Roman S at 2025-01-29T21:42:05-05:00 Fix Control.Arrow (***) diagram (fixes #25698) - - - - - 662645f0 by Matthew Pickering at 2025-02-03T11:44:41-05:00 compiler: Always load GHC.Data.FastString optimised into GHCi The FastString table is shared between the boot compiler and interpreted compiler. Therefore it's very important the representation of `FastString` matches in both cases. Otherwise, the interpreter will read a FastString from the shared variable but place the fields in the wrong place which leads to segfaults. Ideally this state would not be shared, but for now we can always compile both with `-O2` and this leads to a working interpreter. - - - - - 05e5785a by Peter Trommler at 2025-02-03T11:45:17-05:00 RTS: Fix compile on powerpc64 ELF v1 Cabal does not know about the different ABIs for powerpc64 and compiles StgCRunAsm.S unconditionally. The old make-based build system excluded this file from the build and it was OK to signal an error when it was compiled accidentally. With this patch we compile StgCRunAsm.S to an empty file, which fixes the build. Fixes #25700 - - - - - cbbb64fb by Matthew Pickering at 2025-02-03T23:40:33-05:00 interpreter: Always print unit and module name in BCO_NAME instruction Currently the BCO_Name instruction is a bit difficult to use since the names are not qualified by the module they come from. When you have a very generic name such as "wildX4", it becomes impossible to work out which module the identifier comes from. Fixes #25694 - - - - - 764a43ac by Ben Gamari at 2025-02-03T23:41:10-05:00 upload-ghc-libs: Drop more references to ghc-internal from ghc-boot-th (cherry picked from commit afec4b75c2d0e9f5c462a86d9f3697acf30355c7) Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 9a59b026 by Ben Gamari at 2025-02-04T10:00:18-05:00 gitlab-ci: Don't use .full-ci to run test-primops test-primops depends upon the existence of validate jobs, yet these do not exist in the context of nightly jobs, which .full-ci includes. - - - - - 7cc08550 by Ben Gamari at 2025-02-04T18:34:49-05:00 CorePrep: Name `sat` binders more descriptively - - - - - fb40981d by Ben Gamari at 2025-02-04T18:35:26-05:00 ghc-toolchain: Parse i686 triples This is a moniker used for later 32-bit x86 implementations (Pentium Pro and later). Fixes #25691. - - - - - 02794411 by Cheng Shao at 2025-02-04T18:36:03-05:00 compiler: remove unused assembleOneBCO function This patch removes the unused assembleOneBCO function from the bytecode assembler. - - - - - db19c8a9 by Matthew Pickering at 2025-02-05T23:16:50-05:00 perf: Replace uses of genericLength with strictGenericLength genericLength is a recursive function and marked NOINLINE. It is not going to specialise. In profiles, it can be seen that 3% of total compilation time when computing bytecode is spend calling this non-specialised function. In addition, we can simplify `addListToSS` to avoid traversing the input list twice and also allocating an intermediate list (after the call to reverse). Overall these changes reduce the time spend in 'assembleBCOs' from 5.61s to 3.88s. Allocations drop from 8GB to 5.3G. Fixes #25706 - - - - - 5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00 perf: nameToCLabel: Directly manipulate ByteString rather than going via strings `nameToCLabel` is called from `lookupHsSymbol` many times during bytecode linking. We can save a lot of allocations and time by directly manipulating the bytestrings rather than going via intermediate lists. Before: 2GB allocation, 1.11s After: 260MB allocation, 375ms Fixes #25719 ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot ------------------------- - - - - - 66c7f656 by Matthew Pickering at 2025-02-06T17:15:25-05:00 interpreter: Fix INTERP_STATS profiling code The profiling code had slightly bitrotted since the last time it was used. This just fixes things so that if you toggle the INTERP_STATS macro then it just works and prints out the stats. Fixes #25695 - - - - - f71c2835 by Matthew Pickering at 2025-02-06T17:16:02-05:00 perf: Key the interpreter symbol cache by Name rather than FastString Profiles showed that about 0.2s was being spend constructing the keys before looking up values in the old symbol cache. The performance of this codepath is critical as it translates directly to a delay when a user evaluates a function like `main` in the interpreter. Therefore we implement a solution which keys the cache(s) by `Name` rather than the symbol directly, so the cache can be consulted before the symbol is constructed. Fixes #25731 - - - - - 8f8d3a90 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by IO operations Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 28600825 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label threads forked by System.Timeout Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 8a249827 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label signal handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 26af26f0 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Label Windows console event handling threads Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - bf9c3d4f by Ben Gamari at 2025-02-08T01:17:28-05:00 ghci: Label evaluation sandbox thread Addresses part of #25452. Addresses core-libraries-committee#305. - - - - - 38f78ce5 by Ben Gamari at 2025-02-08T01:17:28-05:00 base: Add changelog entry for addition of thread labels Addresses #25452. Addresses core-libraries-committee#305. - - - - - c100deb5 by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Clean up style This cleans up a number of stylistic inconsistencies although it's still far from perfect. - - - - - c4a7680a by Ben Gamari at 2025-02-08T01:18:05-05:00 gen-ci: Properly encapsulate GitLab predicates - - - - - 52b6539b by M Farkas-Dyck at 2025-02-08T11:34:51-08:00 Avoid partiality in `Language.Haskell.Syntax.Expr`, `GHC.Hs.Expr`, `GHC.Rename.Expr`, etc. In particular, use `NonEmpty` where appropriate: - the argument of `FieldLabelString` - the argument of `HsMultiIf` - `grhssGRHSs` Decreases overall compile-time allocation by about 0.1% in the benchmark suite (min -0.8%, max +0.3%). Metric Decrease: T3294 - - - - - a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00 gitlab-ci: Bump docker images Closes #25693. - - - - - a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Drop uses of head/tail To silence warnings with GHC 9.10 - - - - - 12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00 hadrian: Disable x-data-list-nonempty-unzip warning - - - - - e22a14fc by Simon Peyton Jones at 2025-02-11T16:21:10+00:00 Deal correctly with Given CallStack constraints As #25675 showed, the CallStack solving mechanism was failing to account for Given CallStack constraints. This small patch fixes it and improves the Notes. Small improvement to GHCi debugger output in break011, break024, which is discussed on the MR !13883 - - - - - db3e810f by Simon Peyton Jones at 2025-02-12T09:12:30-05:00 Fix inlineBoringOk again This MR fixes #25713, which turned out to be a consequence of not completing #17182. I think I have now gotten it right. See the new Note [inlineBoringOk] - - - - - ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - c1ffe19e by Ben Gamari at 2025-03-10T19:35:36-04:00 ghc-internal: Move STM utilities out of GHC.Internal.Conc.Sync This is necessary to avoid an import cycle on Windows when importing `GHC.Internal.Exception.Context` in `GHC.Internal.Conc.Sync`. On the road to address #25365. - - - - - 51a24b4e by Ben Gamari at 2025-03-10T19:35:40-04:00 base: Capture backtrace from throwSTM Implements core-libraries-committee#297. Fixes #25365. - - - - - 79ebe723 by Ben Gamari at 2025-03-10T19:35:40-04:00 base: Annotate rethrown exceptions in catchSTM with WhileHandling Implements core-libraries-committee#298 - - - - - 1902 changed files: - .gitattributes - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/hello.hs - .gitlab/jobs.yaml - .gitlab/merge_request_templates/Default.md - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload.sh - .gitlab/rel_eng/upload_ghc_libs.py - .gitmodules - compile_flags.txt - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/UsageEnv.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - + compiler/GHC/Data/Graph/Directed/Internal.hs - + compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - compiler/GHC/Data/IOEnv.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/Infinite.hs - + compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/Unboxed.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Config/CoreToStg/Prep.hs - compiler/GHC/Driver/Config/Linker.hs - compiler/GHC/Driver/Config/Parser.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Errors.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Phases.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Coverage.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Ppr.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Config.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Llvm/Ppr.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - + compiler/GHC/Parser/Lexer/Interface.hs - + compiler/GHC/Parser/Lexer/String.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - + compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/CgUtils.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Hpc.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/CodeGen.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Linker/Utils.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Monad.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Symbols.hs - compiler/GHC/StgToJS/Types.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Errors/Types/PromotionErr.hs - compiler/GHC/Tc/Gen/Annotation.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Utils/Unify.hs-boot - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Cache.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Finder/Types.hs - + compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/ModInfo.hs - + compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Info.hs - compiler/GHC/Unit/Module/Env.hs - + compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/Location.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/Module/Status.hs - compiler/GHC/Unit/Module/Warnings.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Panic/Plain.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/cbits/genSym.c - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/conf.py - docs/users_guide/debug-info.rst - docs/users_guide/debugging.rst - docs/users_guide/diagnostics-as-json-schema-1_0.json - + docs/users_guide/diagnostics-as-json-schema-1_1.json - docs/users_guide/expected-undocumented-flags.txt - + docs/users_guide/exts/doandifthenelse.rst - docs/users_guide/exts/equality_constraints.rst - docs/users_guide/exts/multiline_strings.rst - docs/users_guide/exts/overloaded_record_update.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/exts/primitives.rst - docs/users_guide/exts/rewrite_rules.rst - docs/users_guide/exts/stolen_syntax.rst - docs/users_guide/exts/strict.rst - docs/users_guide/exts/syntax.rst - docs/users_guide/exts/type_abstractions.rst - docs/users_guide/ghci.rst - docs/users_guide/packages.rst - docs/users_guide/phases.rst - docs/users_guide/profiling.rst - docs/users_guide/release-notes.rst - docs/users_guide/runtime_control.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using-warnings.rst - docs/users_guide/using.rst - docs/users_guide/wasm.rst - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Exception.hs - ghc/GHCi/UI/Info.hs - ghc/GHCi/UI/Monad.hs - + ghc/GHCi/UI/Print.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/bindist/Makefile - hadrian/bindist/config.mk.in - hadrian/bootstrap/plan-9_10_1.json - hadrian/bootstrap/plan-9_6_1.json - hadrian/bootstrap/plan-9_6_2.json - hadrian/bootstrap/plan-9_6_3.json - hadrian/bootstrap/plan-9_6_4.json - hadrian/bootstrap/plan-9_6_5.json - hadrian/bootstrap/plan-9_6_6.json - hadrian/bootstrap/plan-9_8_1.json - hadrian/bootstrap/plan-9_8_2.json - hadrian/bootstrap/plan-bootstrap-9_10_1.json - hadrian/bootstrap/plan-bootstrap-9_6_1.json - hadrian/bootstrap/plan-bootstrap-9_6_2.json - hadrian/bootstrap/plan-bootstrap-9_6_3.json - hadrian/bootstrap/plan-bootstrap-9_6_4.json - hadrian/bootstrap/plan-bootstrap-9_6_5.json - hadrian/bootstrap/plan-bootstrap-9_6_6.json - hadrian/bootstrap/plan-bootstrap-9_8_1.json - hadrian/bootstrap/plan-bootstrap-9_8_2.json - hadrian/cabal.project - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/doc/user-settings.md - hadrian/hadrian.cabal - hadrian/src/CommandLine.hs - hadrian/src/Flavour.hs - hadrian/src/Hadrian/Utilities.hs - hadrian/src/Oracles/ModuleFiles.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Dependencies.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/SourceDist.hs - hadrian/src/Rules/Test.hs - hadrian/src/Rules/ToolArgs.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Parser.hs - hadrian/src/Settings/Warnings.hs - hadrian/stack.yaml - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/array - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Control/Exception.hs - libraries/base/src/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Char.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/Data/Semigroup.hs - libraries/base/src/GHC/Base.hs - libraries/base/src/GHC/Conc.hs - libraries/base/src/GHC/Conc/Sync.hs - libraries/base/src/GHC/Exception.hs - libraries/base/src/GHC/Exts.hs - + libraries/base/src/GHC/Num/BigNat.hs - + libraries/base/src/GHC/Num/Integer.hs - + libraries/base/src/GHC/Num/Natural.hs - libraries/base/src/Prelude.hs - libraries/base/src/System/Timeout.hs - libraries/base/tests/IO/T21336/T21336a.stderr - libraries/base/tests/IO/T21336/T21336b.stderr - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/all.T - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/openFile002.stderr-mingw32 - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withBinaryFile002.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFile002.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/IO/withFileBlocking002.stderr - libraries/base/tests/T15349.stderr - libraries/base/tests/T16111.stderr - libraries/base/tests/T19288.stderr - libraries/base/tests/T24807.stderr - libraries/base/tests/all.T - libraries/base/tests/assert.stderr - libraries/base/tests/readFloat.stderr - − libraries/base/tests/topHandler04.hs - − libraries/base/tests/topHandler04.stderr - libraries/base/tests/unicode002.stdout - libraries/base/tests/unicode003.hs - libraries/base/tests/unicode003.stdout - libraries/binary - libraries/bytestring - libraries/deepseq - libraries/directory - libraries/exceptions - libraries/file-io - libraries/filepath - − libraries/ghc-bignum/.gitignore - + libraries/ghc-bignum/Dummy.hs - − libraries/ghc-bignum/Setup.hs - − libraries/ghc-bignum/aclocal.m4 - libraries/ghc-bignum/changelog.md - − libraries/ghc-bignum/config.mk.in - − libraries/ghc-bignum/configure.ac - − libraries/ghc-bignum/ghc-bignum.buildinfo.in - libraries/ghc-bignum/ghc-bignum.cabal - − libraries/ghc-bignum/install-sh - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Data/SizedSeq.hs - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-compact/tests/all.T - libraries/ghc-compact/tests/compact_function.stderr - libraries/ghc-compact/tests/compact_mutable.stderr - libraries/ghc-compact/tests/compact_pinned.stderr - libraries/ghc-experimental/ghc-experimental.cabal.in - libraries/ghc-experimental/src/Data/Sum/Experimental.hs - libraries/ghc-experimental/src/Data/Tuple/Experimental.hs - + libraries/ghc-experimental/src/GHC/RTS/Flags/Experimental.hs - + libraries/ghc-experimental/src/GHC/Stats/Experimental.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-experimental/src/Prelude/Experimental.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-heap/tests/stack_big_ret.hs - libraries/ghc-internal/.gitignore - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/aclocal.m4 - libraries/ghc-bignum/README.rst → libraries/ghc-internal/bignum-backend.rst - libraries/ghc-prim/cbits/atomic.c → libraries/ghc-internal/cbits/atomic.c - libraries/ghc-prim/cbits/bitrev.c → libraries/ghc-internal/cbits/bitrev.c - libraries/ghc-prim/cbits/bswap.c → libraries/ghc-internal/cbits/bswap.c - libraries/ghc-prim/cbits/clz.c → libraries/ghc-internal/cbits/clz.c - libraries/ghc-prim/cbits/ctz.c → libraries/ghc-internal/cbits/ctz.c - libraries/ghc-prim/cbits/debug.c → libraries/ghc-internal/cbits/debug.c - libraries/ghc-bignum/cbits/gmp_wrappers.c → libraries/ghc-internal/cbits/gmp_wrappers.c - libraries/ghc-prim/cbits/longlong.c → libraries/ghc-internal/cbits/longlong.c - libraries/ghc-prim/cbits/mulIntMayOflo.c → libraries/ghc-internal/cbits/mulIntMayOflo.c - libraries/ghc-prim/cbits/pdep.c → libraries/ghc-internal/cbits/pdep.c - libraries/ghc-prim/cbits/pext.c → libraries/ghc-internal/cbits/pext.c - libraries/ghc-prim/cbits/popcnt.c → libraries/ghc-internal/cbits/popcnt.c - libraries/ghc-prim/cbits/word2float.c → libraries/ghc-internal/cbits/word2float.c - libraries/ghc-internal/configure.ac - libraries/ghc-internal/ghc-internal.buildinfo.in - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-bignum/GMP.rst → libraries/ghc-internal/gmp-backend.rst - libraries/ghc-bignum/gmp/ghc-gmp.h → libraries/ghc-internal/gmp/ghc-gmp.h - libraries/ghc-bignum/gmp/gmp-tarballs → libraries/ghc-internal/gmp/gmp-tarballs - libraries/ghc-bignum/include/HsIntegerGmp.h.in → libraries/ghc-internal/include/HsIntegerGmp.h.in - libraries/ghc-bignum/include/WordSize.h → libraries/ghc-internal/include/WordSize.h - libraries/ghc-internal/src/GHC/Internal/ArrayArray.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-bignum/src/GHC/Num/Backend.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Check.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Check.hs - libraries/ghc-bignum/src/GHC/Num/Backend/FFI.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/FFI.hs - libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/GMP.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Native.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Native.hs - libraries/ghc-bignum/src/GHC/Num/Backend/Selected.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Backend/Selected.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs - libraries/ghc-bignum/src/GHC/Num/BigNat.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/BigNat.hs-boot - libraries/ghc-bignum/src/GHC/Num/Integer.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghc-bignum/src/GHC/Num/Integer.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs-boot - libraries/ghc-bignum/src/GHC/Num/Natural.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs - libraries/ghc-bignum/src/GHC/Num/Natural.hs-boot → libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs-boot - libraries/ghc-bignum/src/GHC/Num/Primitives.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/Primitives.hs - libraries/ghc-bignum/src/GHC/Num/WordArray.hs → libraries/ghc-internal/src/GHC/Internal/Bignum/WordArray.hs - libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot - libraries/ghc-prim/GHC/CString.hs → libraries/ghc-internal/src/GHC/Internal/CString.hs - libraries/ghc-internal/src/GHC/Internal/Char.hs - libraries/ghc-prim/GHC/Classes.hs → libraries/ghc-internal/src/GHC/Internal/Classes.hs - libraries/ghc-internal/src/GHC/Internal/Conc/IO.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Signal.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs-boot - libraries/ghc-internal/src/GHC/Internal/ConsoleHandler.hsc - libraries/ghc-internal/src/GHC/Internal/Control/Arrow.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad/Zip.hs - libraries/ghc-internal/src/GHC/Internal/Data/Coerce.hs - libraries/ghc-internal/src/GHC/Internal/Data/Data.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Functor/Identity.hs - libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - + libraries/ghc-internal/src/GHC/Internal/Data/NonEmpty.hs - libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs - libraries/ghc-internal/src/GHC/Internal/Data/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Ord.hs - libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs - libraries/ghc-internal/src/GHC/Internal/Data/Version.hs-boot - libraries/ghc-prim/GHC/Debug.hs → libraries/ghc-internal/src/GHC/Internal/Debug.hs - libraries/ghc-internal/src/GHC/Internal/Encoding/UTF8.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs-boot - libraries/ghc-internal/src/GHC/Internal/Err.hs - libraries/ghc-internal/src/GHC/Internal/Event.hs - libraries/ghc-internal/src/GHC/Internal/Event/Arr.hs - libraries/ghc-internal/src/GHC/Internal/Event/IntTable.hs - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Event/TimerManager.hs - libraries/ghc-internal/src/GHC/Internal/Event/Windows/ConsoleEvent.hsc - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Float/ConversionUtils.hs - libraries/ghc-internal/src/GHC/Internal/Float/RealFracMethods.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/String/Encoding.hs - libraries/ghc-internal/src/GHC/Internal/Foreign/C/Types.hs - libraries/ghc-internal/src/GHC/Internal/Generics.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/Table.hs - libraries/ghc-internal/src/GHC/Internal/IO/Encoding/Iconv.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Flock.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/LinuxOFD.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs-boot - libraries/ghc-internal/src/GHC/Internal/IO/SubSystem.hs - libraries/ghc-internal/src/GHC/Internal/InfoProv/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Int.hs - libraries/ghc-internal/src/GHC/Internal/Integer.hs - libraries/ghc-internal/src/GHC/Internal/Integer/Logarithms.hs - libraries/ghc-internal/src/GHC/Internal/IsList.hs - libraries/ghc-internal/src/GHC/Internal/Ix.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs - libraries/ghc-internal/src/GHC/Internal/JS/Prim/Internal/Build.hs - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-prim/GHC/Magic.hs → libraries/ghc-internal/src/GHC/Internal/Magic.hs - libraries/ghc-prim/GHC/Magic/Dict.hs → libraries/ghc-internal/src/GHC/Internal/Magic/Dict.hs - libraries/ghc-internal/src/GHC/Internal/Maybe.hs - libraries/ghc-internal/src/GHC/Internal/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs - libraries/ghc-internal/src/GHC/Internal/Num.hs-boot - libraries/ghc-internal/src/GHC/Internal/Numeric/Natural.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-prim/GHC/Prim/Exception.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Exception.hs - libraries/ghc-prim/GHC/Prim/Ext.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Ext.hs - libraries/ghc-prim/GHC/Prim/Panic.hs → libraries/ghc-internal/src/GHC/Internal/Prim/Panic.hs - libraries/ghc-prim/GHC/Prim/PtrEq.hs → libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-internal/src/GHC/Internal/Read.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs-boot - libraries/ghc-internal/src/GHC/Internal/Records.hs - + libraries/ghc-internal/src/GHC/Internal/STM.hs - libraries/ghc-internal/src/GHC/Internal/Show.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs-boot - − libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hs-boot - libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs - libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Text/ParserCombinators/ReadP.hs - libraries/ghc-prim/GHC/Tuple.hs → libraries/ghc-internal/src/GHC/Internal/Tuple.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits.hs - libraries/ghc-internal/src/GHC/Internal/TypeLits/Internal.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats.hs - libraries/ghc-internal/src/GHC/Internal/TypeNats/Internal.hs - libraries/ghc-prim/GHC/Types.hs → libraries/ghc-internal/src/GHC/Internal/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghc-internal/src/GHC/Internal/Word.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/unicode_version - + libraries/ghc-prim/Dummy.hs - − libraries/ghc-prim/Setup.hs - libraries/ghc-prim/changelog.md - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/ghci/ghci.cabal.in - libraries/haskeline - libraries/hpc - libraries/integer-gmp/integer-gmp.cabal - libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs - libraries/os-string - libraries/parsec - libraries/process - libraries/semaphore-compat - libraries/stm - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - libraries/template-haskell/tests/all.T - + libraries/template-haskell/tests/dataToCodeQUnit.hs - + libraries/template-haskell/tests/dataToCodeQUnit.stdout - libraries/terminfo - libraries/text - libraries/transformers - libraries/unix - linters/lint-codes/LintCodes/Static.hs - linters/lint-codes/Main.hs - m4/find_ld.m4 - m4/fp_settings.m4 - m4/fptools_happy.m4 - m4/ghc_toolchain.m4 - rts/Capability.c - rts/Capability.h - rts/CheckUnload.c - rts/Disassembler.c - rts/Exception.cmm - rts/ExecPage.c - rts/IOManager.c - rts/IPE.c - rts/Interpreter.c - rts/Interpreter.h - rts/Linker.c - rts/Prelude.h - rts/PrimOps.cmm - rts/Printer.c - rts/ProfHeap.c - rts/RtsFlags.c - rts/RtsMain.c - rts/RtsSymbols.c - rts/Schedule.c - rts/StgCRunAsm.S - rts/StgMiscClosures.cmm - rts/StgStdThunks.cmm - rts/Task.h - rts/adjustor/NativeAmd64Asm.S - rts/adjustor/NativeAmd64MingwAsm.S - rts/adjustor/Nativei386.c - rts/adjustor/Nativei386Asm.S - rts/configure.ac - rts/external-symbols.list.in - rts/include/RtsAPI.h - rts/include/Stg.h - rts/include/rts/Bytecodes.h - rts/include/rts/Config.h - rts/include/rts/IPE.h - rts/include/rts/Threads.h - rts/include/rts/storage/HeapAlloc.h - rts/include/rts/storage/InfoTables.h - rts/include/stg/Prim.h - rts/js/environment.js - rts/js/mem.js - rts/js/string.js - rts/js/verify.js - rts/linker/MMap.c - rts/linker/MMap.h - rts/linker/MachO.c - rts/posix/ticker/TimerFd.c - rts/rts.cabal - rts/sm/Compact.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GCThread.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - rts/wasm/scheduler.cmm - rts/win32/libHSghc-prim.def - rts/xxhash.h - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/all.T - testsuite/tests/annotations/should_fail/annfail12.stderr - testsuite/tests/arityanal/should_run/T21694a.stderr - testsuite/tests/arityanal/should_run/T24296.stderr - testsuite/tests/array/should_run/arr003.stderr - testsuite/tests/array/should_run/arr004.stderr - testsuite/tests/array/should_run/arr007.stderr - testsuite/tests/array/should_run/arr008.stderr - testsuite/tests/arrows/should_compile/T21301.stderr - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stderr - testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout - testsuite/tests/backpack/reexport/bkpreex02.stderr - testsuite/tests/backpack/reexport/bkpreex03.stdout - testsuite/tests/backpack/should_compile/bkp09.stderr - testsuite/tests/backpack/should_compile/bkp14.stderr - testsuite/tests/backpack/should_compile/bkp15.stderr - testsuite/tests/backpack/should_compile/bkp31.stderr - testsuite/tests/backpack/should_compile/bkp32.stderr - testsuite/tests/backpack/should_compile/bkp47.stderr - testsuite/tests/backpack/should_compile/bkp51.stderr - testsuite/tests/backpack/should_compile/bkp61.stderr - testsuite/tests/backpack/should_fail/T19244a.stderr - testsuite/tests/backpack/should_fail/T19244b.stderr - testsuite/tests/backpack/should_fail/bkpfail04.stderr - testsuite/tests/backpack/should_fail/bkpfail06.stderr - testsuite/tests/backpack/should_fail/bkpfail07.stderr - testsuite/tests/backpack/should_fail/bkpfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail12.stderr - testsuite/tests/backpack/should_fail/bkpfail13.stderr - testsuite/tests/backpack/should_fail/bkpfail14.stderr - testsuite/tests/backpack/should_fail/bkpfail15.stderr - testsuite/tests/backpack/should_fail/bkpfail20.stderr - testsuite/tests/backpack/should_fail/bkpfail21.stderr - testsuite/tests/backpack/should_fail/bkpfail22.stderr - testsuite/tests/backpack/should_fail/bkpfail29.stderr - testsuite/tests/backpack/should_fail/bkpfail32.stderr - testsuite/tests/backpack/should_fail/bkpfail33.stderr - testsuite/tests/backpack/should_fail/bkpfail38.stderr - testsuite/tests/backpack/should_fail/bkpfail42.stderr - testsuite/tests/backpack/should_fail/bkpfail46.stderr - testsuite/tests/backpack/should_fail/bkpfail47.stderr - testsuite/tests/backpack/should_fail/bkpfail48.stderr - testsuite/tests/backpack/should_fail/bkpfail50.stderr - testsuite/tests/backpack/should_fail/bkpfail52.stderr - testsuite/tests/backpack/should_fail/bkpfail53.stderr - testsuite/tests/backpack/should_run/bkprun05.stderr - testsuite/tests/bytecode/T24634/Makefile - + testsuite/tests/bytecode/T25510/Makefile - + testsuite/tests/bytecode/T25510/T25510A.hs - + testsuite/tests/bytecode/T25510/T25510B.hs - + testsuite/tests/bytecode/T25510/all.T - + testsuite/tests/cmm/opt/T24556.cmm - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_compile/Makefile - testsuite/tests/codeGen/should_compile/T25166.stdout - testsuite/tests/codeGen/should_run/T16846.stderr - testsuite/tests/codeGen/should_run/T23146/all.T - testsuite/tests/codeGen/should_run/T25364.hs - testsuite/tests/codeGen/should_run/T25364.stdout - testsuite/tests/codeGen/should_run/T5626.stderr - testsuite/tests/codeGen/should_run/T7319.stderr - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/codeGen/should_run/cgrun016.stderr - testsuite/tests/codeGen/should_run/cgrun025.stderr - testsuite/tests/codeGen/should_run/cgrun045.stderr - testsuite/tests/codeGen/should_run/cgrun051.stderr - testsuite/tests/codeGen/should_run/cgrun059.stderr - testsuite/tests/concurrent/should_run/T13330.stderr - testsuite/tests/concurrent/should_run/T4030.stderr - testsuite/tests/concurrent/should_run/T5611.stderr - testsuite/tests/concurrent/should_run/T5611a.stderr - testsuite/tests/concurrent/should_run/T5866.stderr - testsuite/tests/concurrent/should_run/all.T - testsuite/tests/concurrent/should_run/allocLimit1.stderr - testsuite/tests/concurrent/should_run/allocLimit3.stderr - testsuite/tests/concurrent/should_run/conc009.stderr - testsuite/tests/concurrent/should_run/conc020.stderr - testsuite/tests/concurrent/should_run/conc021.stderr - testsuite/tests/concurrent/should_run/conc031.stderr - testsuite/tests/concurrent/should_run/conc040.stderr - testsuite/tests/concurrent/should_run/conc058.stderr - testsuite/tests/concurrent/should_run/conc064.stderr - testsuite/tests/concurrent/should_run/conc068.stderr - testsuite/tests/core-to-stg/T14895.stderr - testsuite/tests/core-to-stg/T24124.stderr - + testsuite/tests/core-to-stg/T25284/A.hs - + testsuite/tests/core-to-stg/T25284/B.hs - + testsuite/tests/core-to-stg/T25284/Cls.hs - + testsuite/tests/core-to-stg/T25284/Main.hs - + testsuite/tests/core-to-stg/T25284/T25284.stdout - + testsuite/tests/core-to-stg/T25284/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/cpranal/should_compile/T18109.stderr - testsuite/tests/cpranal/should_compile/T18174.stderr - testsuite/tests/deSugar/should_compile/T13208.stdout - testsuite/tests/deSugar/should_compile/T16615.stderr - testsuite/tests/deSugar/should_compile/T22719.stderr - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/deSugar/should_fail/DsStrictFail.stderr - testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr - testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr - testsuite/tests/deSugar/should_run/Or5.stderr - testsuite/tests/deSugar/should_run/T11193.stderr - testsuite/tests/deSugar/should_run/T11572.stderr - testsuite/tests/deSugar/should_run/T11601.stderr - testsuite/tests/deSugar/should_run/T20024.stderr - testsuite/tests/deSugar/should_run/dsrun005.stderr - testsuite/tests/deSugar/should_run/dsrun007.stderr - testsuite/tests/deSugar/should_run/dsrun008.stderr - testsuite/tests/default/DefaultImportFail01.stderr - testsuite/tests/default/DefaultImportFail02.stderr - testsuite/tests/default/DefaultImportFail03.stderr - testsuite/tests/default/DefaultImportFail04.stderr - testsuite/tests/default/DefaultImportFail05.stderr - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail07.stderr - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/dependent/ghci/T11786.stdout - testsuite/tests/dependent/should_fail/RAE_T32a.stderr - testsuite/tests/dependent/should_fail/T11407.stderr - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/dependent/should_fail/T14066c.stderr - testsuite/tests/dependent/should_fail/T14880.stderr - testsuite/tests/dependent/should_fail/TypeSkolEscape.stderr - testsuite/tests/deriving/should_compile/T11068_aggressive.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/deriving/should_compile/T14579.stderr - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/deriving/should_compile/T15798c.stderr - testsuite/tests/deriving/should_compile/T17240.stderr - testsuite/tests/deriving/should_compile/T20496.stderr - testsuite/tests/deriving/should_compile/deriving-inferred-ty-arg.stderr - testsuite/tests/deriving/should_compile/drv-empty-data.stderr - testsuite/tests/deriving/should_compile/drv-phantom.stderr - testsuite/tests/deriving/should_fail/T10598_fail1.stderr - testsuite/tests/deriving/should_fail/T10598_fail2.stderr - testsuite/tests/deriving/should_fail/T10684.stderr - testsuite/tests/deriving/should_fail/T12163.stderr - testsuite/tests/deriving/should_fail/T12801.stderr - testsuite/tests/deriving/should_fail/T14339.stderr - testsuite/tests/deriving/should_fail/T14365.stderr - testsuite/tests/deriving/should_fail/T14916.stderr - testsuite/tests/deriving/should_fail/T16181.stderr - testsuite/tests/deriving/should_fail/T16923.stderr - testsuite/tests/deriving/should_fail/T18127b.stderr - testsuite/tests/deriving/should_fail/T1830_1.stderr - testsuite/tests/deriving/should_fail/T19692.stderr - testsuite/tests/deriving/should_fail/T21302.stderr - testsuite/tests/deriving/should_fail/T22696b.stderr - testsuite/tests/deriving/should_fail/T23522.stderr - testsuite/tests/deriving/should_fail/T2701.stderr - testsuite/tests/deriving/should_fail/T2851.stderr - testsuite/tests/deriving/should_fail/T3101.stderr - testsuite/tests/deriving/should_fail/T3621.stderr - testsuite/tests/deriving/should_fail/T4846.stderr - testsuite/tests/deriving/should_fail/T5478.stderr - testsuite/tests/deriving/should_fail/T5686.stderr - testsuite/tests/deriving/should_fail/T5922.stderr - testsuite/tests/deriving/should_fail/T6147.stderr - testsuite/tests/deriving/should_fail/T7401_fail.stderr - testsuite/tests/deriving/should_fail/T7959.stderr - testsuite/tests/deriving/should_fail/T9071.stderr - testsuite/tests/deriving/should_fail/T9071_2.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail4.stderr - testsuite/tests/deriving/should_fail/deriving-via-fail5.stderr - testsuite/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor1.stderr - testsuite/tests/deriving/should_fail/drvfail-functor2.stderr - testsuite/tests/deriving/should_fail/drvfail001.stderr - testsuite/tests/deriving/should_fail/drvfail002.stderr - testsuite/tests/deriving/should_fail/drvfail003.stderr - testsuite/tests/deriving/should_fail/drvfail004.stderr - testsuite/tests/deriving/should_fail/drvfail005.stderr - testsuite/tests/deriving/should_fail/drvfail007.stderr - testsuite/tests/deriving/should_fail/drvfail012.stderr - testsuite/tests/deriving/should_fail/drvfail013.stderr - testsuite/tests/deriving/should_fail/drvfail016.stderr - testsuite/tests/deriving/should_run/T9576.stderr - testsuite/tests/dmdanal/should_compile/T10069.stderr - testsuite/tests/dmdanal/should_compile/T10482.stderr - testsuite/tests/dmdanal/should_compile/T10482a.stderr - testsuite/tests/dmdanal/should_compile/T13143.stderr - testsuite/tests/dmdanal/should_compile/T16029.stdout - testsuite/tests/dmdanal/should_compile/T18982.stderr - testsuite/tests/dmdanal/should_compile/T20510.stderr - testsuite/tests/dmdanal/should_compile/T20663.stderr - testsuite/tests/dmdanal/should_compile/T23398.stderr - testsuite/tests/dmdanal/should_run/T12368.stderr - testsuite/tests/dmdanal/should_run/T12368a.stderr - testsuite/tests/dmdanal/should_run/T13380.stderr - testsuite/tests/dmdanal/should_run/T13380d.stderr - testsuite/tests/dmdanal/should_run/T13380e.stderr - testsuite/tests/dmdanal/should_run/T23208.stderr - testsuite/tests/dmdanal/should_run/strun002.stderr - testsuite/tests/driver/Makefile - testsuite/tests/driver/T13914/T13914.stdout - testsuite/tests/driver/T20604/T20604.stdout - + testsuite/tests/driver/T25382.hs - testsuite/tests/driver/all.T - testsuite/tests/driver/fat-iface/fat001.stdout - testsuite/tests/driver/fat-iface/fat006.stdout - testsuite/tests/driver/j-space/jspace.hs - testsuite/tests/driver/json.stderr - testsuite/tests/driver/json_warn.hs - testsuite/tests/driver/json_warn.stderr - testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits002.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits003.stdout - testsuite/tests/driver/multipleHomeUnits/multipleHomeUnits_callstack.stderr - testsuite/tests/driver/recomp24656/recomp24656.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/exceptions/T25052.stdout - testsuite/tests/ffi/should_run/T7170.stderr - testsuite/tests/ffi/should_run/ffi008.stderr - testsuite/tests/ffi/should_run/fptrfail01.stderr - testsuite/tests/gadt/CasePrune.stderr - testsuite/tests/gadt/gadt10.stderr - testsuite/tests/generics/GenCannotDoRep0_0.stderr - testsuite/tests/generics/GenCannotDoRep0_1.stderr - testsuite/tests/generics/GenCannotDoRep1_0.stderr - testsuite/tests/generics/GenCannotDoRep1_1.stderr - testsuite/tests/generics/GenCannotDoRep1_3.stderr - testsuite/tests/generics/GenCannotDoRep1_4.stderr - testsuite/tests/generics/GenCannotDoRep1_6.stderr - testsuite/tests/generics/GenCannotDoRep1_7.stderr - testsuite/tests/generics/GenCannotDoRep1_8.stderr - testsuite/tests/generics/GenDerivOutput.stderr - testsuite/tests/generics/GenDerivOutput1_0.stderr - testsuite/tests/generics/GenDerivOutput1_1.stderr - testsuite/tests/generics/T10030.stdout - testsuite/tests/generics/T10604/T10604_deriving.stderr - testsuite/tests/generics/T10604/T10604_no_PolyKinds.stderr - testsuite/tests/generics/T5462No1.stderr - testsuite/tests/generics/T8468.stderr - testsuite/tests/ghc-api/T10942.hs - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/ghc-api/T20757.stderr - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr - testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr - testsuite/tests/ghc-api/exactprint/all.T - testsuite/tests/ghc-e/should_fail/T18441fail0.stderr - testsuite/tests/ghc-e/should_fail/T18441fail1.stderr - testsuite/tests/ghc-e/should_fail/T18441fail10.stderr - testsuite/tests/ghc-e/should_fail/T18441fail11.stderr - testsuite/tests/ghc-e/should_fail/T18441fail14.stderr - testsuite/tests/ghc-e/should_fail/T18441fail15.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail6.stderr - testsuite/tests/ghc-e/should_fail/T18441fail7.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr - testsuite/tests/ghc-e/should_fail/T23663.stderr - testsuite/tests/ghc-e/should_fail/T24172.stderr - testsuite/tests/ghc-e/should_fail/T9930fail.stderr - testsuite/tests/ghc-e/should_run/ghc-e005.stderr - testsuite/tests/ghci.debugger/scripts/break006.stderr - testsuite/tests/ghci.debugger/scripts/break009.stdout - testsuite/tests/ghci.debugger/scripts/break011.stdout - testsuite/tests/ghci.debugger/scripts/break016.stdout - testsuite/tests/ghci.debugger/scripts/break017.stdout - testsuite/tests/ghci.debugger/scripts/break024.stdout - testsuite/tests/ghci.debugger/scripts/break030.stdout - testsuite/tests/ghci/T16793/T16793.stdout - testsuite/tests/ghci/T18060/T18060.stdout - testsuite/tests/ghci/linking/T25240/all.T - testsuite/tests/ghci/linking/all.T - testsuite/tests/ghci/scripts/Defer02.stderr - testsuite/tests/ghci/scripts/ListTuplePunsPpr.stdout - testsuite/tests/ghci/scripts/T10059.stdout - testsuite/tests/ghci/scripts/T10501.stderr - testsuite/tests/ghci/scripts/T10508.stderr - testsuite/tests/ghci/scripts/T14676.stderr - testsuite/tests/ghci/scripts/T15325.stderr - testsuite/tests/ghci/scripts/T15941.stdout - testsuite/tests/ghci/scripts/T16575.stdout - testsuite/tests/ghci/scripts/T16804.stderr - testsuite/tests/ghci/scripts/T18755.stdout - testsuite/tests/ghci/scripts/T19310.stdout - testsuite/tests/ghci/scripts/T20150.stdout - testsuite/tests/ghci/scripts/T20627.stdout - testsuite/tests/ghci/scripts/T21294a.stdout - testsuite/tests/ghci/scripts/T23686.stderr - + testsuite/tests/ghci/scripts/T24459.script - + testsuite/tests/ghci/scripts/T24459.stdout - testsuite/tests/ghci/scripts/T4127.stdout - testsuite/tests/ghci/scripts/T4127a.stderr - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/T5557.stdout - testsuite/tests/ghci/scripts/T7627.stdout - testsuite/tests/ghci/scripts/T8113.stdout - testsuite/tests/ghci/scripts/T8469.stdout - testsuite/tests/ghci/scripts/T8535.stdout - testsuite/tests/ghci/scripts/T9181.stdout - testsuite/tests/ghci/scripts/T9293.stderr - testsuite/tests/ghci/scripts/T9881.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/ghci/scripts/ghci005.stdout - testsuite/tests/ghci/scripts/ghci011.stdout - testsuite/tests/ghci/scripts/ghci020.stdout - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci025.stdout - testsuite/tests/ghci/scripts/ghci055.stdout - testsuite/tests/ghci/scripts/ghci057.stderr - testsuite/tests/ghci/scripts/ghci059.stdout - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/ghci/scripts/ghci066.stdout - testsuite/tests/ghci/should_fail/T18027a.stderr - testsuite/tests/ghci/should_fail/T18052b.stderr - testsuite/tests/ghci/should_run/GHCiPrimCall/Makefile - testsuite/tests/ghci/should_run/Makefile - testsuite/tests/ghci/should_run/T10145.stdout - testsuite/tests/ghci/should_run/T13456.stdout - testsuite/tests/ghci/should_run/T15369.stdout - testsuite/tests/ghci/should_run/T16096.stdout - testsuite/tests/ghci/should_run/T18594.stdout - testsuite/tests/ghci/should_run/T21052.stdout - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/hpc/function/tough.stdout - testsuite/tests/hpc/function2/tough2.stdout - testsuite/tests/hpc/simple/tixs/T10529a.stderr - testsuite/tests/hpc/simple/tixs/T10529b.stderr - testsuite/tests/hpc/simple/tixs/T10529c.stderr - + testsuite/tests/indexed-types/should_compile/DataInstanceKindsDefaults.hs - testsuite/tests/indexed-types/should_compile/T11361a.stderr - + testsuite/tests/indexed-types/should_compile/T25611a.hs - + testsuite/tests/indexed-types/should_compile/T25611b.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs → testsuite/tests/indexed-types/should_compile/T25611c.hs - + testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/BadFamInstDecl.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4a.stderr - testsuite/tests/indexed-types/should_fail/ExplicitForAllFams4b.stderr - testsuite/tests/indexed-types/should_fail/HsBootFam.stderr - testsuite/tests/indexed-types/should_fail/NotRelaxedExamples.stderr - testsuite/tests/indexed-types/should_fail/Overlap3.stderr - testsuite/tests/indexed-types/should_fail/Overlap7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail12.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail13.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail14.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail1b.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail4.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail7.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T10817.stderr - testsuite/tests/indexed-types/should_fail/T10899.stderr - testsuite/tests/indexed-types/should_fail/T11136.stderr - testsuite/tests/indexed-types/should_fail/T11450.stderr - testsuite/tests/indexed-types/should_fail/T12041.stderr - testsuite/tests/indexed-types/should_fail/T12522a.stderr - testsuite/tests/indexed-types/should_fail/T12867.stderr - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T13971b.stderr - testsuite/tests/indexed-types/should_fail/T14230.stderr - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T15740.stderr - testsuite/tests/indexed-types/should_fail/T15870.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16110_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail1.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail2.stderr - testsuite/tests/indexed-types/should_fail/T16356_Fail3.stderr - testsuite/tests/indexed-types/should_fail/T17008a.stderr - testsuite/tests/indexed-types/should_fail/T18648.stderr - testsuite/tests/indexed-types/should_fail/T2157.stderr - testsuite/tests/indexed-types/should_fail/T2334A.stderr - testsuite/tests/indexed-types/should_fail/T3092.stderr - testsuite/tests/indexed-types/should_fail/T7536.stderr - testsuite/tests/indexed-types/should_fail/T7938.stderr - testsuite/tests/indexed-types/should_fail/T8368.stderr - testsuite/tests/indexed-types/should_fail/T8368a.stderr - testsuite/tests/indexed-types/should_fail/T9160.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/indexed-types/should_fail/T9896.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity1.stderr - testsuite/tests/indexed-types/should_fail/TyFamArity2.stderr - testsuite/tests/indexed-types/should_fail/TyFamUndec.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/javascript/Makefile - testsuite/tests/javascript/T23479_1.hs → testsuite/tests/javascript/T23479.hs - testsuite/tests/javascript/T23479_1.stdout → testsuite/tests/javascript/T23479.stdout - testsuite/tests/javascript/T23479_2.hs → testsuite/tests/javascript/T24744.hs - testsuite/tests/javascript/T23479_2.stdout → testsuite/tests/javascript/T24744.stdout - + testsuite/tests/javascript/T25633.hs - + testsuite/tests/javascript/T25633.stdout - testsuite/tests/javascript/all.T - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/lib/integer/T20066.stderr - + testsuite/tests/linear/should_compile/T25428.hs - + testsuite/tests/linear/should_compile/T25515.hs - testsuite/tests/linear/should_compile/all.T - testsuite/tests/linear/should_fail/LinearConfusedDollar.stderr - testsuite/tests/linear/should_fail/LinearErrOrigin.stderr - testsuite/tests/linear/should_fail/LinearLet10.stderr - testsuite/tests/linear/should_fail/LinearPartialSig.stderr - testsuite/tests/linear/should_fail/LinearVar.stderr - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/T20083.stderr - testsuite/tests/linear/should_fail/T21278.stderr - + testsuite/tests/linear/should_fail/T25185.hs - + testsuite/tests/linear/should_fail/T25185.stderr - testsuite/tests/linear/should_fail/all.T - + testsuite/tests/llvm/should_compile/T25606.hs - testsuite/tests/llvm/should_compile/all.T - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/mdo/should_fail/mdofail006.stderr - testsuite/tests/module/mod110.stderr - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod53.stderr - testsuite/tests/module/mod54.stderr - testsuite/tests/module/mod55.stderr - testsuite/tests/module/mod56.stderr - testsuite/tests/module/mod87.stderr - testsuite/tests/module/mod97.stderr - testsuite/tests/numeric/should_compile/T14170.stdout - testsuite/tests/numeric/should_compile/T14465.stdout - testsuite/tests/numeric/should_compile/T19892.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - + testsuite/tests/numeric/should_run/T25653.hs - + testsuite/tests/numeric/should_run/T25653.stdout - testsuite/tests/numeric/should_run/all.T - testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr - testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr - testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20718.stderr - testsuite/tests/parser/should_compile/T20846.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail2.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail3.stderr - testsuite/tests/parser/should_fail/ListTuplePunsFail4.stderr - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.hs - + testsuite/tests/parser/should_fail/MultilineStringsUnterminated.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr - testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.hs - testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr - testsuite/tests/parser/should_fail/T18251e.stderr - + testsuite/tests/parser/should_fail/T25530.hs - + testsuite/tests/parser/should_fail/T25530.stderr - testsuite/tests/parser/should_fail/all.T - testsuite/tests/parser/should_fail/readFail035.stderr - testsuite/tests/parser/should_run/NumericUnderscores0.hs - testsuite/tests/parser/should_run/NumericUnderscores0.stdout - testsuite/tests/parser/should_run/RecordDotSyntax1.hs - + testsuite/tests/parser/should_run/T25375.hs - + testsuite/tests/parser/should_run/T25375.stdout - + testsuite/tests/parser/should_run/T25609.hs - + testsuite/tests/parser/should_run/T25609.stdout - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/partial-sigs/should_compile/TypedSplice.stderr - testsuite/tests/partial-sigs/should_fail/ExtraConstraintsWildcardInTypeSpliceUsed.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardInTypeSplice.stderr - testsuite/tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr - testsuite/tests/partial-sigs/should_fail/T10999.stderr - testsuite/tests/partial-sigs/should_fail/T13324_fail2.stderr - testsuite/tests/patsyn/should_compile/T13350/Makefile - testsuite/tests/patsyn/should_run/ghci.stderr - testsuite/tests/perf/compiler/MultiLayerModulesTH_Make.stderr - testsuite/tests/perf/compiler/MultiLayerModulesTH_OneShot.stderr - testsuite/tests/perf/compiler/T11068.stdout - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/perf/size/all.T - testsuite/tests/plugins/plugins02.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/pmcheck/should_compile/T12957.stderr - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/polykinds/T10451.stderr - testsuite/tests/polykinds/T11203.stderr - testsuite/tests/polykinds/T11399.stderr - testsuite/tests/polykinds/T11821a.stderr - testsuite/tests/polykinds/T14110.stderr - testsuite/tests/polykinds/T14450.stderr - testsuite/tests/polykinds/T14555.stderr - testsuite/tests/polykinds/T14563.stderr - testsuite/tests/polykinds/T14580.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T15795.stderr - testsuite/tests/polykinds/T15795a.stderr - testsuite/tests/polykinds/T16762.stderr - testsuite/tests/polykinds/T16762a.stderr - testsuite/tests/polykinds/T16762c.stderr - testsuite/tests/polykinds/T17963.stderr - testsuite/tests/polykinds/T18451.stderr - testsuite/tests/polykinds/T22742.stderr - + testsuite/tests/polykinds/T25661.hs - + testsuite/tests/polykinds/T25661.stderr - testsuite/tests/polykinds/T5716a.stderr - testsuite/tests/polykinds/T7805.stderr - testsuite/tests/polykinds/all.T - testsuite/tests/primops/should_run/T10481.stderr - libraries/ghc-prim/tests/T6026.hs → testsuite/tests/primops/should_run/T6026.hs - libraries/ghc-prim/tests/T6026.stdout → testsuite/tests/primops/should_run/T6026.stdout - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/T15761.stderr - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/printer/Test20297.stdout - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/profiling/should_run/T25675.hs - + testsuite/tests/profiling/should_run/T25675.stdout - testsuite/tests/profiling/should_run/all.T - testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - testsuite/tests/profiling/should_run/callstack001.stdout - testsuite/tests/profiling/should_run/ioprof.prof.sample - testsuite/tests/profiling/should_run/toplevel_scc_1.prof.sample - testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quasiquotation/all.T - testsuite/tests/quotes/T10384.stderr - testsuite/tests/quotes/T18263.stderr - testsuite/tests/quotes/TH_double_splice.stderr - testsuite/tests/quotes/TH_localname.stderr - testsuite/tests/quotes/TH_ppr1.stdout - testsuite/tests/quotes/TTH_top_splice.stderr - testsuite/tests/rebindable/RebindableFailA.stderr - + testsuite/tests/rename/should_compile/ReExportTuples.hs - + testsuite/tests/rename/should_compile/T25182.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/Or3.hs - testsuite/tests/rename/should_fail/Or3.stderr - testsuite/tests/rename/should_fail/T12686a.stderr - testsuite/tests/rename/should_fail/T12686c.stderr - testsuite/tests/rename/should_fail/T15828.stderr - testsuite/tests/rename/should_fail/T16635b.stderr - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T18740a.stderr - testsuite/tests/rename/should_fail/T19843h.stderr - testsuite/tests/rename/should_fail/T22478b.hs - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T23740i.stderr - + testsuite/tests/rename/should_fail/T25437.hs - + testsuite/tests/rename/should_fail/T25437.stderr - testsuite/tests/rename/should_fail/T5001b.stderr - testsuite/tests/rename/should_fail/T6148d.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBackpack3.stderr - testsuite/tests/rep-poly/RepPolyInferPatBind.stderr - testsuite/tests/rep-poly/RepPolyInferPatSyn.stderr - testsuite/tests/rep-poly/RepPolyMcGuard.stderr - testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr - testsuite/tests/rep-poly/RepPolyTuple3.stderr - testsuite/tests/rep-poly/T12709.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/T23153.stderr - + testsuite/tests/rep-poly/T23153b.hs - testsuite/tests/rep-poly/T23154.stderr - + testsuite/tests/rep-poly/T23883a.hs - + testsuite/tests/rep-poly/T23883a.stderr - + testsuite/tests/rep-poly/T23883b.hs - + testsuite/tests/rep-poly/T23883b.stderr - + testsuite/tests/rep-poly/T23883c.hs - + testsuite/tests/rep-poly/T23883c.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rep-poly/all.T - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles13.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/roles/should_fail/Roles10.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T13832.stderr - + testsuite/tests/rts/T14497-compact.hs - + testsuite/tests/rts/T14497-compact.stdout - testsuite/tests/rts/T1791/Makefile - + testsuite/tests/rts/T20201a.hs - + testsuite/tests/rts/T20201a.stderr - + testsuite/tests/rts/T20201b.hs - + testsuite/tests/rts/T20201b.stderr - + testsuite/tests/rts/T25560.hs - testsuite/tests/rts/T2783.stderr - testsuite/tests/rts/T7087.stderr - testsuite/tests/rts/T7636.stderr - testsuite/tests/rts/all.T - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/continuations/cont_missing_prompt_err.stderr - testsuite/tests/rts/ipe/IpeStats/Makefile - testsuite/tests/rts/ipe/T24005/t24005.hs - testsuite/tests/rts/linker/all.T - testsuite/tests/runghc/T7859.stderr - testsuite/tests/runghc/T7859.stderr-mingw32 - testsuite/tests/safeHaskell/check/pkg01/all.T - testsuite/tests/safeHaskell/ghci/p12.stderr - testsuite/tests/safeHaskell/ghci/p5.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang09.stderr - testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr - testsuite/tests/safeHaskell/unsafeLibs/T21433.stderr - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/Orphans.stdout - + testsuite/tests/simd/should_run/T25455.hs - + testsuite/tests/simd/should_run/T25455.stdout - + testsuite/tests/simd/should_run/T25486.hs - + testsuite/tests/simd/should_run/T25486.stdout - + testsuite/tests/simd/should_run/T25561.hs - + testsuite/tests/simd/should_run/T25561.stdout - + testsuite/tests/simd/should_run/T25658.hs - + testsuite/tests/simd/should_run/T25658.stdout - + testsuite/tests/simd/should_run/T25659.hs - + testsuite/tests/simd/should_run/T25659.stdout - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/int16x8_basic.hs - + testsuite/tests/simd/should_run/int16x8_basic.stdout - + testsuite/tests/simd/should_run/int16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/int16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/int32x4_basic.hs - + testsuite/tests/simd/should_run/int32x4_basic.stdout - + testsuite/tests/simd/should_run/int32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/int32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/int64x2_basic.hs - + testsuite/tests/simd/should_run/int64x2_basic.stdout - + testsuite/tests/simd/should_run/int64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/int64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/int8x16_basic.hs - + testsuite/tests/simd/should_run/int8x16_basic.stdout - + testsuite/tests/simd/should_run/int8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/int8x16_basic_baseline.stdout - + testsuite/tests/simd/should_run/simd_insert.hs - + testsuite/tests/simd/should_run/simd_insert.stdout - + testsuite/tests/simd/should_run/simd_insert_array.hs - + testsuite/tests/simd/should_run/simd_insert_array.stdout - + testsuite/tests/simd/should_run/simd_insert_array_baseline.hs - + testsuite/tests/simd/should_run/simd_insert_array_baseline.stdout - + testsuite/tests/simd/should_run/simd_insert_baseline.hs - + testsuite/tests/simd/should_run/simd_insert_baseline.stdout - + testsuite/tests/simd/should_run/word16x8_basic.hs - + testsuite/tests/simd/should_run/word16x8_basic.stdout - + testsuite/tests/simd/should_run/word16x8_basic_baseline.hs - + testsuite/tests/simd/should_run/word16x8_basic_baseline.stdout - + testsuite/tests/simd/should_run/word32x4_basic.hs - + testsuite/tests/simd/should_run/word32x4_basic.stdout - + testsuite/tests/simd/should_run/word32x4_basic_baseline.hs - + testsuite/tests/simd/should_run/word32x4_basic_baseline.stdout - + testsuite/tests/simd/should_run/word64x2_basic.hs - + testsuite/tests/simd/should_run/word64x2_basic.stdout - + testsuite/tests/simd/should_run/word64x2_basic_baseline.hs - + testsuite/tests/simd/should_run/word64x2_basic_baseline.stdout - + testsuite/tests/simd/should_run/word8x16_basic.hs - + testsuite/tests/simd/should_run/word8x16_basic.stdout - + testsuite/tests/simd/should_run/word8x16_basic_baseline.hs - + testsuite/tests/simd/should_run/word8x16_basic_baseline.stdout - testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr - testsuite/tests/simplCore/should_compile/T13156.stdout - testsuite/tests/simplCore/should_compile/T14978.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T17673.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18078.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - testsuite/tests/simplCore/should_compile/T20040.stderr - testsuite/tests/simplCore/should_compile/T21286.stderr - testsuite/tests/simplCore/should_compile/T21851_2.stderr - testsuite/tests/simplCore/should_compile/T22375.stderr - testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr - testsuite/tests/simplCore/should_compile/T22428.stderr - testsuite/tests/simplCore/should_compile/T23083.stderr - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - testsuite/tests/simplCore/should_compile/T24662.stderr - + testsuite/tests/simplCore/should_compile/T25713.hs - + testsuite/tests/simplCore/should_compile/T25713.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4201.stdout - testsuite/tests/simplCore/should_compile/T4306.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/T5366.stdout - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/T7865.stdout - testsuite/tests/simplCore/should_compile/T8274.stdout - testsuite/tests/simplCore/should_compile/T8832.stdout - testsuite/tests/simplCore/should_compile/T9400.stderr - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/noinline01.stderr - testsuite/tests/simplCore/should_compile/par01.stderr - testsuite/tests/simplCore/should_compile/rule2.stderr - testsuite/tests/simplCore/should_compile/simpl016.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/simplCore/should_fail/T7411.stderr - testsuite/tests/simplCore/should_run/T16066.stderr - testsuite/tests/simplCore/should_run/T16893/T16893.stderr - testsuite/tests/simplCore/should_run/T457.stderr - testsuite/tests/simplCore/should_run/T5587.stderr - testsuite/tests/simplCore/should_run/T5625.stderr - testsuite/tests/simplCore/should_run/T7924.stderr - testsuite/tests/simplStg/should_compile/T15226b.stderr - testsuite/tests/simplStg/should_compile/T19717.stderr - testsuite/tests/th/ClosedFam1TH.stderr - + testsuite/tests/th/EmptyGuard.hs - + testsuite/tests/th/EmptyGuard.stderr - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - + testsuite/tests/th/FunNameTH.hs - testsuite/tests/th/ListTuplePunsTH.stderr - testsuite/tests/th/T10279.hs - testsuite/tests/th/T10279.stderr - testsuite/tests/th/T10734.stdout - testsuite/tests/th/T10796b.stderr - testsuite/tests/th/T10828.stderr - testsuite/tests/th/T10891.stderr - testsuite/tests/th/T10945.stderr - testsuite/tests/th/T10946.stderr - testsuite/tests/th/T11145.stderr - testsuite/tests/th/T11341.stderr - testsuite/tests/th/T11345.stdout - testsuite/tests/th/T11452.stderr - testsuite/tests/th/T12045TH2.stderr - testsuite/tests/th/T12387a.stderr - testsuite/tests/th/T12403.stdout - testsuite/tests/th/T12478_1.stdout - testsuite/tests/th/T12478_4.stderr - testsuite/tests/th/T12646.stderr - testsuite/tests/th/T13776.hs - testsuite/tests/th/T13776.stderr - testsuite/tests/th/T13837.stderr - testsuite/tests/th/T13887.stdout - testsuite/tests/th/T14060.stdout - testsuite/tests/th/T14627.stderr - testsuite/tests/th/T15360b.stderr - testsuite/tests/th/T15433a.stderr - testsuite/tests/th/T15738.stderr - testsuite/tests/th/T15792.stderr - testsuite/tests/th/T15843.stdout - testsuite/tests/th/T16976.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T16980.stderr - testsuite/tests/th/T17296.stderr - testsuite/tests/th/T17380.stderr - testsuite/tests/th/T17804.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T18102.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T1849.stdout - testsuite/tests/th/T18740d.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T19373.stdout - testsuite/tests/th/T19470.stderr - testsuite/tests/th/T20711.stdout - testsuite/tests/th/T20842.stdout - testsuite/tests/th/T20868.stdout - testsuite/tests/th/T20884.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T2222.stderr - testsuite/tests/th/T22559a.stderr - testsuite/tests/th/T22559b.stderr - testsuite/tests/th/T22559c.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23927.stdout - testsuite/tests/th/T24111.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T24997.stdout - + testsuite/tests/th/T25174.hs - + testsuite/tests/th/T25179.hs - testsuite/tests/th/T25256.stdout - testsuite/tests/th/T2700.stderr - testsuite/tests/th/T4135.stderr - testsuite/tests/th/T5037.stderr - testsuite/tests/th/T5358.stderr - testsuite/tests/th/T5976.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/T7477.stderr - testsuite/tests/th/T8577.stderr - testsuite/tests/th/T8625.stdout - testsuite/tests/th/T8761.stderr - testsuite/tests/th/T8953.stderr - testsuite/tests/th/T8987.stderr - testsuite/tests/th/T9262.stderr - testsuite/tests/th/T9692.stderr - testsuite/tests/th/TH_NestedSplicesFail1.stderr - testsuite/tests/th/TH_NestedSplicesFail2.stderr - testsuite/tests/th/TH_NestedSplicesFail3.stderr - testsuite/tests/th/TH_NestedSplicesFail4.stderr - testsuite/tests/th/TH_NestedSplicesFail5.stderr - testsuite/tests/th/TH_NestedSplicesFail6.stderr - testsuite/tests/th/TH_NestedSplicesFail7.stderr - testsuite/tests/th/TH_NestedSplicesFail8.stderr - testsuite/tests/th/TH_PromotedList.stderr - testsuite/tests/th/TH_PromotedTuple.stderr - testsuite/tests/th/TH_RichKinds.stderr - testsuite/tests/th/TH_RichKinds2.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/th/TH_TyInstWhere2.stderr - testsuite/tests/th/TH_exn2.stderr - testsuite/tests/th/TH_foreignCallingConventions.stderr - testsuite/tests/th/TH_fun_par.stderr - testsuite/tests/th/TH_implicitParams.stdout - testsuite/tests/th/TH_reifyDecl1.stderr - testsuite/tests/th/TH_reifyInstances.stderr - testsuite/tests/th/TH_reifyLinear.stderr - testsuite/tests/th/TH_reifyLocalDefs.stderr - testsuite/tests/th/TH_reifyLocalDefs2.stderr - testsuite/tests/th/TH_reifyMkName.stderr - testsuite/tests/th/TH_repGuard.stderr - testsuite/tests/th/TH_repPatSigTVar.stderr - testsuite/tests/th/TH_repPrim.stderr - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_tuple1.stdout - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/all.T - testsuite/tests/th/overloaded/TH_overloaded_csp.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - + testsuite/tests/th/wasm/T25473A.hs - + testsuite/tests/th/wasm/T25473B.hs - + testsuite/tests/th/wasm/all.T - testsuite/tests/type-data/should_run/T22332a.stderr - testsuite/tests/typecheck/no_skolem_info/T10946_sk.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClasses.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesCore.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesEffects.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesReader.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesState.hs - + testsuite/tests/typecheck/should_compile/T16234/ControlMonadPrimitive.hs - + testsuite/tests/typecheck/should_compile/T16234/DataPeano.hs - + testsuite/tests/typecheck/should_compile/T16234/Main.hs - + testsuite/tests/typecheck/should_compile/T16234/Makefile - + testsuite/tests/typecheck/should_compile/T16234/all.T - testsuite/tests/typecheck/should_compile/T17343.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/T22141a.stderr - testsuite/tests/typecheck/should_compile/T22141b.stderr - testsuite/tests/typecheck/should_compile/T22141c.stderr - testsuite/tests/typecheck/should_compile/T22141d.stderr - testsuite/tests/typecheck/should_compile/T22141e.stderr - + testsuite/tests/typecheck/should_compile/T25180.hs - + testsuite/tests/typecheck/should_compile/T25180.stderr - + testsuite/tests/typecheck/should_compile/T25597.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef02.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef04.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef05.stderr - testsuite/tests/typecheck/should_fail/AssocTyDef06.stderr - testsuite/tests/typecheck/should_fail/ErrorIndexLinks.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity7.stderr - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T11347.stderr - testsuite/tests/typecheck/should_fail/T11974b.stderr - testsuite/tests/typecheck/should_fail/T12966.stderr - testsuite/tests/typecheck/should_fail/T13292.stderr - testsuite/tests/typecheck/should_fail/T14048a.stderr - testsuite/tests/typecheck/should_fail/T14048c.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr - testsuite/tests/typecheck/should_fail/T15067.stderr - testsuite/tests/typecheck/should_fail/T15474.stderr - testsuite/tests/typecheck/should_fail/T15648.stderr - testsuite/tests/typecheck/should_fail/T15648a.hs - testsuite/tests/typecheck/should_fail/T15807.stderr - testsuite/tests/typecheck/should_fail/T15816.stderr - testsuite/tests/typecheck/should_fail/T15883b.stderr - testsuite/tests/typecheck/should_fail/T15883c.stderr - testsuite/tests/typecheck/should_fail/T15883d.stderr - testsuite/tests/typecheck/should_fail/T15883e.stderr - testsuite/tests/typecheck/should_fail/T16829b.stderr - testsuite/tests/typecheck/should_fail/T17021b.stderr - testsuite/tests/typecheck/should_fail/T17567.stderr - testsuite/tests/typecheck/should_fail/T17567StupidTheta.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T17940.stderr - testsuite/tests/typecheck/should_fail/T18640c.stderr - testsuite/tests/typecheck/should_fail/T18714.stderr - testsuite/tests/typecheck/should_fail/T18723a.stderr - testsuite/tests/typecheck/should_fail/T18723c.stderr - testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T20043.stderr - testsuite/tests/typecheck/should_fail/T20443b.hs - testsuite/tests/typecheck/should_fail/T20443b.stderr - testsuite/tests/typecheck/should_fail/T20768_fail.stderr - testsuite/tests/typecheck/should_fail/T20873c.stderr - testsuite/tests/typecheck/should_fail/T20873d.stderr - testsuite/tests/typecheck/should_fail/T21447.stderr - testsuite/tests/typecheck/should_fail/T22478c.hs - testsuite/tests/typecheck/should_fail/T22478c.stderr - testsuite/tests/typecheck/should_fail/T22707.stderr - testsuite/tests/typecheck/should_fail/T23734.stderr - testsuite/tests/typecheck/should_fail/T23739b.stderr - testsuite/tests/typecheck/should_fail/T23739c.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - testsuite/tests/typecheck/should_fail/T23778.stderr - testsuite/tests/typecheck/should_fail/T24298.stderr - testsuite/tests/typecheck/should_fail/T24553.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/T5095.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/T7279.stderr - testsuite/tests/typecheck/should_fail/T8262.stderr - testsuite/tests/typecheck/should_fail/T8514.stderr - testsuite/tests/typecheck/should_fail/T9305.stderr - testsuite/tests/typecheck/should_fail/T9858a.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_ExistentialEscape.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearMultiAppPat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearMultiPat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearSinglePat.hs - testsuite/tests/typecheck/should_fail/TyAppPat_NonlinearSinglePat.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_Nonmatching.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBinding.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.hs - testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.hs - testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail1.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInfinite.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesNotEnabled.stderr - − testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/VisFlag2.stderr - testsuite/tests/typecheck/should_fail/VisFlag5.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/typecheck/should_fail/tcfail028.stderr - testsuite/tests/typecheck/should_fail/tcfail046.stderr - testsuite/tests/typecheck/should_fail/tcfail070.stderr - testsuite/tests/typecheck/should_fail/tcfail072.stderr - testsuite/tests/typecheck/should_fail/tcfail073.stderr - testsuite/tests/typecheck/should_fail/tcfail079.stderr - testsuite/tests/typecheck/should_fail/tcfail086.stderr - testsuite/tests/typecheck/should_fail/tcfail097.stderr - testsuite/tests/typecheck/should_fail/tcfail117.stderr - testsuite/tests/typecheck/should_fail/tcfail118.stderr - testsuite/tests/typecheck/should_fail/tcfail123.stderr - testsuite/tests/typecheck/should_fail/tcfail132.stderr - testsuite/tests/typecheck/should_fail/tcfail136.stderr - testsuite/tests/typecheck/should_fail/tcfail146.stderr - testsuite/tests/typecheck/should_fail/tcfail147.stderr - testsuite/tests/typecheck/should_fail/tcfail148.stderr - testsuite/tests/typecheck/should_fail/tcfail151.stderr - testsuite/tests/typecheck/should_fail/tcfail159.stderr - testsuite/tests/typecheck/should_fail/tcfail162.stderr - testsuite/tests/typecheck/should_fail/tcfail169.stderr - testsuite/tests/typecheck/should_fail/tcfail199.stderr - testsuite/tests/typecheck/should_fail/tcfail200.stderr - testsuite/tests/typecheck/should_fail/tcfail224.stderr - testsuite/tests/typecheck/should_run/T10284.stderr - testsuite/tests/typecheck/should_run/T11049.stderr - testsuite/tests/typecheck/should_run/T11715.stderr - testsuite/tests/typecheck/should_run/T13838.stderr - testsuite/tests/typecheck/should_run/T21973a.stderr - testsuite/tests/typecheck/should_run/T22510.stdout - testsuite/tests/typecheck/should_run/T9497a-run.stderr - testsuite/tests/typecheck/should_run/T9497b-run.stderr - testsuite/tests/typecheck/should_run/T9497c-run.stderr - testsuite/tests/unboxedsums/T12711.stdout - testsuite/tests/unboxedsums/T20858.stdout - testsuite/tests/unboxedsums/T20858b.stdout - testsuite/tests/unlifted-datatypes/should_fail/UnlDataInvalidResKind1.stderr - testsuite/tests/unlifted-datatypes/should_run/UnlGadt1.stderr - testsuite/tests/unlifted-datatypes/should_run/all.T - testsuite/tests/unsatisfiable/T14339_Unsat.stderr - testsuite/tests/unsatisfiable/T23816.stderr - testsuite/tests/unsatisfiable/UnsatDefer.stderr - testsuite/tests/vdq-rta/should_compile/T22326_th_pprint1.stderr - testsuite/tests/vdq-rta/should_compile/T23739_th_pprint1.stderr - testsuite/tests/warnings/should_compile/DerivingTypeable.stderr - testsuite/tests/warnings/should_compile/T15460.stderr-ws-32 - testsuite/tests/warnings/should_compile/T15460.stderr-ws-64 - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/T24396.stderr - testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs - testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.hs - testsuite/tests/wcompat-warnings/Template.hs - testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Parsers.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/Bug923.html - utils/haddock/html-test/ref/Instances.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - utils/hsc2hs - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/297ce2a3e2c7cc726bbb9a0722c05d2ce5a20c00...79ebe7230b38e6478b1d516b54cbd1d104396f40 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/297ce2a3e2c7cc726bbb9a0722c05d2ce5a20c00...79ebe7230b38e6478b1d516b54cbd1d104396f40 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/ea5da9d0/attachment-0001.html> From gitlab at gitlab.haskell.org Mon Mar 10 23:40:35 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Mon, 10 Mar 2025 19:40:35 -0400 Subject: [Git][ghc/ghc][wip/T25647] handle explicit implicit binders seperately Message-ID: <67cf7873a90f8_32071f1808a838223@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 881da0f0 by Patrick at 2025-03-11T07:40:26+08:00 handle explicit implicit binders seperately - - - - - 3 changed files: - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -72,7 +72,7 @@ module GHC.Tc.Gen.HsType ( HoleMode(..), -- Utils - tyLitFromLit, tyLitFromOverloadedLit, + tyLitFromLit, tyLitFromOverloadedLit, expliciteOuterTyVars, impliciteOuterTyVars, ) where @@ -3281,6 +3281,19 @@ outerTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] outerTyVars (HsOuterImplicit { hso_ximplicit = tvs }) = tvs outerTyVars (HsOuterExplicit { hso_xexplicit = tvbs }) = binderVars tvbs +expliciteOuterTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] +-- The returned [TcTyVar] is not necessarily in dependency order +-- at least for the HsOuterImplicit case +expliciteOuterTyVars (HsOuterImplicit {}) = [] +expliciteOuterTyVars (HsOuterExplicit { hso_xexplicit = tvbs }) = binderVars tvbs + +impliciteOuterTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] +-- The returned [TcTyVar] is not necessarily in dependency order +impliciteOuterTyVars (HsOuterImplicit { hso_ximplicit = tvs }) = tvs +impliciteOuterTyVars (HsOuterExplicit {}) = [] + + + --------------- outerTyVarBndrs :: HsOuterTyVarBndrs Specificity GhcTc -> [InvisTVBinder] outerTyVarBndrs (HsOuterImplicit{hso_ximplicit = imp_tvs}) = [Bndr tv SpecifiedSpec | tv <- imp_tvs] ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -21,7 +21,7 @@ module GHC.Tc.TyCl ( tcFamTyPats, tcTyFamInstEqn, tcAddOpenTyFamInstCtxt, tcMkDataFamInstCtxt, tcAddDataFamInstCtxt, unravelFamInstPats, addConsistencyConstraints, - checkFamTelescope + checkFamTelescope, tcFamInsLHSBinders ) where import GHC.Prelude @@ -39,7 +39,7 @@ import GHC.Tc.Solver( pushLevelAndSolveEqualities, pushLevelAndSolveEqualitiesX import GHC.Tc.Utils.Monad import GHC.Tc.Utils.Env import GHC.Tc.Utils.Unify( unifyType, emitResidualTvConstraint ) -import GHC.Tc.Types.Constraint( emptyWC ) +import GHC.Tc.Types.Constraint( emptyWC, WantedConstraints ) import GHC.Tc.Validity import GHC.Tc.Zonk.Type import GHC.Tc.Zonk.TcType @@ -248,6 +248,51 @@ tcTyClGroup (TyClGroup { group_tyclds = tyclds ; return (gbl_env'', inst_info, deriv_info, th_bndrs' `plusNameEnv` th_bndrs) } + +-- tcFamInsLHSBinders :: FamEqn TyVar Name -> TcM [TyVar] +tcFamInsLHSBinders :: TcLevel -> SkolemInfo -> HsOuterFamEqnTyVarBndrs GhcTc -> HsOuterFamEqnTyVarBndrs GhcRn + -> [TcTyVar] -> Type -> WantedConstraints -> IOEnv (Env TcGblEnv TcLclEnv) ([TyCoVar], [TcTyVar]) +tcFamInsLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted = do + -- This code (and the stuff immediately above) is very similar + -- to that in tcTyFamInstEqnGuts. Maybe we should abstract the + -- common code; but for the moment I concluded that it's + -- clearer to duplicate it. Still, if you fix a bug here, + -- check there too! + + -- See Note [Type variables in type families instance decl] + ; let outer_exp_tvs = scopedSort $ expliciteOuterTyVars outer_bndrs + ; let outer_imp_tvs = impliciteOuterTyVars outer_bndrs + ; checkFamTelescope tclvl hs_outer_bndrs outer_exp_tvs + ; outer_imp_wc_tvs <- liftZonkM $ zonkTcTyVarsToTcTyVarsMaybe $ outer_imp_tvs ++ wcs + -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] + ; (dvs, cqdvs) <- candidateQTyVarsWithBinders (outer_imp_wc_tvs ++ outer_exp_tvs) lhs_ty + ; qtvs <- quantifyTyVarsWithBinders cqdvs skol_info dvs + -- Have to make a same defaulting choice for reuslt kind here + -- and the `kindGeneralizeAll` in `tcConDecl`. + -- see (GT4) in + -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] + + ; let final_tvs = scopedSort (qtvs ++ outer_exp_tvs) + + ; traceTc "tcFamInsLHSBinders" $ + vcat [ + -- ppr fam_tc + text "lhs_ty:" <+> ppr lhs_ty + , text "final_tvs:" <+> pprTyVars final_tvs + , text "outer_imp_tvs:" <+> pprTyVars outer_imp_tvs + , text "outer_exp_tvs:" <+> pprTyVars outer_exp_tvs + , text "wcs:" <+> pprTyVars wcs + , text "outer_imp_wc_tvs:" <+> pprTyVars outer_imp_wc_tvs + , text "outer_bndrs:" <+> ppr outer_bndrs + , text "qtvs:" <+> pprTyVars qtvs + , text "cqdvs:" <+> pprTyVars cqdvs + , text "dvs:" <+> ppr dvs + ] + -- This scopedSort is important: the qtvs may be /interleaved/ with + -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] + ; reportUnsolvedEqualities skol_info final_tvs tclvl wanted + return (final_tvs, qtvs) + -- Gives the kind for every TyCon that has a standalone kind signature type KindSigEnv = NameEnv Kind @@ -3439,37 +3484,8 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty ; traceTc "tcTyFamInstEqnGuts 0" (ppr outer_bndrs $$ ppr skol_info) - -- See Note [Type variables in type families instance decl] - ; let outer_tvs = (outerTyVars outer_bndrs) - ; checkFamTelescope tclvl outer_hs_bndrs outer_tvs - ; outer_tvs <- liftZonkM $ zonkTcTyVarsToTcTyVarsMaybe $ outer_tvs ++ wcs - - ; traceTc "tcTyFamInstEqnGuts 1" ( - vcat [ - text "wildcards" <+> ppr wcs, - text "outer_tvs" <+> pprTyVars outer_tvs, - ppr skol_info - ] - ) - - -- This code (and the stuff immediately above) is very similar - -- to that in tcDataFamInstHeader. Maybe we should abstract the - -- common code; but for the moment I concluded that it's - -- clearer to duplicate it. Still, if you fix a bug here, - -- check there too! - - -- See Note [Generalising in tcTyFamInstEqnGuts] - ; (dvs, cqdvs) <- candidateQTyVarsWithBinders outer_tvs lhs_ty - ; qtvs <- quantifyTyVarsWithBinders cqdvs skol_info dvs - ; let final_tvs = scopedSort qtvs - -- This scopedSort is important: the qtvs may be /interleaved/ with - -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] - ; reportUnsolvedEqualities skol_info final_tvs tclvl wanted - - ; traceTc "tcTyFamInstEqnGuts 2" $ - vcat [ ppr fam_tc - , text "lhs_ty:" <+> ppr lhs_ty - , text "final_tvs:" <+> pprTyVars final_tvs ] + -- -- See Note [Type variables in type families instance decl] + ; (final_tvs, qtvs) <- tcFamInsLHSBinders tclvl skol_info outer_bndrs outer_hs_bndrs wcs lhs_ty wanted -- See Note [Error on unconstrained meta-variables] in GHC.Tc.Utils.TcMType -- Example: typecheck/should_fail/T17301 @@ -3509,7 +3525,7 @@ checkFamTelescope tclvl hs_outer_bndrs outer_tvs , let b_last = last bndrs = do { skol_info <- mkSkolemInfo (ForAllSkol $ HsTyVarBndrsRn (map unLoc bndrs)) ; setSrcSpan (combineSrcSpans (getLocA b_first) (getLocA b_last)) $ do - emitResidualTvConstraint skol_info (scopedSort outer_tvs) tclvl emptyWC } + emitResidualTvConstraint skol_info outer_tvs tclvl emptyWC } | otherwise = return () ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -92,7 +92,6 @@ import Control.Monad import Data.Tuple import GHC.Data.Maybe import Data.List( mapAccumL ) -import GHC.Core.TyCo.Ppr (pprTyVars) {- @@ -969,6 +968,7 @@ tcDataFamInstDecl is processing a non-associated data family instance, this TyVarEnv will simply be empty, and there is nothing to worry about. -} + ----------------------- tcDataFamInstHeader :: AssocInstInfo -> SkolemInfo -> TyCon -> HsOuterFamEqnTyVarBndrs GhcRn @@ -1017,37 +1017,7 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity , lhs_applied_kind , res_kind ) } - -- This code (and the stuff immediately above) is very similar - -- to that in tcTyFamInstEqnGuts. Maybe we should abstract the - -- common code; but for the moment I concluded that it's - -- clearer to duplicate it. Still, if you fix a bug here, - -- check there too! - - -- See Note [Type variables in type families instance decl] - ; let outer_tvs = (outerTyVars outer_bndrs) - ; checkFamTelescope tclvl hs_outer_bndrs outer_tvs - ; outer_tvs <- liftZonkM $ zonkTcTyVarsToTcTyVarsMaybe $ outer_tvs ++ wcs - - -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; (dvs, cqdvs) <- candidateQTyVarsWithBinders outer_tvs lhs_ty - ; qtvs <- quantifyTyVarsWithBinders cqdvs skol_info dvs - -- Have to make a same defaulting choice for reuslt kind here - -- and the `kindGeneralizeAll` in `tcConDecl`. - -- see (GT4) in - -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - - ; let final_tvs = scopedSort qtvs - ; traceTc "tcDataFamInstHeader 1" $ - vcat [ - text "skol_info:" <+> ppr skol_info, - text "outer_tvs:" <+> pprTyVars outer_tvs, - text "dvs:" <+> ppr dvs, - text "wcs:" <+> ppr wcs, - text "final_tvs:" <+> ppr final_tvs - ] - -- This scopedSort is important: the qtvs may be /interleaved/ with - -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] - ; reportUnsolvedEqualities skol_info final_tvs tclvl wanted + ; (final_tvs, qtvs) <- tcFamInsLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted ; (final_tvs, non_user_tvs, lhs_ty, master_res_kind, instance_res_kind, stupid_theta) <- liftZonkM $ do View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/881da0f013b84e1226adceb1bbe7e6c006232e35 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/881da0f013b84e1226adceb1bbe7e6c006232e35 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/fabb110c/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 00:28:36 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Mon, 10 Mar 2025 20:28:36 -0400 Subject: [Git][ghc/ghc][wip/T25647] handle explicit implicit binders seperately fix Message-ID: <67cf83b48bfe1_338434e5a3830031@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 7cb61cb6 by Patrick at 2025-03-11T08:28:27+08:00 handle explicit implicit binders seperately fix - - - - - 2 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -265,7 +265,7 @@ tcFamInsLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted ; checkFamTelescope tclvl hs_outer_bndrs outer_exp_tvs ; outer_imp_wc_tvs <- liftZonkM $ zonkTcTyVarsToTcTyVarsMaybe $ outer_imp_tvs ++ wcs -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; (dvs, cqdvs) <- candidateQTyVarsWithBinders (outer_imp_wc_tvs ++ outer_exp_tvs) lhs_ty + ; (dvs, cqdvs) <- candidateQTyVarsWithBinders outer_imp_wc_tvs outer_exp_tvs lhs_ty ; qtvs <- quantifyTyVarsWithBinders cqdvs skol_info dvs -- Have to make a same defaulting choice for reuslt kind here -- and the `kindGeneralizeAll` in `tcConDecl`. ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1392,7 +1392,7 @@ partitionCandidates dvs@(DV { dv_kvs = kvs, dv_tvs = tvs }) pred (extracted_tvs, rest_tvs) = partitionDVarSet pred tvs extracted = dVarSetToVarSet extracted_kvs `unionVarSet` dVarSetToVarSet extracted_tvs -candidateQTyVarsWithBinders :: [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar]) +candidateQTyVarsWithBinders :: [TyVar] -> [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar]) -- (candidateQTyVarsWithBinders tvs ty) returns the candidateQTyVars -- of (forall tvs. ty), but do not treat 'tvs' as bound for the purpose -- of Note [Naughty quantification candidates]. Why? @@ -1402,11 +1402,12 @@ candidateQTyVarsWithBinders :: [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar]) -- also return the bound variables that need to be quantified -- since they can be come from implicit binders and wildcards -- See Note [Type variables in type families instance decl] -candidateQTyVarsWithBinders bound_tvs ty +candidateQTyVarsWithBinders imp_bound_tvs exp_bound_tvs ty = do { kvs <- candidateQTyVarsOfKinds (map tyVarKind bound_tvs) ; cur_lvl <- getTcLevel ; all_tvs <- collect_cand_qtvs ty False cur_lvl emptyVarSet kvs ty - ; return (all_tvs `delCandidates` bound_tvs, boundedCandidates all_tvs bound_tvs) } + ; return (all_tvs `delCandidates` bound_tvs, boundedCandidates all_tvs imp_bound_tvs) } + where bound_tvs = imp_bound_tvs ++ exp_bound_tvs -- | Gathers free variables to use as quantification candidates (in View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7cb61cb6eb803628b556667d3bdfb9b7a48b0c51 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7cb61cb6eb803628b556667d3bdfb9b7a48b0c51 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/290f091f/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 00:35:50 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 10 Mar 2025 20:35:50 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T25838 Message-ID: <67cf856676f25_338434c5e54318b8@gitlab.mail> Ben Gamari pushed new branch wip/T25838 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25838 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/05f81176/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 11 01:51:52 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 10 Mar 2025 21:51:52 -0400 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] wrap last stmt expansion in a HsPar so that the error messages are prettier Message-ID: <67cf9738d976_33843486d23845425@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: e1c75108 by Apoorv Ingle at 2025-03-10T20:50:08-05:00 wrap last stmt expansion in a HsPar so that the error messages are prettier - - - - - 2 changed files: - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Tc/Gen/Do.hs Changes: ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -586,7 +586,8 @@ addTickHsExpr (HsProc x pat cmdtop) = addTickHsExpr (XExpr (WrapExpr w e)) = liftM (XExpr . WrapExpr w) $ (addTickHsExpr e) -- Explicitly no tick on inside -addTickHsExpr (XExpr (ExpandedThingTc o e)) = addTickHsExpanded o e +addTickHsExpr (XExpr (ExpandedThingTc o e)) = + liftM (XExpr . ExpandedThingTc o) $ addTickHsExpr e addTickHsExpr e@(XExpr (ConLikeTc {})) = return e -- We used to do a freeVar on a pat-syn builder, but actually @@ -609,21 +610,6 @@ addTickHsExpr (HsDo srcloc cxt (L l stmts)) ListComp -> Just $ BinBox QualBinBox _ -> Nothing -addTickHsExpanded :: HsThingRn -> HsExpr GhcTc -> TM (HsExpr GhcTc) -addTickHsExpanded o@(OrigStmt (L pos LastStmt{}) _) e - -- LastStmt always gets a tick for breakpoint and hpc coverage - = do d <- getDensity - case d of - TickForCoverage -> liftM (XExpr . ExpandedThingTc o) $ tick_it e - TickForBreakPoints -> liftM (XExpr . ExpandedThingTc o) $ tick_it e - _ -> liftM (XExpr . ExpandedThingTc o) $ addTickHsExpr e - where - tick_it e = unLoc <$> allocTickBox (ExpBox False) False False (locA pos) - (addTickHsExpr e) -addTickHsExpanded o e - = liftM (XExpr . ExpandedThingTc o) $ addTickHsExpr e - - addTickTupArg :: HsTupArg GhcTc -> TM (HsTupArg GhcTc) addTickTupArg (Present x e) = do { e' <- addTickLHsExpr e ; return (Present x e') } ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -76,14 +76,14 @@ expand_do_stmts flav [stmt@(L _loc (LastStmt _ (L body_loc body) _ ret_expr))] -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt` | NoSyntaxExprRn <- ret_expr -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt - = return $ mkExpandedStmt stmt flav body + = return $ mkExpandedStmt stmt flav (HsPar noExtField (L body_loc body)) | SyntaxExprRn ret <- ret_expr -- -- ------------------------------------------------ -- return e ~~> return e -- to make T18324 work = do let expansion = genHsApp ret (L body_loc body) - return $ mkExpandedStmt stmt flav expansion + return $ mkExpandedStmt stmt flav (HsPar noExtField (L body_loc expansion)) expand_do_stmts doFlavour (stmt@(L _ (LetStmt _ bs)) : lstmts) = -- See Note [Expanding HsDo with XXExprGhcRn] Equation (3) below View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e1c75108759b12df147832c57bb253f9086d0348 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e1c75108759b12df147832c57bb253f9086d0348 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250310/1174bd5d/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 10:10:34 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 06:10:34 -0400 Subject: [Git][ghc/ghc][master] users guide: Fix typo Message-ID: <67d00c1abf3c1_3efa205ad80425719@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1 changed file: - docs/users_guide/using-concurrent.rst Changes: ===================================== docs/users_guide/using-concurrent.rst ===================================== @@ -157,7 +157,7 @@ use the RTS :rts-flag:`-N ⟨x⟩` options. .. note:: The maximum number of capabilities supported by the GHC runtime system is - determined when at RTS startup to be either 256, the value given by + determined at RTS startup to be either 256, the value given by :rts-flag:`-N ⟨x⟩`, or the number of logical CPU cores, whichever is greater. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cbae3708e67bc37c0c9d972c4a60610f08191618 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cbae3708e67bc37c0c9d972c4a60610f08191618 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/dc1d3215/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 11 10:11:02 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 06:11:02 -0400 Subject: [Git][ghc/ghc][master] testsuite: Don't count fragile passes as failures in JUnit output Message-ID: <67d00c3626dad_3efa203765cc295b7@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 1 changed file: - testsuite/driver/junit.py Changes: ===================================== testsuite/driver/junit.py ===================================== @@ -19,8 +19,7 @@ def junit(t: TestRun) -> ET.ElementTree: for res_type, group in [('stat failure', t.unexpected_stat_failures), ('unexpected failure', t.unexpected_failures), ('unexpected pass', t.unexpected_passes), - ('fragile failure', t.fragile_failures), - ('fragile pass', t.fragile_passes)]: + ('fragile failure', t.fragile_failures)]: for tr in group: testcase = ET.SubElement(testsuite, 'testcase', classname = tr.way, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1951eb7a68420450cf17182c343e0132474483af -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1951eb7a68420450cf17182c343e0132474483af You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/b0c43e88/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 10:11:40 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 06:11:40 -0400 Subject: [Git][ghc/ghc][master] Use panic rather than error in expectJust Message-ID: <67d00c5c16435_3efa205d716833350@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - 2 changed files: - compiler/GHC/Data/Maybe.hs - compiler/GHC/Utils/Panic.hs Changes: ===================================== compiler/GHC/Data/Maybe.hs ===================================== @@ -34,6 +34,8 @@ import Control.Exception (SomeException(..)) import Data.Maybe import Data.Foldable ( foldlM, for_ ) import GHC.Utils.Misc (HasCallStack) +import GHC.Utils.Panic +import GHC.Utils.Outputable import Data.List.NonEmpty ( NonEmpty ) import Control.Applicative( Alternative( (<|>) ) ) @@ -72,7 +74,7 @@ expectJust :: HasCallStack => Maybe a -> a expectJust = fromMaybe expectJustError expectJustError :: HasCallStack => a -expectJustError = error "expectJust" +expectJustError = pprPanic "expectJust" empty {-# NOINLINE expectJustError #-} whenIsJust :: Monad m => Maybe a -> (a -> m ()) -> m () ===================================== compiler/GHC/Utils/Panic.hs ===================================== @@ -188,7 +188,7 @@ handleGhcException = MC.handle -- | Throw an exception saying "bug in GHC" with a callstack pprPanic :: HasCallStack => String -> SDoc -> a -pprPanic s doc = panicDoc s (doc $$ callStackDoc) +pprPanic s doc = withFrozenCallStack $ panicDoc s (doc $$ callStackDoc) -- | Throw an exception saying "bug in GHC" panicDoc :: String -> SDoc -> a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/589f40b9525c59d646a8b13cd51057bd350f7849 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/589f40b9525c59d646a8b13cd51057bd350f7849 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/fa3a4549/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 10:24:56 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 11 Mar 2025 06:24:56 -0400 Subject: [Git][ghc/ghc][wip/T23109] 2 commits: Revert ConLike change Message-ID: <67d00f7881c1b_3ffdaccc2e03394b@gitlab.mail> Simon Peyton Jones pushed to branch wip/T23109 at Glasgow Haskell Compiler / GHC Commits: a5f8696d by Simon Peyton Jones at 2025-03-11T10:24:15+00:00 Revert ConLike change I'm not sure why I made this change - - - - - ef8709e3 by Simon Peyton Jones at 2025-03-11T10:24:29+00:00 No newtype axioms for unary type classes - - - - - 5 changed files: - compiler/GHC/Core/Utils.hs - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/typecheck/should_compile/T12763.stderr Changes: ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -2149,7 +2149,17 @@ exprIsHNF = exprIsHNFlike isDataConWorkId isEvaldUnfolding -- data constructors. Conlike arguments are considered interesting by the -- inliner. exprIsConLike :: CoreExpr -> Bool -- True => lambda, conlike, PAP --- exprIsConLike = exprIsHNFlike isConLikeId isConLikeUnfolding +exprIsConLike = exprIsHNFlike isConLikeId isConLikeUnfolding + +{- FOR SOME REASON I TRIED THIS VARIANT, BUT I CAN'T REMEMBER WHY + It means, for example, that constructors with wappers don't count + as con-like: + T23307a.$WCons + = \ (@a_ahj) (conrep_ai4 [Occ=Once1!] :: Unconsed a_ahj) -> + case conrep_ai4 of + { Unconsed unbx_ai5 [Occ=Once1] unbx1_ai6 [Occ=Once1] -> + T23307a.Cons @a_ahj unbx_ai5 unbx1_ai6 } + -- Trying: just a constructor application exprIsConLike (Var v) = isConLikeId v exprIsConLike (Lit l) = not (isLitRubbish l) @@ -2165,6 +2175,7 @@ exprIsConLike (Let {}) = False exprIsConLike (Case {}) = False exprIsConLike (Type {}) = False exprIsConLike (Coercion {}) = False +-} -- | Returns true for values or value-like expressions. These are lambdas, -- constructors / CONLIKE functions (as determined by the function argument) ===================================== testsuite/tests/roles/should_compile/Roles14.stderr ===================================== @@ -3,10 +3,8 @@ TYPE SIGNATURES TYPE CONSTRUCTORS class C2{1} :: * -> Constraint roles representational -COERCION AXIOMS - axiom Roles12.N:C2 :: C2 a = a -> a Dependent modules: [] -Dependent packages: [base-4.20.0.0] +Dependent packages: [base-4.21.0.0] ==================== Typechecker ==================== Roles12.$tcC2 ===================================== testsuite/tests/roles/should_compile/Roles3.stderr ===================================== @@ -15,13 +15,8 @@ TYPE CONSTRUCTORS type synonym Syn1{1} :: * -> * roles nominal type synonym Syn2{1} :: * -> * -COERCION AXIOMS - axiom Roles3.N:C1 :: C1 a = a -> a - axiom Roles3.N:C2 :: C2 a b = (a ~ b) => a -> b - axiom Roles3.N:C3 :: C3 a b = a -> F3 b -> F3 b - axiom Roles3.N:C4 :: C4 a b = a -> F4 b -> F4 b Dependent modules: [] -Dependent packages: [base-4.20.0.0] +Dependent packages: [base-4.21.0.0] ==================== Typechecker ==================== Roles3.$tcC4 ===================================== testsuite/tests/roles/should_compile/Roles4.stderr ===================================== @@ -5,11 +5,8 @@ TYPE CONSTRUCTORS class C1{1} :: * -> Constraint class C3{1} :: * -> Constraint type synonym Syn1{1} :: * -> * -COERCION AXIOMS - axiom Roles4.N:C1 :: C1 a = a -> a - axiom Roles4.N:C3 :: C3 a = a -> Syn1 a Dependent modules: [] -Dependent packages: [base-4.20.0.0] +Dependent packages: [base-4.21.0.0] ==================== Typechecker ==================== Roles4.$tcC3 ===================================== testsuite/tests/typecheck/should_compile/T12763.stderr ===================================== @@ -3,9 +3,7 @@ TYPE SIGNATURES m :: forall a. C a => a -> () TYPE CONSTRUCTORS class C{1} :: * -> Constraint -COERCION AXIOMS - axiom T12763.N:C :: C a = a -> () CLASS INSTANCES instance C Int -- Defined at T12763.hs:9:10 Dependent modules: [] -Dependent packages: [base-4.17.0.0] +Dependent packages: [base-4.21.0.0] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b77b97b6df4553dbc98ae8bfceed0994aa97f56...ef8709e3fc15a55702e88b09971af1d20d0b8a95 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b77b97b6df4553dbc98ae8bfceed0994aa97f56...ef8709e3fc15a55702e88b09971af1d20d0b8a95 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/746e68f0/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 10:42:48 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 11 Mar 2025 06:42:48 -0400 Subject: [Git][ghc/ghc][wip/romes/better-main] driver: Move DynFlags consistency fixes off Main Message-ID: <67d013a8e92a8_3ffdac1c76e0352d5@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/better-main at Glasgow Haskell Compiler / GHC Commits: ca1779de by Rodrigo Mesquita at 2025-03-11T10:41:35+00:00 driver: Move DynFlags consistency fixes off Main These consistency fixes found in Main.hs are required for the proper functioning of the compiler and should live together with all remaining fixes in `makeDynFlagsConsistent`. This is especially relevant to GHC applications that shouldn't have to copy/fix themselves possibly inconsistent DynFlags. Additionally, outputs information when verbosity is high about these consistency fixes that were previously quiet, adds information to the Note on consistency of DynFlags, and improves one of the fixes that incorrectly used `dynNow`. - - - - - 7 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - ghc/GHCi/UI.hs - ghc/Main.hs - utils/check-exact/Parsers.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -918,7 +918,7 @@ parseDynamicFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) parseDynamicFlags logger dflags cmdline = do - (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine dflags cmdline + (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine logger dflags cmdline -- flags that have just been read are used by the logger when loading package -- env (this is checked by T16318) let logger1 = setLogFlags logger (initLogFlags dflags1) @@ -1015,11 +1015,13 @@ normalise_hyp fp checkNewDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags checkNewDynFlags logger dflags = do -- See Note [DynFlags consistency] - let (dflags', warnings) = makeDynFlagsConsistent dflags + let (dflags', warnings, infoverb) = makeDynFlagsConsistent dflags let diag_opts = initDiagOpts dflags print_config = initPrintConfig dflags liftIO $ printOrThrowDiagnostics logger print_config diag_opts $ fmap GhcDriverMessage $ warnsToMessages diag_opts warnings + liftIO $ + mapM_ (\(L loc m) -> logMsg logger MCDump loc m) infoverb return dflags' checkNewInteractiveDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -100,8 +100,9 @@ doBackpack [src_filename] = do dflags0 <- getDynFlags let dflags1 = dflags0 let parser_opts1 = initParserOpts dflags1 + logger0 <- getLogger (p_warns, src_opts) <- liftIO $ getOptionsFromFile parser_opts1 (supportedLanguagePragmas dflags1) src_filename - (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma dflags1 src_opts + (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma logger0 dflags1 src_opts modifySession (hscSetFlags dflags) logger <- getLogger -- Get the logger after having set the session flags, -- so that logger options are correctly set. ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -655,10 +655,11 @@ runUnlitPhase hsc_env input_fn output_fn = do getFileArgs :: HscEnv -> FilePath -> IO ((DynFlags, Messages PsMessage, Messages DriverMessage)) getFileArgs hsc_env input_fn = do let dflags0 = hsc_dflags hsc_env + logger = hsc_logger hsc_env parser_opts = initParserOpts dflags0 (warns0, src_opts) <- getOptionsFromFile parser_opts (supportedLanguagePragmas dflags0) input_fn (dflags1, unhandled_flags, warns) - <- parseDynamicFilePragma dflags0 src_opts + <- parseDynamicFilePragma logger dflags0 src_opts checkProcessArgsResult unhandled_flags return (dflags1, warns0, warns) ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -247,6 +247,7 @@ import GHC.Driver.Plugins.External import GHC.Settings.Config import GHC.Core.Unfold import GHC.Driver.CmdLine +import GHC.Utils.Logger import GHC.Utils.Panic import GHC.Utils.Misc import GHC.Utils.Constants (debugIsOn) @@ -806,7 +807,7 @@ updOptLevel n = fst . updOptLevelChanged n -- the parsed 'DynFlags', the left-over arguments, and a list of warnings. -- Throws a 'UsageError' if errors occurred during parsing (such as unknown -- flags or missing arguments). -parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] +parseDynamicFlagsCmdLine :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -816,7 +817,7 @@ parseDynamicFlagsCmdLine = parseDynamicFlagsFull flagsAll True -- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags -- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db). -- Used to parse flags set in a modules pragma. -parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] +parseDynamicFilePragma :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -865,10 +866,11 @@ parseDynamicFlagsFull :: forall m. MonadIO m => [Flag (CmdLineP DynFlags)] -- ^ valid flags to match against -> Bool -- ^ are the arguments from the command line? + -> Logger -- ^ logger -> DynFlags -- ^ current dynamic flags -> [Located String] -- ^ arguments to parse -> m (DynFlags, [Located String], Messages DriverMessage) -parseDynamicFlagsFull activeFlags cmdline dflags0 args = do +parseDynamicFlagsFull activeFlags cmdline logger dflags0 args = do ((leftover, errs, cli_warns), dflags1) <- processCmdLineP activeFlags dflags0 args -- See Note [Handling errors when parsing command-line flags] @@ -884,7 +886,7 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do throwGhcExceptionIO (CmdLineError ("combination not supported: " ++ intercalate "/" (map wayDesc (Set.toAscList theWays)))) - let (dflags3, consistency_warnings) = makeDynFlagsConsistent dflags2 + let (dflags3, consistency_warnings, infoverb) = makeDynFlagsConsistent dflags2 -- Set timer stats & heap size when (enableTimeStats dflags3) $ liftIO enableTimingStats @@ -898,6 +900,9 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do let diag_opts = initDiagOpts dflags3 warns = warnsToMessages diag_opts $ mconcat [consistency_warnings, sh_warns, cli_warns] + liftIO $ + mapM_ (\(L loc m) -> logMsg logger MCDump loc m) infoverb + return (dflags3, leftover, warns) -- | Check (and potentially disable) any extensions that aren't allowed @@ -3491,12 +3496,35 @@ combination when parsing flags, we also need to check when we update the flags; this is because API clients may parse flags but update the DynFlags afterwords, before finally running code inside a session (see T10052 and #10052). + +Host ways vs Build ways mismatch +-------------------------------- +Many consistency checks aim to fix the situation where the wanted build ways +are not compatible with the ways the compiler is built in. This happens when +using the interpreter, TH, and the runtime linker, where the compiler cannot +load objects compiled for ways not matching its own. + +For instance, a profiled-dynamic object can only be loaded by a +profiled-dynamic compiler (and not any other kind of compiler). + +This incompatibility is traditionally solved in either of two ways: + +(1) Force the "wanted" build ways to match the compiler ways exactly, + guaranteeing they match. + +(2) Force the use of the external interpreter. When interpreting is offloaded + to the external interpreter it no longer matters what are the host compiler ways. + +In the checks and fixes performed by `makeDynFlagsConsistent`, the choice +between the two does not seem uniform. TODO: Make this choice more evident and uniform. -} -- | Resolve any internal inconsistencies in a set of 'DynFlags'. -- Returns the consistent 'DynFlags' as well as a list of warnings --- to report to the user. -makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn]) +-- to report to the user, and a list of verbose info msgs. +-- +-- See Note [DynFlags consistency] +makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn], [Located SDoc]) -- Whenever makeDynFlagsConsistent does anything, it starts over, to -- ensure that a later change doesn't invalidate an earlier check. -- Be careful not to introduce potential loops! @@ -3587,13 +3615,41 @@ makeDynFlagsConsistent dflags | LinkMergedObj <- ghcLink dflags , Nothing <- outputFile dflags - = pgmError "--output must be specified when using --merge-objs" + = pgmError "--output must be specified when using --merge-objs" + + -- When we do ghci, force using dyn ways if the target RTS linker + -- only supports dynamic code + | LinkInMemory <- ghcLink dflags + , sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags + , not (ways dflags `hasWay` WayDyn && gopt Opt_ExternalInterpreter dflags) + = flip loopNoWarn "Forcing dynamic way because target RTS linker only supports dynamic code" $ + -- See checkOptions, -fexternal-interpreter is + -- required when using --interactive with a non-standard + -- way (-prof, -static, or -dynamic). + setGeneralFlag' Opt_ExternalInterpreter $ + addWay' WayDyn dflags - | otherwise = (dflags, mempty) + | LinkInMemory <- ghcLink dflags + , not (gopt Opt_ExternalInterpreter dflags) + , targetWays_ dflags /= hostFullWays + = flip loopNoWarn "Forcing ways to the host ways because we're using the interpreter" $ + let dflags_a = dflags { targetWays_ = hostFullWays } + dflags_b = foldl gopt_set dflags_a + $ concatMap (wayGeneralFlags platform) + hostFullWays + dflags_c = foldl gopt_unset dflags_b + $ concatMap (wayUnsetGeneralFlags platform) + hostFullWays + in dflags_c + + | otherwise = (dflags, mempty, mempty) where loc = mkGeneralSrcSpan (fsLit "when making flags consistent") loop updated_dflags warning = case makeDynFlagsConsistent updated_dflags of - (dflags', ws) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws) + (dflags', ws, is) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws, is) + loopNoWarn updated_dflags doc + = case makeDynFlagsConsistent updated_dflags of + (dflags', ws, is) -> (dflags', ws, L loc (text doc):is) platform = targetPlatform dflags arch = platformArch platform os = platformOS platform ===================================== ghc/GHCi/UI.hs ===================================== @@ -3148,7 +3148,7 @@ newDynFlags interactive_only minus_opts = do logger <- getLogger idflags0 <- GHC.getInteractiveDynFlags - (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine idflags0 lopts + (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine logger idflags0 lopts liftIO $ printOrThrowDiagnostics logger (initPrintConfig idflags1) (initDiagOpts idflags1) (GhcDriverMessage <$> warns) when (not $ null leftovers) (unknownFlagsErr $ map unLoc leftovers) @@ -3161,7 +3161,7 @@ newDynFlags interactive_only minus_opts = do dflags0 <- getDynFlags when (not interactive_only) $ do - (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine dflags0 lopts + (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine logger dflags0 lopts must_reload <- GHC.setProgramDynFlags dflags1 -- if the package flags changed, reset the context and link ===================================== ghc/Main.hs ===================================== @@ -224,41 +224,9 @@ main' postLoadMode units dflags0 args flagWarnings = do -- The rest of the arguments are "dynamic" -- Leftover ones are presumably files - (dflags3', fileish_args, dynamicFlagWarnings) <- + (dflags4, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags logger2 dflags2 args' - -- When we do ghci, force using dyn ways if the target RTS linker - -- only supports dynamic code - let dflags3 - | LinkInMemory <- link, - sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags3' - = setDynamicNow $ - -- See checkOptions below, -fexternal-interpreter is - -- required when using --interactive with a non-standard - -- way (-prof, -static, or -dynamic). - setGeneralFlag' Opt_ExternalInterpreter $ - -- Use .o for dynamic object, otherwise it gets dropped - -- with "Warning: ignoring unrecognised input", see - -- objish_suffixes - dflags3' { dynObjectSuf_ = objectSuf dflags3' } - | otherwise - = dflags3' - - let dflags4 = if backendNeedsFullWays bcknd && - not (gopt Opt_ExternalInterpreter dflags3) - then - let platform = targetPlatform dflags3 - dflags3a = dflags3 { targetWays_ = hostFullWays } - dflags3b = foldl gopt_set dflags3a - $ concatMap (wayGeneralFlags platform) - hostFullWays - dflags3c = foldl gopt_unset dflags3b - $ concatMap (wayUnsetGeneralFlags platform) - hostFullWays - in dflags3c - else - dflags3 - let logger4 = setLogFlags logger2 (initLogFlags dflags4) GHC.prettyPrintGhcErrors logger4 $ do @@ -804,7 +772,7 @@ initMulti unitArgsFiles = do dynFlagsAndSrcs <- forM unitArgsFiles $ \f -> do when (verbosity initial_dflags > 2) (liftIO $ print f) args <- liftIO $ expandResponse [f] - (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine initial_dflags (map (mkGeneralLocated f) (removeRTS args)) + (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine logger initial_dflags (map (mkGeneralLocated f) (removeRTS args)) handleSourceError (\e -> do GHC.printException e liftIO $ exitWith (ExitFailure 1)) $ do ===================================== utils/check-exact/Parsers.hs ===================================== @@ -348,12 +348,14 @@ initDynFlags file = do -- Based on GHC backpack driver doBackPack dflags0 <- GHC.getSessionDynFlags let parser_opts0 = GHC.initParserOpts dflags0 + logger <- getLogger (_, src_opts) <- GHC.liftIO $ GHC.getOptionsFromFile parser_opts0 (GHC.supportedLanguagePragmas dflags0) file - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 src_opts + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 src_opts -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 @@ -375,13 +377,15 @@ initDynFlagsPure fp s = do -- as long as `parseDynamicFilePragma` is impure there seems to be -- no reason to use it. dflags0 <- GHC.getSessionDynFlags + logger <- getLogger let parser_opts0 = GHC.initParserOpts dflags0 let (_, pragmaInfo) = GHC.getOptions parser_opts0 (GHC.supportedLanguagePragmas dflags0) (GHC.stringToStringBuffer $ s) fp - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 pragmaInfo + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 pragmaInfo -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ca1779dece5286808ca6ed3e4ba9a8777718dfb1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ca1779dece5286808ca6ed3e4ba9a8777718dfb1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/5c23e90b/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 10:43:26 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 06:43:26 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 17 commits: users guide: Fix typo Message-ID: <67d013ce48ec_3ffdac50a76c389c4@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 97 changed files: - compiler/GHC.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/using-concurrent.rst - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/driver/junit.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2befa653b2d98858f4282a2e33da2d483375682c...6bb0e2617dd771dd9b059dc1906b268f5e53e440 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2befa653b2d98858f4282a2e33da2d483375682c...6bb0e2617dd771dd9b059dc1906b268f5e53e440 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/e4f983c8/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 11:11:14 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 11 Mar 2025 07:11:14 -0400 Subject: [Git][ghc/ghc][wip/T25647] fix lint Message-ID: <67d01a525df28_11b4928b9a0-14@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: a88b45e4 by Patrick at 2025-03-11T19:11:08+08:00 fix lint - - - - - 1 changed file: - compiler/GHC/Tc/TyCl/Instance.hs Changes: ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -31,7 +31,7 @@ import GHC.Tc.TyCl.Utils ( addTyConsToGblEnv ) import GHC.Tc.TyCl.Class ( tcClassDecl2, tcATDefault, HsSigFun, mkHsSigFun, findMethodBind, instantiateMethod ) -import GHC.Tc.Solver( pushLevelAndSolveEqualitiesX, reportUnsolvedEqualities ) +import GHC.Tc.Solver( pushLevelAndSolveEqualitiesX ) import GHC.Tc.Gen.Sig import GHC.Tc.Utils.Monad import GHC.Tc.Validity View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a88b45e457510be56c70e9760f8200be1296fd7b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a88b45e457510be56c70e9760f8200be1296fd7b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/0973a516/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 11 12:14:11 2025 From: gitlab at gitlab.haskell.org (Matthew Craven (@clyring)) Date: Tue, 11 Mar 2025 08:14:11 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/clyring/ghc-prim-exports Message-ID: <67d0291361108_285923077bc26fd@gitlab.mail> Matthew Craven pushed new branch wip/clyring/ghc-prim-exports at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/clyring/ghc-prim-exports You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/3e6430e1/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 11 14:26:15 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 11 Mar 2025 10:26:15 -0400 Subject: [Git][ghc/ghc][wip/T25672] 82 commits: testsuite: Mark T23071 and T2047 as fragile on FreeBSD Message-ID: <67d04807699dc_521a13821d89565b@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25672 at Glasgow Haskell Compiler / GHC Commits: ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - 8a91d786 by Simon Peyton Jones at 2025-03-11T11:46:59+00:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 381 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T21003.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6107f52962d7d89df7db6af89aad1326fac05bd7...8a91d78604923267e962bad97fb35a6afaa219c3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6107f52962d7d89df7db6af89aad1326fac05bd7...8a91d78604923267e962bad97fb35a6afaa219c3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/a5c442c6/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 14:33:09 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 10:33:09 -0400 Subject: [Git][ghc/ghc][wip/kill-ioport] Kill IOPort# Message-ID: <67d049a57e9c5_58d2bc5c3872953@gitlab.mail> Ben Gamari pushed to branch wip/kill-ioport at Glasgow Haskell Compiler / GHC Commits: f0ef569f by Ben Gamari at 2025-03-11T10:32:50-04:00 Kill IOPort# This type is unnecessary, having been superceded by `MVar` and a rework of WinIO's blocking logic. See #20947. See https://github.com/haskell/core-libraries-committee/issues/213. - - - - - 36 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Prim.hs - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/GHC/Exts.hs - − libraries/base/src/GHC/IOPort.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc - libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/IO/Buffer.hs - libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc - − libraries/ghc-internal/src/GHC/Internal/IOPort.hs - libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs - libraries/ghc-prim/changelog.md - rts/Prelude.h - rts/PrimOps.cmm - rts/RtsSymbols.c - rts/external-symbols.list.in - rts/include/stg/MiscClosures.h - rts/include/stg/SMP.h - rts/win32/AsyncWinIO.c - rts/win32/libHSghc-internal.def - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/primops/should_run/UnliftedIOPort.hs - testsuite/tests/primops/should_run/all.T - utils/genprimopcode/Main.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f0ef569f8b1046ee3cca06d7825319945f357349 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f0ef569f8b1046ee3cca06d7825319945f357349 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/9bcc31d0/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 11 14:51:53 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 11 Mar 2025 10:51:53 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/iface-tests Message-ID: <67d04e09acf5f_58d2b4ec2d0824bb@gitlab.mail> Matthew Pickering pushed new branch wip/iface-tests at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/iface-tests You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/15685aa4/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 11 14:52:16 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 11 Mar 2025 10:52:16 -0400 Subject: [Git][ghc/ghc][wip/iface-tests] testsuite: Add a performance test for interface file checking Message-ID: <67d04e2076e93_58d2b2d68888263b@gitlab.mail> Matthew Pickering pushed to branch wip/iface-tests at Glasgow Haskell Compiler / GHC Commits: e9b4b5df by Matthew Pickering at 2025-03-11T14:52:00+00:00 testsuite: Add a performance test for interface file checking This commit adds two tests. * `IfaceRecomp`: Tests the performance of the full recompilation check * `IfaceRecompSrcChanged`: Tests the performance of the recompilation check when the hash of the source file has changed. The IfaceRecompTest.hs file is designed to be "large"-ish in some senses, but the interface file is still not particually large. Some parts of the interface should not be used by the recompilation check: * Core definitions from interface files (`-fwrite-if-simplified-core`) * Haddock docs (`-haddock`) * Extra debugging information about specific flags (`-fwrite-if-self-recomp-flags`) I intend to improve the performance of this test and expand it if necessary in the near future. Fixes #25840 - - - - - 4 changed files: - + testsuite/tests/perf/compiler/IfaceRecomp.hs - + testsuite/tests/perf/compiler/IfaceRecompTest.hs - testsuite/tests/perf/compiler/Makefile - testsuite/tests/perf/compiler/all.T Changes: ===================================== testsuite/tests/perf/compiler/IfaceRecomp.hs ===================================== @@ -0,0 +1,93 @@ +{-# LANGUAGE ScopedTypeVariables #-} +module Main where + +import GHC hiding (SuccessFlag(..)) +import GHC.Utils.Outputable +import GHC.Data.FastString +import GHC.Tc.Utils.Monad +import GHC.Iface.Load +import GHC.Iface.Recomp +import GHC.Driver.Env.Types +import GHC.Driver.Ppr +import GHC.Unit.Types + +import Control.Monad +import System.Environment +import System.FilePath +import System.Directory +import GHC.Data.Maybe +import GHC.Unit.Env +import GHC.Driver.Make +import GHC.Driver.Env + +-- This test checks propeties of reading interface files from disk + +parseMode :: String -> (MaybeValidated ModIface -> Bool) +parseMode "full" = checkFullMode +parseMode "src" = checkSrcMode +parseMode mode = error $ "unknown mode:" ++ mode + +-- Checks performance of a full complete recompilation check +checkFullMode :: MaybeValidated ModIface -> Bool +checkFullMode (UpToDateItem {}) = True +checkFullMode _ = False + +-- Checks performance of a recompilation check that only checks if the source file has changed +checkSrcMode :: MaybeValidated ModIface -> Bool +checkSrcMode (OutOfDateItem (RecompBecause SourceFileChanged) _) = True +checkSrcMode _ = False + +main :: IO () +main = do + args <- getArgs + (libdir, iterations, check) <- case args of + (dir: n: mode: _) -> return (dir, read n, parseMode mode) + _ -> do + error "Error: Expected libdir, iterations, mode" + + + runGhc (Just libdir) $ do + -- Set GHC session flags + -- Parse command line flags + + logger <- getLogger + dflags0 <- getSessionDynFlags + let parseDynFlags dflags as = do + (dflags', _, _) <- parseDynamicFlags logger dflags (map noLoc as) + return dflags' + + -- Set up basic flags for our test + dflags1 <- parseDynFlags dflags0 ["-haddock", "-fwrite-if-self-recomp-flags", "-fno-code", "-fwrite-interface", "-fwrite-if-simplified-core","-v0", "-O"] + _ <- setSessionDynFlags dflags1 + + + -- Get the current directory to find our test module + pwd <- liftIO getCurrentDirectory + let moduleFile = pwd </> "IfaceRecompTest.hs" + + hsc_env <- getSession + let hiFile = pwd </> "IfaceRecompTest.hi" + Right mod_sum <- liftIO $ summariseFile hsc_env (ue_unitHomeUnit (UnitId (mkFastString "main")) (hsc_unit_env hsc_env)) mempty moduleFile Nothing Nothing + + + -- liftIO $ putStrLn $ "Loading interface file: " ++ hiFile + + dflags <- getSessionDynFlags + let test_mod = mkModule (fsToUnit (mkFastString "main")) (mkModuleName "IfaceRecompTest") + + -- Load the interface + mb_iface <- liftIO $ readIface dflags (hsc_NC hsc_env) test_mod hiFile + case mb_iface of + Failed {} -> liftIO $ do + error "Failed to load interface" + Succeeded iface -> do + -- liftIO $ putStrLn "Successfully loaded interface. Now checking it 10000 times." + + -- Call checkOldIface 10000 times + liftIO $ replicateM_ iterations $ do + res <- checkOldIface (hscSetFlags (ms_hspp_opts mod_sum) hsc_env) mod_sum (Just iface) + if check res + then return () + else error $ "Interface check failed: " ++ showSDoc dflags (ppr (fmap (const ()) res)) + + liftIO $ putStrLn "Completed interface checks." ===================================== testsuite/tests/perf/compiler/IfaceRecompTest.hs ===================================== @@ -0,0 +1,500 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module IfaceRecompTest where + +import Prelude (Eq(..), Bool(..), Maybe(..), Int, Ord(..), Either(..), String, Char + , elem, not, filter, (++), otherwise, reverse, Num(..), (&&), (||), seq, (.) + , dropWhile, break, Enum(..), map, length, replicate, concat, fromIntegral + , RealFrac(..), mod, sqrt, all, div ) + +-- | Adds two integers +add :: Int -> Int -> Int +add x y = x + y + +-- | Subtracts second integer from first +subtract :: Int -> Int -> Int +subtract x y = x - y + +-- | Multiplies two integers +multiply :: Int -> Int -> Int +multiply x y = x * y + +-- | Divides first integer by second +divide :: Int -> Int -> Int +divide x y = x `div` y + +-- | Calculates square of an integer +square :: Int -> Int +square x = x * x + +-- | Calculates cube of an integer +cube :: Int -> Int +cube x = x * x * x + +-- | Calculates factorial of a non-negative integer +factorial :: Int -> Int +factorial 0 = 1 +factorial n = n * factorial (n - 1) + +-- | Checks if a number is even +isEven :: Int -> Bool +isEven n = n `mod` 2 == 0 + +-- | Checks if a number is odd +isOdd :: Int -> Bool +isOdd = not . isEven + +-- | Calculates the greatest common divisor of two integers +gcd :: Int -> Int -> Int +gcd a 0 = abs a +gcd a b = gcd b (a `mod` b) + +-- | Calculates the least common multiple of two integers +lcm :: Int -> Int -> Int +lcm a b = abs (a * b) `div` gcd a b + +-- | Checks if a number is prime +isPrime :: Int -> Bool +isPrime n | n <= 1 = False +isPrime 2 = True +isPrime n = all (\x -> n `mod` x /= 0) [2..isqrt n] + where isqrt = floor . sqrt . fromIntegral + +-- | Concatenates two strings +concatStrings :: String -> String -> String +concatStrings = (++) + +-- | Repeats a string n times +repeatString :: String -> Int -> String +repeatString str n = concat (replicate n str) + +-- | Reverses a string +reverseString :: String -> String +reverseString = reverse + +-- | Capitalizes the first letter of a string +capitalize :: String -> String +capitalize [] = [] +capitalize (c:cs) = toUpper c : cs + where toUpper c | 'a' <= c && c <= 'z' = toEnum (fromEnum c - fromEnum 'a' + fromEnum 'A') + | otherwise = c + +-- | Calculates the length of a string +stringLength :: String -> Int +stringLength = length + +-- | Converts a string to uppercase +toUppercase :: String -> String +toUppercase = map toUpper + where toUpper c | 'a' <= c && c <= 'z' = toEnum (fromEnum c - fromEnum 'a' + fromEnum 'A') + | otherwise = c + +-- | Converts a string to lowercase +toLowercase :: String -> String +toLowercase = map toLower + where toLower c | 'A' <= c && c <= 'Z' = toEnum (fromEnum c - fromEnum 'A' + fromEnum 'a') + | otherwise = c + +-- | Checks if a string contains a substring +contains :: String -> String -> Bool +contains str substr = isJust (findSubstring substr str) + where + findSubstring [] _ = Just [] + findSubstring _ [] = Nothing + findSubstring pat@(p:ps) (s:ss) + | p == s && isPrefixOf ps ss = Just pat + | otherwise = findSubstring pat ss + isPrefixOf [] _ = True + isPrefixOf _ [] = False + isPrefixOf (p:ps) (s:ss) = p == s && isPrefixOf ps ss + isJust Nothing = False + isJust (Just _) = True + +-- | Splits a string by a delimiter +splitString :: Char -> String -> [String] +splitString delim str = case break (== delim) str of + (a, []) -> [a] + (a, _:rest) -> a : splitString delim rest + +-- | Joins a list of strings with a delimiter +joinStrings :: String -> [String] -> String +joinStrings delim = intercalate delim + where + intercalate _ [] = [] + intercalate _ [x] = x + intercalate sep (x:xs) = x ++ sep ++ intercalate sep xs + +-- | Trims whitespace from both ends of a string +trim :: String -> String +trim = trimEnd . trimStart + where + trimStart = dropWhile isSpace + trimEnd = reverse . trimStart . reverse + isSpace c = c == ' ' || c == '\t' || c == '\n' || c == '\r' + +-- | Returns the first n elements of a list +take :: Int -> [a] -> [a] +take _ [] = [] +take n _ | n <= 0 = [] +take n (x:xs) = x : take (n-1) xs + +-- | Drops the first n elements from a list +drop :: Int -> [a] -> [a] +drop _ [] = [] +drop n xs | n <= 0 = xs +drop n (_:xs) = drop (n-1) xs + +-- | Splits a list at the nth position +splitAt :: Int -> [a] -> ([a], [a]) +splitAt n xs = (take n xs, drop n xs) + +-- | Maps a function over a list +mapList :: (a -> b) -> [a] -> [b] +mapList _ [] = [] +mapList f (x:xs) = f x : mapList f xs + +-- | Filters a list based on a predicate +filterList :: (a -> Bool) -> [a] -> [a] +filterList _ [] = [] +filterList p (x:xs) + | p x = x : filterList p xs + | otherwise = filterList p xs + +-- | Folds a list from the left +foldl' :: (b -> a -> b) -> b -> [a] -> b +foldl' _ acc [] = acc +foldl' f acc (x:xs) = let acc' = f acc x in acc' `seq` foldl' f acc' xs + +-- | Folds a list from the right +foldr' :: (a -> b -> b) -> b -> [a] -> b +foldr' _ acc [] = acc +foldr' f acc (x:xs) = f x (foldr' f acc xs) + +-- | Removes duplicate elements from a list +nub :: Eq a => [a] -> [a] +nub [] = [] +nub (x:xs) = x : nub (filter (/= x) xs) + +-- | Sorts a list +sort :: Ord a => [a] -> [a] +sort [] = [] +sort (x:xs) = sort [y | y <- xs, y < x] ++ [x] ++ sort [y | y <- xs, y >= x] + +-- | Merges two sorted lists +merge :: Ord a => [a] -> [a] -> [a] +merge [] ys = ys +merge xs [] = xs +merge (x:xs) (y:ys) + | x <= y = x : merge xs (y:ys) + | otherwise = y : merge (x:xs) ys + +-- | Zips two lists together +zipLists :: [a] -> [b] -> [(a, b)] +zipLists [] _ = [] +zipLists _ [] = [] +zipLists (a:as) (b:bs) = (a, b) : zipLists as bs + +-- | Unzips a list of pairs +unzipLists :: [(a, b)] -> ([a], [b]) +unzipLists [] = ([], []) +unzipLists ((a, b):ps) = let (as, bs) = unzipLists ps in (a:as, b:bs) + +-- | Creates a list with n copies of a value +replicate' :: Int -> a -> [a] +replicate' n x | n <= 0 = [] +replicate' n x = x : replicate' (n-1) x + +-- | Returns Just the first element satisfying a predicate, or Nothing +find :: (a -> Bool) -> [a] -> Maybe a +find _ [] = Nothing +find p (x:xs) + | p x = Just x + | otherwise = find p xs + +-- | Returns all elements satisfying a predicate +findAll :: (a -> Bool) -> [a] -> [a] +findAll = filterList + +-- | Checks if any element satisfies a predicate +any' :: (a -> Bool) -> [a] -> Bool +any' _ [] = False +any' p (x:xs) = p x || any' p xs + +-- | Checks if all elements satisfy a predicate +all' :: (a -> Bool) -> [a] -> Bool +all' _ [] = True +all' p (x:xs) = p x && all' p xs + +-- | Safe version of head +headMaybe :: [a] -> Maybe a +headMaybe [] = Nothing +headMaybe (x:_) = Just x + +-- | Safe version of tail +tailMaybe :: [a] -> Maybe [a] +tailMaybe [] = Nothing +tailMaybe (_:xs) = Just xs + +-- | Safe version of last +lastMaybe :: [a] -> Maybe a +lastMaybe [] = Nothing +lastMaybe [x] = Just x +lastMaybe (_:xs) = lastMaybe xs + +-- | Safe version of init +initMaybe :: [a] -> Maybe [a] +initMaybe [] = Nothing +initMaybe [_] = Just [] +initMaybe (x:xs) = case initMaybe xs of + Nothing -> Nothing + Just ys -> Just (x:ys) + +-- | Safe list indexing +at :: [a] -> Int -> Maybe a +at [] _ = Nothing +at (x:_) 0 = Just x +at (_:xs) n | n > 0 = at xs (n-1) + | otherwise = Nothing + +-- | Maps a function over a Maybe +mapMaybe :: (a -> b) -> Maybe a -> Maybe b +mapMaybe _ Nothing = Nothing +mapMaybe f (Just x) = Just (f x) + +-- | Returns the Just value or a default +fromMaybe :: a -> Maybe a -> a +fromMaybe d Nothing = d +fromMaybe _ (Just x) = x + +-- | Converts a Maybe to a list +maybeToList :: Maybe a -> [a] +maybeToList Nothing = [] +maybeToList (Just x) = [x] + +-- | Maps a function over the Left value of an Either +mapLeft :: (a -> c) -> Either a b -> Either c b +mapLeft f (Left x) = Left (f x) +mapLeft _ (Right y) = Right y + +-- | Maps a function over the Right value of an Either +mapRight :: (b -> c) -> Either a b -> Either a c +mapRight _ (Left x) = Left x +mapRight f (Right y) = Right (f y) + +-- | Converts an Either to a Maybe, discarding the Left value +eitherToMaybe :: Either a b -> Maybe b +eitherToMaybe (Left _) = Nothing +eitherToMaybe (Right y) = Just y + +-- | A simple pair type +data Pair a b = Pair a b + +-- | Creates a pair +makePair :: a -> b -> Pair a b +makePair = Pair + +-- | Gets the first element of a pair +fst' :: Pair a b -> a +fst' (Pair a _) = a + +-- | Gets the second element of a pair +snd' :: Pair a b -> b +snd' (Pair _ b) = b + +-- | Swaps the elements of a pair +swap :: Pair a b -> Pair b a +swap (Pair a b) = Pair b a + +-- | A simple triple type +data Triple a b c = Triple a b c + +-- | Creates a triple +makeTriple :: a -> b -> c -> Triple a b c +makeTriple = Triple + +-- | Gets the first element of a triple +fst3 :: Triple a b c -> a +fst3 (Triple a _ _) = a + +-- | Gets the second element of a triple +snd3 :: Triple a b c -> b +snd3 (Triple _ b _) = b + +-- | Gets the third element of a triple +thd3 :: Triple a b c -> c +thd3 (Triple _ _ c) = c + +-- | A simple tree type +data Tree a = Leaf | Node a (Tree a) (Tree a) + +-- | Creates a leaf node +leaf :: Tree a +leaf = Leaf + +-- | Creates a tree node +node :: a -> Tree a -> Tree a -> Tree a +node = Node + +-- | Checks if a tree is empty +isEmpty :: Tree a -> Bool +isEmpty Leaf = True +isEmpty _ = False + +-- | Returns the value at the root of a tree, if any +rootValue :: Tree a -> Maybe a +rootValue Leaf = Nothing +rootValue (Node x _ _) = Just x + +-- | Returns the left subtree +leftSubtree :: Tree a -> Tree a +leftSubtree Leaf = Leaf +leftSubtree (Node _ left _) = left + +-- | Returns the right subtree +rightSubtree :: Tree a -> Tree a +rightSubtree Leaf = Leaf +rightSubtree (Node _ _ right) = right + +-- | Inserts a value into a binary search tree +insertBST :: Ord a => a -> Tree a -> Tree a +insertBST x Leaf = Node x Leaf Leaf +insertBST x (Node y left right) + | x < y = Node y (insertBST x left) right + | x > y = Node y left (insertBST x right) + | otherwise = Node x left right + +-- | Searches for a value in a binary search tree +searchBST :: Ord a => a -> Tree a -> Bool +searchBST _ Leaf = False +searchBST x (Node y left right) + | x == y = True + | x < y = searchBST x left + | otherwise = searchBST x right + +-- | Performs an in-order traversal of a tree +inOrderTraversal :: Tree a -> [a] +inOrderTraversal Leaf = [] +inOrderTraversal (Node x left right) = inOrderTraversal left ++ [x] ++ inOrderTraversal right + +-- | Performs a pre-order traversal of a tree +preOrderTraversal :: Tree a -> [a] +preOrderTraversal Leaf = [] +preOrderTraversal (Node x left right) = [x] ++ preOrderTraversal left ++ preOrderTraversal right + +-- | Performs a post-order traversal of a tree +postOrderTraversal :: Tree a -> [a] +postOrderTraversal Leaf = [] +postOrderTraversal (Node x left right) = postOrderTraversal left ++ postOrderTraversal right ++ [x] + +-- | Calculates the height of a tree +treeHeight :: Tree a -> Int +treeHeight Leaf = 0 +treeHeight (Node _ left right) = 1 + max (treeHeight left) (treeHeight right) + +-- | Calculates the size of a tree (number of nodes) +treeSize :: Tree a -> Int +treeSize Leaf = 0 +treeSize (Node _ left right) = 1 + treeSize left + treeSize right + +-- | Maps a function over a tree +mapTree :: (a -> b) -> Tree a -> Tree b +mapTree _ Leaf = Leaf +mapTree f (Node x left right) = Node (f x) (mapTree f left) (mapTree f right) + +-- | Folds a tree from the left +foldTree :: (a -> b -> b -> b) -> b -> Tree a -> b +foldTree _ acc Leaf = acc +foldTree f acc (Node x left right) = + f x (foldTree f acc left) (foldTree f acc right) + +-- | A simple queue type +data Queue a = Queue [a] [a] + +-- | Creates an empty queue +emptyQueue :: Queue a +emptyQueue = Queue [] [] + +-- | Checks if a queue is empty +isEmptyQueue :: Queue a -> Bool +isEmptyQueue (Queue [] []) = True +isEmptyQueue _ = False + +-- | Adds an element to a queue +enqueue :: a -> Queue a -> Queue a +enqueue x (Queue ins outs) = Queue (x:ins) outs + +-- | Removes an element from a queue +dequeue :: Queue a -> Maybe (a, Queue a) +dequeue (Queue [] []) = Nothing +dequeue (Queue ins []) = dequeue (Queue [] (reverse ins)) +dequeue (Queue ins (x:xs)) = Just (x, Queue ins xs) + +-- | A simple stack type +data Stack a = Stack [a] + +-- | Creates an empty stack +emptyStack :: Stack a +emptyStack = Stack [] + +-- | Checks if a stack is empty +isEmptyStack :: Stack a -> Bool +isEmptyStack (Stack []) = True +isEmptyStack _ = False + +-- | Pushes an element onto a stack +push :: a -> Stack a -> Stack a +push x (Stack xs) = Stack (x:xs) + +-- | Pops an element from a stack +pop :: Stack a -> Maybe (a, Stack a) +pop (Stack []) = Nothing +pop (Stack (x:xs)) = Just (x, Stack xs) + +-- | Peeks at the top element of a stack without removing it +peek :: Stack a -> Maybe a +peek (Stack []) = Nothing +peek (Stack (x:_)) = Just x + +-- | A simple set type +newtype Set a = Set [a] + +-- | Creates an empty set +emptySet :: Set a +emptySet = Set [] + +-- | Checks if a set is empty +isEmptySet :: Set a -> Bool +isEmptySet (Set []) = True +isEmptySet _ = False + +-- | Adds an element to a set +addToSet :: Eq a => a -> Set a -> Set a +addToSet x (Set xs) + | x `elem` xs = Set xs + | otherwise = Set (x:xs) + +-- | Removes an element from a set +removeFromSet :: Eq a => a -> Set a -> Set a +removeFromSet x (Set xs) = Set (filter (/= x) xs) + +-- | Checks if an element is in a set +inSet :: Eq a => a -> Set a -> Bool +inSet x (Set xs) = x `elem` xs + +-- | Converts a set to a list +setToList :: Set a -> [a] +setToList (Set xs) = xs + +-- | Calculates the union of two sets +unionSets :: Eq a => Set a -> Set a -> Set a +unionSets (Set xs) (Set ys) = Set (nub (xs ++ ys)) + where + nub [] = [] + nub (z:zs) = z : nub (filter (/= z) zs) + +-- | Calculates the intersection of two sets +intersectSets :: Eq a => Set a -> Set a -> Set a +intersectSets (Set xs) (Set ys) = Set [x | x <- xs, x `elem` ys] + +-- | Calculates the difference of two sets +diffSets :: Eq a => Set a -> Set a -> Set a +diffSets (Set xs) (Set ys) = Set [x | x <- xs, not (x `elem` ys)] ===================================== testsuite/tests/perf/compiler/Makefile ===================================== @@ -46,3 +46,8 @@ T22744: ./genT22744 '$(TEST_HC)' $(TEST_HC_OPTS) T22744.hs +IfaceRecomp: + '$(TEST_HC)' $(TEST_HC_OPTS) -fno-code -fwrite-interface -fwrite-if-simplified-core -haddock -O -v0 -c IfaceRecompTest.hs -fwrite-if-self-recomp-flags -Werror -Wall + +IfaceRecompSrcChanged: IfaceRecomp + echo "-- change src hash" >> IfaceRecompTest.hs ===================================== testsuite/tests/perf/compiler/all.T ===================================== @@ -794,3 +794,19 @@ test('interpreter_steplocal', ], ghci_script, ['interpreter_steplocal.script']) + + +def ifaceRecompTest(name, iterations, target): + return test(name, + [collect_stats('bytes allocated', 5) + , extra_run_opts(' '.join(['"' + config.libdir + '"', str(iterations), target])) + , pre_cmd('$MAKE -s --no-print-directory ' + name) + , only_ways(['normal']) + , extra_files(['IfaceRecomp.hs', 'IfaceRecompTest.hs']) + , copy_files + ], + multimod_compile_and_run, + ['IfaceRecomp', '-O -package ghc']) + +ifaceRecompTest("IfaceRecomp", 10000, "full") +ifaceRecompTest("IfaceRecompSrcChanged", 10000, "src") View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9b4b5dfabf3ee257b9907c1a95a69a102912ed7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9b4b5dfabf3ee257b9907c1a95a69a102912ed7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/06daebab/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 15:01:32 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 11 Mar 2025 11:01:32 -0400 Subject: [Git][ghc/ghc][wip/iface-tests] testsuite: Add a performance test for interface file checking Message-ID: <67d0504c7ff88_58d2b62bd80892f4@gitlab.mail> Matthew Pickering pushed to branch wip/iface-tests at Glasgow Haskell Compiler / GHC Commits: 5d38d49c by Matthew Pickering at 2025-03-11T15:01:20+00:00 testsuite: Add a performance test for interface file checking This commit adds two tests. * `IfaceRecomp`: Tests the performance of the full recompilation check * `IfaceRecompSrcChanged`: Tests the performance of the recompilation check when the hash of the source file has changed. The IfaceRecompTest.hs file is designed to be "large"-ish in some senses, but the interface file is still not particually large. Some parts of the interface should not be used by the recompilation check: * Core definitions from interface files (`-fwrite-if-simplified-core`) * Haddock docs (`-haddock`) * Extra debugging information about specific flags (`-fwrite-if-self-recomp-flags`) I intend to improve the performance of this test and expand it if necessary in the near future. Fixes #25840 - - - - - 4 changed files: - + testsuite/tests/perf/compiler/IfaceRecomp.hs - + testsuite/tests/perf/compiler/IfaceRecompTest.hs - testsuite/tests/perf/compiler/Makefile - testsuite/tests/perf/compiler/all.T Changes: ===================================== testsuite/tests/perf/compiler/IfaceRecomp.hs ===================================== @@ -0,0 +1,93 @@ +{-# LANGUAGE ScopedTypeVariables #-} +module Main where + +import GHC hiding (SuccessFlag(..)) +import GHC.Utils.Outputable +import GHC.Data.FastString +import GHC.Tc.Utils.Monad +import GHC.Iface.Load +import GHC.Iface.Recomp +import GHC.Driver.Env.Types +import GHC.Driver.Ppr +import GHC.Unit.Types + +import Control.Monad +import System.Environment +import System.FilePath +import System.Directory +import GHC.Data.Maybe +import GHC.Unit.Env +import GHC.Driver.Make +import GHC.Driver.Env + +-- This test checks propeties of reading interface files from disk + +parseMode :: String -> (MaybeValidated ModIface -> Bool) +parseMode "full" = checkFullMode +parseMode "src" = checkSrcMode +parseMode mode = error $ "unknown mode:" ++ mode + +-- Checks performance of a full complete recompilation check +checkFullMode :: MaybeValidated ModIface -> Bool +checkFullMode (UpToDateItem {}) = True +checkFullMode _ = False + +-- Checks performance of a recompilation check that only checks if the source file has changed +checkSrcMode :: MaybeValidated ModIface -> Bool +checkSrcMode (OutOfDateItem (RecompBecause SourceFileChanged) _) = True +checkSrcMode _ = False + +main :: IO () +main = do + args <- getArgs + (libdir, iterations, check) <- case args of + (dir: n: mode: _) -> return (dir, read n, parseMode mode) + _ -> do + error "Error: Expected libdir, iterations, mode" + + + runGhc (Just libdir) $ do + -- Set GHC session flags + -- Parse command line flags + + logger <- getLogger + dflags0 <- getSessionDynFlags + let parseDynFlags dflags as = do + (dflags', _, _) <- parseDynamicFlags logger dflags (map noLoc as) + return dflags' + + -- Set up basic flags for our test + dflags1 <- parseDynFlags dflags0 ["-haddock", "-fwrite-if-self-recomp-flags", "-fno-code", "-fwrite-interface", "-fwrite-if-simplified-core","-v0", "-O"] + _ <- setSessionDynFlags dflags1 + + + -- Get the current directory to find our test module + pwd <- liftIO getCurrentDirectory + let moduleFile = pwd </> "IfaceRecompTest.hs" + + hsc_env <- getSession + let hiFile = pwd </> "IfaceRecompTest.hi" + Right mod_sum <- liftIO $ summariseFile hsc_env (ue_unitHomeUnit (UnitId (mkFastString "main")) (hsc_unit_env hsc_env)) mempty moduleFile Nothing Nothing + + + -- liftIO $ putStrLn $ "Loading interface file: " ++ hiFile + + dflags <- getSessionDynFlags + let test_mod = mkModule (fsToUnit (mkFastString "main")) (mkModuleName "IfaceRecompTest") + + -- Load the interface + mb_iface <- liftIO $ readIface dflags (hsc_NC hsc_env) test_mod hiFile + case mb_iface of + Failed {} -> liftIO $ do + error "Failed to load interface" + Succeeded iface -> do + -- liftIO $ putStrLn "Successfully loaded interface. Now checking it 10000 times." + + -- Call checkOldIface 10000 times + liftIO $ replicateM_ iterations $ do + res <- checkOldIface (hscSetFlags (ms_hspp_opts mod_sum) hsc_env) mod_sum (Just iface) + if check res + then return () + else error $ "Interface check failed: " ++ showSDoc dflags (ppr (fmap (const ()) res)) + + liftIO $ putStrLn "Completed interface checks." ===================================== testsuite/tests/perf/compiler/IfaceRecompTest.hs ===================================== @@ -0,0 +1,500 @@ +{-# LANGUAGE NoImplicitPrelude #-} +module IfaceRecompTest where + +import Prelude (Eq(..), Bool(..), Maybe(..), Int, Ord(..), Either(..), String, Char + , elem, not, filter, (++), otherwise, reverse, Num(..), (&&), (||), seq, (.) + , dropWhile, break, Enum(..), map, length, replicate, concat, fromIntegral + , RealFrac(..), mod, sqrt, all, div ) + +-- | Adds two integers +add :: Int -> Int -> Int +add x y = x + y + +-- | Subtracts second integer from first +subtract :: Int -> Int -> Int +subtract x y = x - y + +-- | Multiplies two integers +multiply :: Int -> Int -> Int +multiply x y = x * y + +-- | Divides first integer by second +divide :: Int -> Int -> Int +divide x y = x `div` y + +-- | Calculates square of an integer +square :: Int -> Int +square x = x * x + +-- | Calculates cube of an integer +cube :: Int -> Int +cube x = x * x * x + +-- | Calculates factorial of a non-negative integer +factorial :: Int -> Int +factorial 0 = 1 +factorial n = n * factorial (n - 1) + +-- | Checks if a number is even +isEven :: Int -> Bool +isEven n = n `mod` 2 == 0 + +-- | Checks if a number is odd +isOdd :: Int -> Bool +isOdd = not . isEven + +-- | Calculates the greatest common divisor of two integers +gcd :: Int -> Int -> Int +gcd a 0 = abs a +gcd a b = gcd b (a `mod` b) + +-- | Calculates the least common multiple of two integers +lcm :: Int -> Int -> Int +lcm a b = abs (a * b) `div` gcd a b + +-- | Checks if a number is prime +isPrime :: Int -> Bool +isPrime n | n <= 1 = False +isPrime 2 = True +isPrime n = all (\x -> n `mod` x /= 0) [2..isqrt n] + where isqrt = floor . sqrt . fromIntegral + +-- | Concatenates two strings +concatStrings :: String -> String -> String +concatStrings = (++) + +-- | Repeats a string n times +repeatString :: String -> Int -> String +repeatString str n = concat (replicate n str) + +-- | Reverses a string +reverseString :: String -> String +reverseString = reverse + +-- | Capitalizes the first letter of a string +capitalize :: String -> String +capitalize [] = [] +capitalize (c:cs) = toUpper c : cs + where toUpper c | 'a' <= c && c <= 'z' = toEnum (fromEnum c - fromEnum 'a' + fromEnum 'A') + | otherwise = c + +-- | Calculates the length of a string +stringLength :: String -> Int +stringLength = length + +-- | Converts a string to uppercase +toUppercase :: String -> String +toUppercase = map toUpper + where toUpper c | 'a' <= c && c <= 'z' = toEnum (fromEnum c - fromEnum 'a' + fromEnum 'A') + | otherwise = c + +-- | Converts a string to lowercase +toLowercase :: String -> String +toLowercase = map toLower + where toLower c | 'A' <= c && c <= 'Z' = toEnum (fromEnum c - fromEnum 'A' + fromEnum 'a') + | otherwise = c + +-- | Checks if a string contains a substring +contains :: String -> String -> Bool +contains str substr = isJust (findSubstring substr str) + where + findSubstring [] _ = Just [] + findSubstring _ [] = Nothing + findSubstring pat@(p:ps) (s:ss) + | p == s && isPrefixOf ps ss = Just pat + | otherwise = findSubstring pat ss + isPrefixOf [] _ = True + isPrefixOf _ [] = False + isPrefixOf (p:ps) (s:ss) = p == s && isPrefixOf ps ss + isJust Nothing = False + isJust (Just _) = True + +-- | Splits a string by a delimiter +splitString :: Char -> String -> [String] +splitString delim str = case break (== delim) str of + (a, []) -> [a] + (a, _:rest) -> a : splitString delim rest + +-- | Joins a list of strings with a delimiter +joinStrings :: String -> [String] -> String +joinStrings delim = intercalate delim + where + intercalate _ [] = [] + intercalate _ [x] = x + intercalate sep (x:xs) = x ++ sep ++ intercalate sep xs + +-- | Trims whitespace from both ends of a string +trim :: String -> String +trim = trimEnd . trimStart + where + trimStart = dropWhile isSpace + trimEnd = reverse . trimStart . reverse + isSpace c = c == ' ' || c == '\t' || c == '\n' || c == '\r' + +-- | Returns the first n elements of a list +take :: Int -> [a] -> [a] +take _ [] = [] +take n _ | n <= 0 = [] +take n (x:xs) = x : take (n-1) xs + +-- | Drops the first n elements from a list +drop :: Int -> [a] -> [a] +drop _ [] = [] +drop n xs | n <= 0 = xs +drop n (_:xs) = drop (n-1) xs + +-- | Splits a list at the nth position +splitAt :: Int -> [a] -> ([a], [a]) +splitAt n xs = (take n xs, drop n xs) + +-- | Maps a function over a list +mapList :: (a -> b) -> [a] -> [b] +mapList _ [] = [] +mapList f (x:xs) = f x : mapList f xs + +-- | Filters a list based on a predicate +filterList :: (a -> Bool) -> [a] -> [a] +filterList _ [] = [] +filterList p (x:xs) + | p x = x : filterList p xs + | otherwise = filterList p xs + +-- | Folds a list from the left +foldl' :: (b -> a -> b) -> b -> [a] -> b +foldl' _ acc [] = acc +foldl' f acc (x:xs) = let acc' = f acc x in acc' `seq` foldl' f acc' xs + +-- | Folds a list from the right +foldr' :: (a -> b -> b) -> b -> [a] -> b +foldr' _ acc [] = acc +foldr' f acc (x:xs) = f x (foldr' f acc xs) + +-- | Removes duplicate elements from a list +nub :: Eq a => [a] -> [a] +nub [] = [] +nub (x:xs) = x : nub (filter (/= x) xs) + +-- | Sorts a list +sort :: Ord a => [a] -> [a] +sort [] = [] +sort (x:xs) = sort [y | y <- xs, y < x] ++ [x] ++ sort [y | y <- xs, y >= x] + +-- | Merges two sorted lists +merge :: Ord a => [a] -> [a] -> [a] +merge [] ys = ys +merge xs [] = xs +merge (x:xs) (y:ys) + | x <= y = x : merge xs (y:ys) + | otherwise = y : merge (x:xs) ys + +-- | Zips two lists together +zipLists :: [a] -> [b] -> [(a, b)] +zipLists [] _ = [] +zipLists _ [] = [] +zipLists (a:as) (b:bs) = (a, b) : zipLists as bs + +-- | Unzips a list of pairs +unzipLists :: [(a, b)] -> ([a], [b]) +unzipLists [] = ([], []) +unzipLists ((a, b):ps) = let (as, bs) = unzipLists ps in (a:as, b:bs) + +-- | Creates a list with n copies of a value +replicate' :: Int -> a -> [a] +replicate' n x | n <= 0 = [] +replicate' n x = x : replicate' (n-1) x + +-- | Returns Just the first element satisfying a predicate, or Nothing +find :: (a -> Bool) -> [a] -> Maybe a +find _ [] = Nothing +find p (x:xs) + | p x = Just x + | otherwise = find p xs + +-- | Returns all elements satisfying a predicate +findAll :: (a -> Bool) -> [a] -> [a] +findAll = filterList + +-- | Checks if any element satisfies a predicate +any' :: (a -> Bool) -> [a] -> Bool +any' _ [] = False +any' p (x:xs) = p x || any' p xs + +-- | Checks if all elements satisfy a predicate +all' :: (a -> Bool) -> [a] -> Bool +all' _ [] = True +all' p (x:xs) = p x && all' p xs + +-- | Safe version of head +headMaybe :: [a] -> Maybe a +headMaybe [] = Nothing +headMaybe (x:_) = Just x + +-- | Safe version of tail +tailMaybe :: [a] -> Maybe [a] +tailMaybe [] = Nothing +tailMaybe (_:xs) = Just xs + +-- | Safe version of last +lastMaybe :: [a] -> Maybe a +lastMaybe [] = Nothing +lastMaybe [x] = Just x +lastMaybe (_:xs) = lastMaybe xs + +-- | Safe version of init +initMaybe :: [a] -> Maybe [a] +initMaybe [] = Nothing +initMaybe [_] = Just [] +initMaybe (x:xs) = case initMaybe xs of + Nothing -> Nothing + Just ys -> Just (x:ys) + +-- | Safe list indexing +at :: [a] -> Int -> Maybe a +at [] _ = Nothing +at (x:_) 0 = Just x +at (_:xs) n | n > 0 = at xs (n-1) + | otherwise = Nothing + +-- | Maps a function over a Maybe +mapMaybe :: (a -> b) -> Maybe a -> Maybe b +mapMaybe _ Nothing = Nothing +mapMaybe f (Just x) = Just (f x) + +-- | Returns the Just value or a default +fromMaybe :: a -> Maybe a -> a +fromMaybe d Nothing = d +fromMaybe _ (Just x) = x + +-- | Converts a Maybe to a list +maybeToList :: Maybe a -> [a] +maybeToList Nothing = [] +maybeToList (Just x) = [x] + +-- | Maps a function over the Left value of an Either +mapLeft :: (a -> c) -> Either a b -> Either c b +mapLeft f (Left x) = Left (f x) +mapLeft _ (Right y) = Right y + +-- | Maps a function over the Right value of an Either +mapRight :: (b -> c) -> Either a b -> Either a c +mapRight _ (Left x) = Left x +mapRight f (Right y) = Right (f y) + +-- | Converts an Either to a Maybe, discarding the Left value +eitherToMaybe :: Either a b -> Maybe b +eitherToMaybe (Left _) = Nothing +eitherToMaybe (Right y) = Just y + +-- | A simple pair type +data Pair a b = Pair a b + +-- | Creates a pair +makePair :: a -> b -> Pair a b +makePair = Pair + +-- | Gets the first element of a pair +fst' :: Pair a b -> a +fst' (Pair a _) = a + +-- | Gets the second element of a pair +snd' :: Pair a b -> b +snd' (Pair _ b) = b + +-- | Swaps the elements of a pair +swap :: Pair a b -> Pair b a +swap (Pair a b) = Pair b a + +-- | A simple triple type +data Triple a b c = Triple a b c + +-- | Creates a triple +makeTriple :: a -> b -> c -> Triple a b c +makeTriple = Triple + +-- | Gets the first element of a triple +fst3 :: Triple a b c -> a +fst3 (Triple a _ _) = a + +-- | Gets the second element of a triple +snd3 :: Triple a b c -> b +snd3 (Triple _ b _) = b + +-- | Gets the third element of a triple +thd3 :: Triple a b c -> c +thd3 (Triple _ _ c) = c + +-- | A simple tree type +data Tree a = Leaf | Node a (Tree a) (Tree a) + +-- | Creates a leaf node +leaf :: Tree a +leaf = Leaf + +-- | Creates a tree node +node :: a -> Tree a -> Tree a -> Tree a +node = Node + +-- | Checks if a tree is empty +isEmpty :: Tree a -> Bool +isEmpty Leaf = True +isEmpty _ = False + +-- | Returns the value at the root of a tree, if any +rootValue :: Tree a -> Maybe a +rootValue Leaf = Nothing +rootValue (Node x _ _) = Just x + +-- | Returns the left subtree +leftSubtree :: Tree a -> Tree a +leftSubtree Leaf = Leaf +leftSubtree (Node _ left _) = left + +-- | Returns the right subtree +rightSubtree :: Tree a -> Tree a +rightSubtree Leaf = Leaf +rightSubtree (Node _ _ right) = right + +-- | Inserts a value into a binary search tree +insertBST :: Ord a => a -> Tree a -> Tree a +insertBST x Leaf = Node x Leaf Leaf +insertBST x (Node y left right) + | x < y = Node y (insertBST x left) right + | x > y = Node y left (insertBST x right) + | otherwise = Node x left right + +-- | Searches for a value in a binary search tree +searchBST :: Ord a => a -> Tree a -> Bool +searchBST _ Leaf = False +searchBST x (Node y left right) + | x == y = True + | x < y = searchBST x left + | otherwise = searchBST x right + +-- | Performs an in-order traversal of a tree +inOrderTraversal :: Tree a -> [a] +inOrderTraversal Leaf = [] +inOrderTraversal (Node x left right) = inOrderTraversal left ++ [x] ++ inOrderTraversal right + +-- | Performs a pre-order traversal of a tree +preOrderTraversal :: Tree a -> [a] +preOrderTraversal Leaf = [] +preOrderTraversal (Node x left right) = [x] ++ preOrderTraversal left ++ preOrderTraversal right + +-- | Performs a post-order traversal of a tree +postOrderTraversal :: Tree a -> [a] +postOrderTraversal Leaf = [] +postOrderTraversal (Node x left right) = postOrderTraversal left ++ postOrderTraversal right ++ [x] + +-- | Calculates the height of a tree +treeHeight :: Tree a -> Int +treeHeight Leaf = 0 +treeHeight (Node _ left right) = 1 + max (treeHeight left) (treeHeight right) + +-- | Calculates the size of a tree (number of nodes) +treeSize :: Tree a -> Int +treeSize Leaf = 0 +treeSize (Node _ left right) = 1 + treeSize left + treeSize right + +-- | Maps a function over a tree +mapTree :: (a -> b) -> Tree a -> Tree b +mapTree _ Leaf = Leaf +mapTree f (Node x left right) = Node (f x) (mapTree f left) (mapTree f right) + +-- | Folds a tree from the left +foldTree :: (a -> b -> b -> b) -> b -> Tree a -> b +foldTree _ acc Leaf = acc +foldTree f acc (Node x left right) = + f x (foldTree f acc left) (foldTree f acc right) + +-- | A simple queue type +data Queue a = Queue [a] [a] + +-- | Creates an empty queue +emptyQueue :: Queue a +emptyQueue = Queue [] [] + +-- | Checks if a queue is empty +isEmptyQueue :: Queue a -> Bool +isEmptyQueue (Queue [] []) = True +isEmptyQueue _ = False + +-- | Adds an element to a queue +enqueue :: a -> Queue a -> Queue a +enqueue x (Queue ins outs) = Queue (x:ins) outs + +-- | Removes an element from a queue +dequeue :: Queue a -> Maybe (a, Queue a) +dequeue (Queue [] []) = Nothing +dequeue (Queue ins []) = dequeue (Queue [] (reverse ins)) +dequeue (Queue ins (x:xs)) = Just (x, Queue ins xs) + +-- | A simple stack type +data Stack a = Stack [a] + +-- | Creates an empty stack +emptyStack :: Stack a +emptyStack = Stack [] + +-- | Checks if a stack is empty +isEmptyStack :: Stack a -> Bool +isEmptyStack (Stack []) = True +isEmptyStack _ = False + +-- | Pushes an element onto a stack +push :: a -> Stack a -> Stack a +push x (Stack xs) = Stack (x:xs) + +-- | Pops an element from a stack +pop :: Stack a -> Maybe (a, Stack a) +pop (Stack []) = Nothing +pop (Stack (x:xs)) = Just (x, Stack xs) + +-- | Peeks at the top element of a stack without removing it +peek :: Stack a -> Maybe a +peek (Stack []) = Nothing +peek (Stack (x:_)) = Just x + +-- | A simple set type +newtype Set a = Set [a] + +-- | Creates an empty set +emptySet :: Set a +emptySet = Set [] + +-- | Checks if a set is empty +isEmptySet :: Set a -> Bool +isEmptySet (Set []) = True +isEmptySet _ = False + +-- | Adds an element to a set +addToSet :: Eq a => a -> Set a -> Set a +addToSet x (Set xs) + | x `elem` xs = Set xs + | otherwise = Set (x:xs) + +-- | Removes an element from a set +removeFromSet :: Eq a => a -> Set a -> Set a +removeFromSet x (Set xs) = Set (filter (/= x) xs) + +-- | Checks if an element is in a set +inSet :: Eq a => a -> Set a -> Bool +inSet x (Set xs) = x `elem` xs + +-- | Converts a set to a list +setToList :: Set a -> [a] +setToList (Set xs) = xs + +-- | Calculates the union of two sets +unionSets :: Eq a => Set a -> Set a -> Set a +unionSets (Set xs) (Set ys) = Set (nub (xs ++ ys)) + where + nub [] = [] + nub (z:zs) = z : nub (filter (/= z) zs) + +-- | Calculates the intersection of two sets +intersectSets :: Eq a => Set a -> Set a -> Set a +intersectSets (Set xs) (Set ys) = Set [x | x <- xs, x `elem` ys] + +-- | Calculates the difference of two sets +diffSets :: Eq a => Set a -> Set a -> Set a +diffSets (Set xs) (Set ys) = Set [x | x <- xs, not (x `elem` ys)] ===================================== testsuite/tests/perf/compiler/Makefile ===================================== @@ -46,3 +46,8 @@ T22744: ./genT22744 '$(TEST_HC)' $(TEST_HC_OPTS) T22744.hs +IfaceRecomp: + '$(TEST_HC)' $(TEST_HC_OPTS) -fno-code -fwrite-interface -fwrite-if-simplified-core -haddock -O -v0 -c IfaceRecompTest.hs -fwrite-if-self-recomp-flags + +IfaceRecompSrcChanged: IfaceRecomp + echo "-- change src hash" >> IfaceRecompTest.hs ===================================== testsuite/tests/perf/compiler/all.T ===================================== @@ -794,3 +794,19 @@ test('interpreter_steplocal', ], ghci_script, ['interpreter_steplocal.script']) + + +def ifaceRecompTest(name, iterations, target): + return test(name, + [collect_stats('bytes allocated', 5) + , extra_run_opts(' '.join(['"' + config.libdir + '"', str(iterations), target])) + , pre_cmd('$MAKE -s --no-print-directory ' + name) + , only_ways(['normal']) + , extra_files(['IfaceRecomp.hs', 'IfaceRecompTest.hs']) + , copy_files + ], + multimod_compile_and_run, + ['IfaceRecomp', '-O -Wall -Werror -package ghc']) + +ifaceRecompTest("IfaceRecomp", 10000, "full") +ifaceRecompTest("IfaceRecompSrcChanged", 10000, "src") View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5d38d49c9d482eee89459981926bd341703eeaf0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5d38d49c9d482eee89459981926bd341703eeaf0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/3b445301/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 16:09:48 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 11 Mar 2025 12:09:48 -0400 Subject: [Git][ghc/ghc][wip/romes/better-main] driver: Move DynFlags consistency fixes off Main Message-ID: <67d0604ca95da_783613fe7d834161@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/better-main at Glasgow Haskell Compiler / GHC Commits: 47fe1b4a by Rodrigo Mesquita at 2025-03-11T16:09:35+00:00 driver: Move DynFlags consistency fixes off Main These consistency fixes found in Main.hs are required for the proper functioning of the compiler and should live together with all remaining fixes in `makeDynFlagsConsistent`. This is especially relevant to GHC applications that shouldn't have to copy/fix themselves possibly inconsistent DynFlags. Additionally, outputs information when verbosity is high about these consistency fixes that were previously quiet, adds information to the Note on consistency of DynFlags, and improves one of the fixes that incorrectly used `dynNow`. - - - - - 7 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - ghc/GHCi/UI.hs - ghc/Main.hs - utils/check-exact/Parsers.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -918,7 +918,7 @@ parseDynamicFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) parseDynamicFlags logger dflags cmdline = do - (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine dflags cmdline + (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine logger dflags cmdline -- flags that have just been read are used by the logger when loading package -- env (this is checked by T16318) let logger1 = setLogFlags logger (initLogFlags dflags1) @@ -1015,11 +1015,13 @@ normalise_hyp fp checkNewDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags checkNewDynFlags logger dflags = do -- See Note [DynFlags consistency] - let (dflags', warnings) = makeDynFlagsConsistent dflags + let (dflags', warnings, infoverb) = makeDynFlagsConsistent dflags let diag_opts = initDiagOpts dflags print_config = initPrintConfig dflags liftIO $ printOrThrowDiagnostics logger print_config diag_opts $ fmap GhcDriverMessage $ warnsToMessages diag_opts warnings + liftIO $ + mapM_ (\(L loc m) -> logMsg logger MCDump loc m) infoverb return dflags' checkNewInteractiveDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -100,8 +100,9 @@ doBackpack [src_filename] = do dflags0 <- getDynFlags let dflags1 = dflags0 let parser_opts1 = initParserOpts dflags1 + logger0 <- getLogger (p_warns, src_opts) <- liftIO $ getOptionsFromFile parser_opts1 (supportedLanguagePragmas dflags1) src_filename - (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma dflags1 src_opts + (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma logger0 dflags1 src_opts modifySession (hscSetFlags dflags) logger <- getLogger -- Get the logger after having set the session flags, -- so that logger options are correctly set. ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -655,10 +655,11 @@ runUnlitPhase hsc_env input_fn output_fn = do getFileArgs :: HscEnv -> FilePath -> IO ((DynFlags, Messages PsMessage, Messages DriverMessage)) getFileArgs hsc_env input_fn = do let dflags0 = hsc_dflags hsc_env + logger = hsc_logger hsc_env parser_opts = initParserOpts dflags0 (warns0, src_opts) <- getOptionsFromFile parser_opts (supportedLanguagePragmas dflags0) input_fn (dflags1, unhandled_flags, warns) - <- parseDynamicFilePragma dflags0 src_opts + <- parseDynamicFilePragma logger dflags0 src_opts checkProcessArgsResult unhandled_flags return (dflags1, warns0, warns) ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -247,6 +247,7 @@ import GHC.Driver.Plugins.External import GHC.Settings.Config import GHC.Core.Unfold import GHC.Driver.CmdLine +import GHC.Utils.Logger import GHC.Utils.Panic import GHC.Utils.Misc import GHC.Utils.Constants (debugIsOn) @@ -806,7 +807,7 @@ updOptLevel n = fst . updOptLevelChanged n -- the parsed 'DynFlags', the left-over arguments, and a list of warnings. -- Throws a 'UsageError' if errors occurred during parsing (such as unknown -- flags or missing arguments). -parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] +parseDynamicFlagsCmdLine :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -816,7 +817,7 @@ parseDynamicFlagsCmdLine = parseDynamicFlagsFull flagsAll True -- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags -- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db). -- Used to parse flags set in a modules pragma. -parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] +parseDynamicFilePragma :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -865,10 +866,11 @@ parseDynamicFlagsFull :: forall m. MonadIO m => [Flag (CmdLineP DynFlags)] -- ^ valid flags to match against -> Bool -- ^ are the arguments from the command line? + -> Logger -- ^ logger -> DynFlags -- ^ current dynamic flags -> [Located String] -- ^ arguments to parse -> m (DynFlags, [Located String], Messages DriverMessage) -parseDynamicFlagsFull activeFlags cmdline dflags0 args = do +parseDynamicFlagsFull activeFlags cmdline logger dflags0 args = do ((leftover, errs, cli_warns), dflags1) <- processCmdLineP activeFlags dflags0 args -- See Note [Handling errors when parsing command-line flags] @@ -884,7 +886,7 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do throwGhcExceptionIO (CmdLineError ("combination not supported: " ++ intercalate "/" (map wayDesc (Set.toAscList theWays)))) - let (dflags3, consistency_warnings) = makeDynFlagsConsistent dflags2 + let (dflags3, consistency_warnings, infoverb) = makeDynFlagsConsistent dflags2 -- Set timer stats & heap size when (enableTimeStats dflags3) $ liftIO enableTimingStats @@ -898,6 +900,9 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do let diag_opts = initDiagOpts dflags3 warns = warnsToMessages diag_opts $ mconcat [consistency_warnings, sh_warns, cli_warns] + liftIO $ + mapM_ (\(L loc m) -> logMsg logger MCDump loc m) infoverb + return (dflags3, leftover, warns) -- | Check (and potentially disable) any extensions that aren't allowed @@ -3491,12 +3496,35 @@ combination when parsing flags, we also need to check when we update the flags; this is because API clients may parse flags but update the DynFlags afterwords, before finally running code inside a session (see T10052 and #10052). + +Host ways vs Build ways mismatch +-------------------------------- +Many consistency checks aim to fix the situation where the wanted build ways +are not compatible with the ways the compiler is built in. This happens when +using the interpreter, TH, and the runtime linker, where the compiler cannot +load objects compiled for ways not matching its own. + +For instance, a profiled-dynamic object can only be loaded by a +profiled-dynamic compiler (and not any other kind of compiler). + +This incompatibility is traditionally solved in either of two ways: + +(1) Force the "wanted" build ways to match the compiler ways exactly, + guaranteeing they match. + +(2) Force the use of the external interpreter. When interpreting is offloaded + to the external interpreter it no longer matters what are the host compiler ways. + +In the checks and fixes performed by `makeDynFlagsConsistent`, the choice +between the two does not seem uniform. TODO: Make this choice more evident and uniform. -} -- | Resolve any internal inconsistencies in a set of 'DynFlags'. -- Returns the consistent 'DynFlags' as well as a list of warnings --- to report to the user. -makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn]) +-- to report to the user, and a list of verbose info msgs. +-- +-- See Note [DynFlags consistency] +makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn], [Located SDoc]) -- Whenever makeDynFlagsConsistent does anything, it starts over, to -- ensure that a later change doesn't invalidate an earlier check. -- Be careful not to introduce potential loops! @@ -3587,13 +3615,41 @@ makeDynFlagsConsistent dflags | LinkMergedObj <- ghcLink dflags , Nothing <- outputFile dflags - = pgmError "--output must be specified when using --merge-objs" + = pgmError "--output must be specified when using --merge-objs" + + -- When we do ghci, force using dyn ways if the target RTS linker + -- only supports dynamic code + | LinkInMemory <- ghcLink dflags + , sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags + , not (ways dflags `hasWay` WayDyn && gopt Opt_ExternalInterpreter dflags) + = flip loopNoWarn "Forcing dynamic way because target RTS linker only supports dynamic code" $ + -- See checkOptions, -fexternal-interpreter is + -- required when using --interactive with a non-standard + -- way (-prof, -static, or -dynamic). + setGeneralFlag' Opt_ExternalInterpreter $ + addWay' WayDyn dflags - | otherwise = (dflags, mempty) + | LinkInMemory <- ghcLink dflags + , not (gopt Opt_ExternalInterpreter dflags) + , targetWays_ dflags /= hostFullWays + = flip loopNoWarn "Forcing ways to the host ways because we're using the interpreter" $ + let dflags_a = dflags { targetWays_ = hostFullWays } + dflags_b = foldl gopt_set dflags_a + $ concatMap (wayGeneralFlags platform) + hostFullWays + dflags_c = foldl gopt_unset dflags_b + $ concatMap (wayUnsetGeneralFlags platform) + hostFullWays + in dflags_c + + | otherwise = (dflags, mempty, mempty) where loc = mkGeneralSrcSpan (fsLit "when making flags consistent") loop updated_dflags warning = case makeDynFlagsConsistent updated_dflags of - (dflags', ws) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws) + (dflags', ws, is) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws, is) + loopNoWarn updated_dflags doc + = case makeDynFlagsConsistent updated_dflags of + (dflags', ws, is) -> (dflags', ws, L loc (text doc):is) platform = targetPlatform dflags arch = platformArch platform os = platformOS platform ===================================== ghc/GHCi/UI.hs ===================================== @@ -3148,7 +3148,7 @@ newDynFlags interactive_only minus_opts = do logger <- getLogger idflags0 <- GHC.getInteractiveDynFlags - (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine idflags0 lopts + (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine logger idflags0 lopts liftIO $ printOrThrowDiagnostics logger (initPrintConfig idflags1) (initDiagOpts idflags1) (GhcDriverMessage <$> warns) when (not $ null leftovers) (unknownFlagsErr $ map unLoc leftovers) @@ -3161,7 +3161,7 @@ newDynFlags interactive_only minus_opts = do dflags0 <- getDynFlags when (not interactive_only) $ do - (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine dflags0 lopts + (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine logger dflags0 lopts must_reload <- GHC.setProgramDynFlags dflags1 -- if the package flags changed, reset the context and link ===================================== ghc/Main.hs ===================================== @@ -224,41 +224,9 @@ main' postLoadMode units dflags0 args flagWarnings = do -- The rest of the arguments are "dynamic" -- Leftover ones are presumably files - (dflags3', fileish_args, dynamicFlagWarnings) <- + (dflags4, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags logger2 dflags2 args' - -- When we do ghci, force using dyn ways if the target RTS linker - -- only supports dynamic code - let dflags3 - | LinkInMemory <- link, - sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags3' - = setDynamicNow $ - -- See checkOptions below, -fexternal-interpreter is - -- required when using --interactive with a non-standard - -- way (-prof, -static, or -dynamic). - setGeneralFlag' Opt_ExternalInterpreter $ - -- Use .o for dynamic object, otherwise it gets dropped - -- with "Warning: ignoring unrecognised input", see - -- objish_suffixes - dflags3' { dynObjectSuf_ = objectSuf dflags3' } - | otherwise - = dflags3' - - let dflags4 = if backendNeedsFullWays bcknd && - not (gopt Opt_ExternalInterpreter dflags3) - then - let platform = targetPlatform dflags3 - dflags3a = dflags3 { targetWays_ = hostFullWays } - dflags3b = foldl gopt_set dflags3a - $ concatMap (wayGeneralFlags platform) - hostFullWays - dflags3c = foldl gopt_unset dflags3b - $ concatMap (wayUnsetGeneralFlags platform) - hostFullWays - in dflags3c - else - dflags3 - let logger4 = setLogFlags logger2 (initLogFlags dflags4) GHC.prettyPrintGhcErrors logger4 $ do @@ -804,7 +772,7 @@ initMulti unitArgsFiles = do dynFlagsAndSrcs <- forM unitArgsFiles $ \f -> do when (verbosity initial_dflags > 2) (liftIO $ print f) args <- liftIO $ expandResponse [f] - (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine initial_dflags (map (mkGeneralLocated f) (removeRTS args)) + (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine logger initial_dflags (map (mkGeneralLocated f) (removeRTS args)) handleSourceError (\e -> do GHC.printException e liftIO $ exitWith (ExitFailure 1)) $ do ===================================== utils/check-exact/Parsers.hs ===================================== @@ -348,12 +348,14 @@ initDynFlags file = do -- Based on GHC backpack driver doBackPack dflags0 <- GHC.getSessionDynFlags let parser_opts0 = GHC.initParserOpts dflags0 + logger <- GHC.getLogger (_, src_opts) <- GHC.liftIO $ GHC.getOptionsFromFile parser_opts0 (GHC.supportedLanguagePragmas dflags0) file - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 src_opts + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 src_opts -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 @@ -375,13 +377,15 @@ initDynFlagsPure fp s = do -- as long as `parseDynamicFilePragma` is impure there seems to be -- no reason to use it. dflags0 <- GHC.getSessionDynFlags + logger <- GHC.getLogger let parser_opts0 = GHC.initParserOpts dflags0 let (_, pragmaInfo) = GHC.getOptions parser_opts0 (GHC.supportedLanguagePragmas dflags0) (GHC.stringToStringBuffer $ s) fp - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 pragmaInfo + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 pragmaInfo -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/47fe1b4ae570d1c11da4043326a4f81bfde8d453 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/47fe1b4ae570d1c11da4043326a4f81bfde8d453 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/b538a301/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 16:56:11 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 12:56:11 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 16 commits: Solve Wanted quantified constraints from Givens Message-ID: <67d06b2b8c3be_90426d38742654c@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: c44bc9c5 by sheaf at 2025-03-11T12:54:52-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 0b35caa6 by Ben Gamari at 2025-03-11T12:54:53-04:00 testsuite: Add testcase for #25577 - - - - - 0d4d0e26 by Ben Gamari at 2025-03-11T12:54:53-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 121ecc47 by Ben Gamari at 2025-03-11T12:54:53-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 4c96f8a6 by Ben Gamari at 2025-03-11T12:54:53-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 028d3d52 by Vladislav Zavialov at 2025-03-11T12:54:55-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - 6483a1ee by Vladislav Zavialov at 2025-03-11T12:54:56-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 8adde5e3 by sheaf at 2025-03-11T12:54:59-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - cecadbfc by sheaf at 2025-03-11T12:54:59-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 44138b36 by sheaf at 2025-03-11T12:54:59-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 8495a23c by Teo Camarasu at 2025-03-11T12:55:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - 299df80e by Teo Camarasu at 2025-03-11T12:55:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - b88eb61f by Matthew Pickering at 2025-03-11T12:55:01-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 46e72fd8 by Matthew Pickering at 2025-03-11T12:55:01-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - d9d6aebf by Matthew Pickering at 2025-03-11T12:55:01-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - d2f3e064 by Matthew Pickering at 2025-03-11T12:55:01-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 100 changed files: - compiler/GHC.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6bb0e2617dd771dd9b059dc1906b268f5e53e440...d2f3e064182fcb50c58ffd21bf131a85c98320ae -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6bb0e2617dd771dd9b059dc1906b268f5e53e440...d2f3e064182fcb50c58ffd21bf131a85c98320ae You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/1daff909/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 16:59:23 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 11 Mar 2025 12:59:23 -0400 Subject: [Git][ghc/ghc][master] 14 commits: Solve Wanted quantified constraints from Givens Message-ID: <67d06beb8486e_90426541b1833047@gitlab.mail> Matthew Pickering pushed to branch master at Glasgow Haskell Compiler / GHC Commits: d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 93 changed files: - compiler/GHC.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/589f40b9525c59d646a8b13cd51057bd350f7849...6bb0e2617dd771dd9b059dc1906b268f5e53e440 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/589f40b9525c59d646a8b13cd51057bd350f7849...6bb0e2617dd771dd9b059dc1906b268f5e53e440 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/faec06b7/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 17:20:37 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 11 Mar 2025 13:20:37 -0400 Subject: [Git][ghc/ghc][wip/nfdata-forcing] 18 commits: users guide: Fix typo Message-ID: <67d070e56db3b_9dbfbc5c74584c@gitlab.mail> Matthew Pickering pushed to branch wip/nfdata-forcing at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 19919eb7 by Matthew Pickering at 2025-03-11T17:19:08+00:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 122 changed files: - compiler/GHC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/using-concurrent.rst - libraries/ghc-boot/GHC/Serialized.hs - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/driver/junit.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b1560f71efad1a37af28c7d739c35403d5b5085b...19919eb73502855267bc5e709762e603e5f5b5a5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b1560f71efad1a37af28c7d739c35403d5b5085b...19919eb73502855267bc5e709762e603e5f5b5a5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/450342b5/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 17:26:45 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Tue, 11 Mar 2025 13:26:45 -0400 Subject: [Git][ghc/ghc][wip/int-index/conpat-one-list-th] 57 commits: compiler: Add export list to GHC.SysTools.Tasks Message-ID: <67d072557c25c_9dbfb5570d06052@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/conpat-one-list-th at Glasgow Haskell Compiler / GHC Commits: 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 189e50c4 by Vladislav Zavialov at 2025-03-11T20:26:10+03:00 Draft: One list in TH's ConP - - - - - 277 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/pmcheck/should_compile/T25164_aux.hs - testsuite/tests/printer/Test24533.stdout - testsuite/tests/quasiquotation/T7918A.hs - testsuite/tests/rename/should_fail/RnPatternSynonymFail.hs - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/th/T19759.hs - testsuite/tests/th/T3899a.hs - testsuite/tests/th/TH_repPatSig_asserts.hs - testsuite/tests/th/TH_repUnboxedTuples.stderr - testsuite/tests/th/TH_unresolvedInfix.hs - testsuite/tests/th/TH_unresolvedInfix.stdout - testsuite/tests/th/overloaded/TH_overloaded_extract.stdout - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ca4aaf1ec91a9bc4ae7fde5796f425f948e5b6c1...189e50c4cbe57dc19dde6fd824c8d4831b6413c5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ca4aaf1ec91a9bc4ae7fde5796f425f948e5b6c1...189e50c4cbe57dc19dde6fd824c8d4831b6413c5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/63fb67a2/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 17:53:35 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 11 Mar 2025 13:53:35 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] New attempt [skip ci] Message-ID: <67d0789fb5f2b_a6d2b14c044923a7@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: f3de74a2 by Simon Peyton Jones at 2025-03-11T17:51:18+00:00 New attempt [skip ci] ...do rules first, using substExpr - - - - - 3 changed files: - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Subst.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -281,7 +281,7 @@ simplRecOrTopPair env bind_cxt old_bndr new_bndr rhs | Just env' <- preInlineUnconditionally env (bindContextLevel bind_cxt) old_bndr rhs env = {-#SCC "simplRecOrTopPair-pre-inline-uncond" #-} - simplTrace "SimplBindr:inline-uncond" (ppr old_bndr) $ + simplTrace "SimplBindr:inline-uncond1" (ppr old_bndr) $ do { tick (PreInlineUnconditionally old_bndr) ; return ( emptyFloats env, env' ) } @@ -1179,7 +1179,7 @@ simplExprF1 _ (Type ty) cont -- The (Type ty) case is handled separately by simplExpr -- and by the other callers of simplExprF -simplExprF1 env (Var v) cont = {-#SCC "simplIdF" #-} simplIdF env v cont +simplExprF1 env (Var v) cont = {-#SCC "simplInId" #-} simplInId env v cont simplExprF1 env (Lit lit) cont = {-#SCC "rebuild" #-} rebuild env (Lit lit) cont simplExprF1 env (Tick t expr) cont = {-#SCC "simplTick" #-} simplTick env t expr cont simplExprF1 env (Cast body co) cont = {-#SCC "simplCast" #-} simplCast env body co cont @@ -1252,7 +1252,8 @@ simplExprF1 env (Let (NonRec bndr rhs) body) cont | Just env' <- preInlineUnconditionally env NotTopLevel bndr rhs env -- Because of the let-can-float invariant, it's ok to -- inline freely, or to drop the binding if it is dead. - = do { tick (PreInlineUnconditionally bndr) + = do { simplTrace "SimplBindr:inline-uncond2" (ppr bndr) $ + tick (PreInlineUnconditionally bndr) ; simplExprF env' body cont } -- Now check for a join point. It's better to do the preInlineUnconditionally @@ -1826,18 +1827,22 @@ simpl_lam env bndr body (ApplyToVal { sc_arg = arg, sc_env = arg_se -- It's wrong to err in either direction -- But fun_ty is an OutType, so is fully substituted - ; if | isSimplified dup -- Don't re-simplify if we've simplified it once - -- Including don't preInlineUnconditionally - -- See Note [Avoiding simplifying repeatedly] - -> completeBindX env from_what bndr arg body cont - - | Just env' <- preInlineUnconditionally env NotTopLevel bndr arg arg_se + ; if | Just env' <- preInlineUnconditionally env NotTopLevel bndr arg arg_se , not (needsCaseBindingL arg_levity arg) + , not ( isSimplified dup && + not (exprIsTrivial arg) && + not (isDeadOcc (idOccInfo bndr)) ) -- Ok to test arg::InExpr in needsCaseBinding because -- exprOkForSpeculation is stable under simplification - -> do { tick (PreInlineUnconditionally bndr) + -> do { simplTrace "SimplBindr:inline-uncond3" (ppr bndr) $ + tick (PreInlineUnconditionally bndr) ; simplLam env' body cont } + | isSimplified dup -- Don't re-simplify if we've simplified it once + -- Including don't preInlineUnconditionally + -- See Note [Avoiding simplifying repeatedly] + -> completeBindX env from_what bndr arg body cont + | otherwise -> simplNonRecE env from_what bndr (arg, arg_se) body cont } @@ -2221,9 +2226,9 @@ Some programs have a /lot/ of data constructors in the source program valuable. -} -simplVar :: SimplEnv -> InVar -> SimplM OutExpr +simplInVar :: SimplEnv -> InVar -> SimplM OutExpr -- Look up an InVar in the environment -simplVar env var +simplInVar env var -- Why $! ? See Note [Bangs in the Simplifier] | isTyVar var = return $! Type $! (substTyVar env var) | isCoVar var = return $! Coercion $! (substCoVar env var) @@ -2234,8 +2239,8 @@ simplVar env var DoneId var1 -> return (Var var1) DoneEx e _ -> return e -simplIdF :: SimplEnv -> InId -> SimplCont -> SimplM (SimplFloats, OutExpr) -simplIdF env var cont +simplInId :: SimplEnv -> InId -> SimplCont -> SimplM (SimplFloats, OutExpr) +simplInId env var cont | Just dc <- isDataConWorkId_maybe var , isLazyDataConRep dc -- See Note [Fast path for lazy data constructors] = rebuild env (Var var) cont @@ -2247,17 +2252,38 @@ simplIdF env var cont where env' = setSubstEnv env tvs cvs ids - DoneId var1 -> - do { rule_base <- getSimplRules - ; let cont' = trimJoinCont var1 (idJoinPointHood var1) cont - info = mkArgInfo env rule_base var1 cont' - ; rebuildCall env info cont' } + DoneId out_id -> simplOutId env out_id cont DoneEx e mb_join -> simplExprF env' e cont' where cont' = trimJoinCont var mb_join cont env' = zapSubstEnv env -- See Note [zapSubstEnv] +--------------------------------------------------------- +simplOutId :: SimplEnv -> OutId -> SimplCont -> SimplM (SimplFloats, OutExpr) +simplOutId env fun cont + = do { rule_base <- getSimplRules + ; let rules_for_me = getRules rule_base fun + + ; mb_match <- tryRules zapped_env rules_for_me fun cont1 + ; case mb_match of { + Just (rhs, cont2) -> simplExprF zapped_env rhs cont2 ; + Nothing -> + + do { logger <- getLogger + ; mb_inline <- tryInlining env logger fun cont1 + ; case mb_inline of{ + Just expr -> do { checkedTick (UnfoldingDone fun) + ; simplExprF zapped_env expr cont1 } ; + Nothing -> + + do { let arg_info = mkArgInfo env rules_for_me fun cont1 + ; rebuildCall zapped_env arg_info cont1 + } } } } } + where + zapped_env = zapSubstEnv env -- See Note [zapSubstEnv] + cont1 = trimJoinCont fun (idJoinPointHood fun) cont + --------------------------------------------------------- -- Dealing with a call site @@ -2285,6 +2311,7 @@ rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_dmds = [] }) con res = argInfoExpr fun rev_args cont_ty = contResultType cont +{- ---------- Try inlining, if ai_rewrite = TryInlining -------- -- In the TryInlining case we try inlining immediately, before simplifying -- any (more) arguments. Why? See Note [Rewrite rules and inlining]. @@ -2303,7 +2330,9 @@ rebuildCall env info@(ArgInfo { ai_fun = fun, ai_args = rev_args ; simplExprF env1 expr full_cont } Nothing -> rebuildCall env (info { ai_rewrite = TryNothing }) cont } +-} +{- ---------- Try rewrite RULES, if ai_rewrite = TryRules -------------- -- See Note [Rewrite rules and inlining] -- See also Note [Trying rewrite rules] @@ -2325,6 +2354,7 @@ rebuildCall env info@(ArgInfo { ai_fun = fun, ai_args = rev_args ApplyToTy {} -> False ApplyToVal {} -> False _ -> True +-} ---------- Simplify type applications and casts -------------- rebuildCall env info (CastIt { sc_co = co, sc_opt = opt, sc_cont = cont }) @@ -2574,42 +2604,41 @@ See Note [No free join points in arityType] in GHC.Core.Opt.Arity -} tryRules :: SimplEnv -> [CoreRule] - -> Id - -> [ArgSpec] -- In /normal, forward/ order + -> OutId -> SimplCont - -> SimplM (Maybe (SimplEnv, CoreExpr, SimplCont)) + -> SimplM (Maybe (CoreExpr, SimplCont)) -tryRules env rules fn args call_cont +tryRules env rules fn cont | null rules = return Nothing - | Just (rule, rule_rhs) <- lookupRule ropts (getUnfoldingInRuleMatch env) + | Just (rule, rule_rhs) <- pprTrace "tryRules" (ppr fn) $ + lookupRule ropts (getUnfoldingInRuleMatch env) (activeRule (seMode env)) fn - (argInfoAppArgs args) rules + (contOutArgs cont) rules -- Fire a rule for the function - = do { logger <- getLogger + = pprTrace "tryRules:success" (ppr fn) $ + do { logger <- getLogger ; checkedTick (RuleFired (ruleName rule)) - ; let cont' = pushSimplifiedArgs zapped_env - (drop (ruleArity rule) args) - call_cont + ; let cont' = dropContArgs (ruleArity rule) cont -- (ruleArity rule) says how -- many args the rule consumed occ_anald_rhs = occurAnalyseExpr rule_rhs -- See Note [Occurrence-analyse after rule firing] ; dump logger rule rule_rhs - ; return (Just (zapped_env, occ_anald_rhs, cont')) } + ; return (Just (occ_anald_rhs, cont')) } -- The occ_anald_rhs and cont' are all Out things -- hence zapping the environment | otherwise -- No rule fires - = do { logger <- getLogger + = pprTrace "tryRules:fail" (ppr fn) $ + do { logger <- getLogger ; nodump logger -- This ensures that an empty file is written ; return Nothing } where - ropts = seRuleOpts env - zapped_env = zapSubstEnv env -- See Note [zapSubstEnv] + ropts = seRuleOpts env printRuleModule rule = parens (maybe (text "BUILTIN") @@ -2621,10 +2650,9 @@ tryRules env rules fn args call_cont = log_rule Opt_D_dump_rule_rewrites "Rule fired" $ vcat [ text "Rule:" <+> ftext (ruleName rule) , text "Module:" <+> printRuleModule rule - , text "Before:" <+> hang (ppr fn) 2 (sep (map ppr args)) - , text "After: " <+> hang (pprCoreExpr rule_rhs) 2 - (sep $ map ppr $ drop (ruleArity rule) args) - , text "Cont: " <+> ppr call_cont ] + , text "Full arity:" <+> ppr (ruleArity rule) + , text "Before:" <+> hang (ppr fn) 2 (ppr cont) + , text "After: " <+> pprCoreExpr rule_rhs ] | logHasDumpFlag logger Opt_D_dump_rule_firings = log_rule Opt_D_dump_rule_firings "Rule fired:" $ @@ -2658,11 +2686,19 @@ trySeqRules :: SimplEnv -> SimplCont -> SimplM (Maybe (SimplEnv, CoreExpr, SimplCont)) -- See Note [User-defined RULES for seq] +-- `in_env` applies to `rhs :: InExpr` but not to `scrut :: OutExpr` trySeqRules in_env scrut rhs cont = do { rule_base <- getSimplRules - ; tryRules in_env (getRules rule_base seqId) seqId out_args rule_cont } + ; let seq_rules = getRules rule_base seqId + ; mb_match <- tryRules out_env seq_rules seqId rule_cont + ; return $ case mb_match of + Just (rhs,cont') -> Just (out_env, rhs, cont') + Nothing -> Nothing } where + out_env = zapSubstEnv in_env no_cast_scrut = drop_casts scrut + + -- All these are OutTypes scrut_ty = exprType no_cast_scrut seq_id_ty = idType seqId -- forall r a (b::TYPE r). a -> b -> b res1_ty = piResultTy seq_id_ty rhs_rep -- forall a (b::TYPE rhs_rep). a -> b -> b @@ -2671,18 +2707,14 @@ trySeqRules in_env scrut rhs cont res4_ty = funResultTy res3_ty -- rhs_ty -> rhs_ty rhs_ty = substTy in_env (exprType rhs) rhs_rep = getRuntimeRep rhs_ty - out_args = [ TyArg { as_arg_ty = rhs_rep - , as_hole_ty = seq_id_ty } - , TyArg { as_arg_ty = scrut_ty - , as_hole_ty = res1_ty } - , TyArg { as_arg_ty = rhs_ty - , as_hole_ty = res2_ty } - , ValArg { as_arg = no_cast_scrut - , as_dmd = seqDmd - , as_hole_ty = res3_ty } ] - rule_cont = ApplyToVal { sc_dup = NoDup, sc_arg = rhs - , sc_env = in_env, sc_cont = cont - , sc_hole_ty = res4_ty } + + rule_cont = ApplyToTy { sc_arg_ty = rhs_rep, sc_hole_ty = seq_id_ty, sc_cont = rule_cont1 } + rule_cont1 = ApplyToTy { sc_arg_ty = scrut_ty, sc_hole_ty = res1_ty, sc_cont = rule_cont2 } + rule_cont2 = ApplyToTy { sc_arg_ty = rhs_ty, sc_hole_ty = res2_ty, sc_cont = rule_cont3 } + rule_cont3 = ApplyToVal { sc_arg = no_cast_scrut, sc_hole_ty = res3_ty, sc_cont = rule_cont4 + , sc_dup = Simplified, sc_env = out_env } + rule_cont4 = ApplyToVal { sc_arg = rhs, sc_hole_ty = res4_ty, sc_cont = cont + , sc_dup = NoDup, sc_env = in_env } -- Lazily evaluated, so we don't do most of this @@ -3161,8 +3193,8 @@ rebuildCase env scrut case_bndr alts@[Alt _ bndrs rhs] cont | is_plain_seq = do { mb_rule <- trySeqRules env scrut rhs cont ; case mb_rule of - Just (env', rule_rhs, cont') -> simplExprF env' rule_rhs cont' - Nothing -> reallyRebuildCase env scrut case_bndr alts cont } + Just (env',rule_rhs, cont') -> simplExprF env' rule_rhs cont' + Nothing -> reallyRebuildCase env scrut case_bndr alts cont } -------------------------------------------------- -- 3. Primop-related case-rules @@ -3726,7 +3758,7 @@ knownCon env scrut dc_floats dc dc_ty_args dc_args bndr bs rhs cont | exprIsTrivial scrut = return (emptyFloats env , extendIdSubst env bndr (DoneEx scrut NotJoinPoint)) -- See Note [Do not duplicate constructor applications] - | otherwise = do { dc_args <- mapM (simplVar env) bs + | otherwise = do { dc_args <- mapM (simplInVar env) bs -- dc_ty_args are already OutTypes, -- but bs are InBndrs ; let con_app = Var (dataConWorkId dc) ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -25,7 +25,7 @@ module GHC.Core.Opt.Simplify.Utils ( isSimplified, contIsStop, contIsDupable, contResultType, contHoleType, contHoleScaling, contIsTrivial, contArgs, contIsRhs, - countArgs, + countArgs, contOutArgs, dropContArgs, mkBoringStop, mkRhsStop, mkLazyArgStop, interestingCallContext, @@ -55,7 +55,6 @@ import GHC.Core.Ppr import GHC.Core.TyCo.Ppr ( pprParendType ) import GHC.Core.FVs import GHC.Core.Utils -import GHC.Core.Rules( RuleEnv, getRules ) import GHC.Core.Opt.Arity import GHC.Core.Unfold import GHC.Core.Unfold.Make @@ -86,6 +85,7 @@ import Control.Monad ( when ) import Data.List ( sortBy ) import GHC.Types.Name.Env import Data.Graph +import Data.Maybe {- ********************************************************************* * * @@ -324,6 +324,7 @@ data ArgInfo = ArgInfo { ai_fun :: OutId, -- The function ai_args :: [ArgSpec], -- ...applied to these args (which are in *reverse* order) + -- NB: all these argumennts are already simplified ai_rewrite :: RewriteCall, -- What transformation to try next for this call -- See Note [Rewrite rules and inlining] in GHC.Core.Opt.Simplify.Iteration @@ -432,6 +433,7 @@ argInfoExpr fun rev_args go (TyArg { as_arg_ty = ty } : as) = go as `App` Type ty go (CastBy co : as) = mkCast (go as) co +{- mkRewriteCall :: Id -> RuleEnv -> RewriteCall -- See Note [Rewrite rules and inlining] in GHC.Core.Opt.Simplify.Iteration -- We try to skip any unnecessary stages: @@ -447,6 +449,7 @@ mkRewriteCall fun rule_env where rules = getRules rule_env fun unf = idUnfolding fun +-} {- ************************************************************************ @@ -585,6 +588,24 @@ contArgs cont -- Do *not* use short-cutting substitution here -- because we want to get as much IdInfo as possible +contOutArgs :: SimplCont -> [OutExpr] +-- Get the leading arguments from the `SimplCont`, as /OutExprs/ +contOutArgs (ApplyToTy { sc_arg_ty = ty, sc_cont = cont }) + = Type ty : contOutArgs cont +contOutArgs (ApplyToVal { sc_dup = dup, sc_arg = arg, sc_env = env, sc_cont = cont }) + | isSimplified dup + = arg : contOutArgs cont + | otherwise + = GHC.Core.Subst.substExprSC (getSubst env) arg : contOutArgs cont +contOutArgs _ + = [] + +dropContArgs :: FullArgCount -> SimplCont -> SimplCont +dropContArgs 0 cont = cont +dropContArgs n (ApplyToTy { sc_cont = cont }) = dropContArgs (n-1) cont +dropContArgs n (ApplyToVal { sc_cont = cont }) = dropContArgs (n-1) cont +dropContArgs n cont = pprPanic "dropContArgs" (ppr n $$ ppr cont) + -- | Describes how the 'SimplCont' will evaluate the hole as a 'SubDemand'. -- This can be more insightful than the limited syntactic context that -- 'SimplCont' provides, because the 'Stop' constructor might carry a useful @@ -616,9 +637,9 @@ contEvalContext k = case k of -- and case binder dmds, see addCaseBndrDmd. No priority right now. ------------------- -mkArgInfo :: SimplEnv -> RuleEnv -> Id -> SimplCont -> ArgInfo +mkArgInfo :: SimplEnv -> [CoreRule] -> Id -> SimplCont -> ArgInfo -mkArgInfo env rule_base fun cont +mkArgInfo env rules_for_fun fun cont | n_val_args < idArity fun -- Note [Unsaturated functions] = ArgInfo { ai_fun = fun, ai_args = [] , ai_rewrite = fun_rewrite @@ -633,11 +654,10 @@ mkArgInfo env rule_base fun cont , ai_dmds = add_type_strictness (idType fun) arg_dmds , ai_discs = arg_discounts } where - n_val_args = countValArgs cont - fun_rewrite = mkRewriteCall fun rule_base - fun_has_rules = case fun_rewrite of - TryRules {} -> True - _ -> False + n_val_args = countValArgs cont + fun_rewrite = TryNothing + + fun_has_rules = not (null rules_for_fun) vanilla_discounts, arg_discounts :: [Int] vanilla_discounts = repeat 0 @@ -1454,6 +1474,10 @@ preInlineUnconditionally -- Reason: we don't want to inline single uses, or discard dead bindings, -- for unlifted, side-effect-ful bindings preInlineUnconditionally env top_lvl bndr rhs rhs_env + = pprTrace "preInlineUnconditionally" (ppr bndr <+> ppr (isJust res)) $ + res + where + res | not pre_inline_unconditionally = Nothing | not active = Nothing | isTopLevel top_lvl && isDeadEndId bndr = Nothing -- Note [Top-level bottoming Ids] @@ -1508,6 +1532,10 @@ preInlineUnconditionally env top_lvl bndr rhs rhs_env canInlineInLam (Lit _) = True canInlineInLam (Lam b e) = isRuntimeVar b || canInlineInLam e canInlineInLam (Tick t e) = not (tickishIsCode t) && canInlineInLam e + canInlineInLam (Var v) = case idOccInfo v of + OneOcc { occ_in_lam = IsInsideLam } -> True + ManyOccs {} -> True + _ -> False canInlineInLam _ = False -- not ticks. Counting ticks cannot be duplicated, and non-counting -- ticks around a Lam will disappear anyway. ===================================== compiler/GHC/Core/Subst.hs ===================================== @@ -239,8 +239,11 @@ substExprSC :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr -- their canonical representatives in the in-scope set substExprSC subst orig_expr | isEmptySubst subst = orig_expr - | otherwise = -- pprTrace "enter subst-expr" (doc $$ ppr orig_expr) $ - substExpr subst orig_expr + | otherwise = pprTrace "enter subst-expr" (ppr subst $$ ppr orig_expr) $ + pprTrace "result subst-expr" (ppr res) $ + res + where + res = substExpr subst orig_expr -- | substExpr applies a substitution to an entire 'CoreExpr'. Remember, -- you may only apply the substitution /once/: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3de74a2ffc48bbb6e75c03c3f0f0d221c6b9f37 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3de74a2ffc48bbb6e75c03c3f0f0d221c6b9f37 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/4c9f177a/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 18:00:01 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 14:00:01 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/drop-pthread-imports Message-ID: <67d07a2131d67_a6d2bc5cd8941ee@gitlab.mail> Ben Gamari pushed new branch wip/drop-pthread-imports at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/drop-pthread-imports You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/bf1756d0/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 11 18:19:25 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 14:19:25 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 17 commits: Solve Wanted quantified constraints from Givens Message-ID: <67d07ead3a28f_a6d2b56aa0498764@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 9fd364a5 by Simon Peyton Jones at 2025-03-11T14:19:09-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 4e2551bd by Teo Camarasu at 2025-03-11T14:19:11-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - a1c2a7a9 by Teo Camarasu at 2025-03-11T14:19:11-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 105 changed files: - compiler/GHC.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d2f3e064182fcb50c58ffd21bf131a85c98320ae...a1c2a7a98ba3feff2bf81181807d98ead79c776e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d2f3e064182fcb50c58ffd21bf131a85c98320ae...a1c2a7a98ba3feff2bf81181807d98ead79c776e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/aec779eb/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 20:44:26 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 11 Mar 2025 16:44:26 -0400 Subject: [Git][ghc/ghc][wip/T25647] some renaming Message-ID: <67d0a0aa96f23_e7e2139e6a860846@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 214aa94c by Patrick at 2025-03-12T04:44:16+08:00 some renaming - - - - - 4 changed files: - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs Changes: ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -717,7 +717,7 @@ rnFamEqn doc atfi groups :: [NonEmpty (LocatedN RdrName)] groups = equivClasses cmpLocated pat_kity_vars - ; traceRn "rnFamEqn: rn_outer_bndrs: " (ppr outer_bndrs <+> ppr rn_outer_bndrs') + ; traceRn "rnFamEqn: rn_outer_bndrs: " (ppr rn_outer_bndrs') ; nms_dups <- mapM (lookupOccRn . unLoc) $ [ tv | (tv :| (_:_)) <- groups ] -- Add to the used variables ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -72,7 +72,7 @@ module GHC.Tc.Gen.HsType ( HoleMode(..), -- Utils - tyLitFromLit, tyLitFromOverloadedLit, expliciteOuterTyVars, impliciteOuterTyVars, + tyLitFromLit, tyLitFromOverloadedLit, explicitOuterTyVars, implicitOuterTyVars, ) where @@ -3281,16 +3281,16 @@ outerTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] outerTyVars (HsOuterImplicit { hso_ximplicit = tvs }) = tvs outerTyVars (HsOuterExplicit { hso_xexplicit = tvbs }) = binderVars tvbs -expliciteOuterTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] +explicitOuterTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] -- The returned [TcTyVar] is not necessarily in dependency order -- at least for the HsOuterImplicit case -expliciteOuterTyVars (HsOuterImplicit {}) = [] -expliciteOuterTyVars (HsOuterExplicit { hso_xexplicit = tvbs }) = binderVars tvbs +explicitOuterTyVars (HsOuterImplicit {}) = [] +explicitOuterTyVars (HsOuterExplicit { hso_xexplicit = tvbs }) = binderVars tvbs -impliciteOuterTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] +implicitOuterTyVars :: HsOuterTyVarBndrs flag GhcTc -> [TcTyVar] -- The returned [TcTyVar] is not necessarily in dependency order -impliciteOuterTyVars (HsOuterImplicit { hso_ximplicit = tvs }) = tvs -impliciteOuterTyVars (HsOuterExplicit {}) = [] +implicitOuterTyVars (HsOuterImplicit { hso_ximplicit = tvs }) = tvs +implicitOuterTyVars (HsOuterExplicit {}) = [] ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -21,7 +21,7 @@ module GHC.Tc.TyCl ( tcFamTyPats, tcTyFamInstEqn, tcAddOpenTyFamInstCtxt, tcMkDataFamInstCtxt, tcAddDataFamInstCtxt, unravelFamInstPats, addConsistencyConstraints, - checkFamTelescope, tcFamInsLHSBinders + checkFamTelescope, tcFamInstLHSBinders ) where import GHC.Prelude @@ -249,10 +249,10 @@ tcTyClGroup (TyClGroup { group_tyclds = tyclds th_bndrs' `plusNameEnv` th_bndrs) } --- tcFamInsLHSBinders :: FamEqn TyVar Name -> TcM [TyVar] -tcFamInsLHSBinders :: TcLevel -> SkolemInfo -> HsOuterFamEqnTyVarBndrs GhcTc -> HsOuterFamEqnTyVarBndrs GhcRn +-- tcFamInstLHSBinders :: FamEqn TyVar Name -> TcM [TyVar] +tcFamInstLHSBinders :: TcLevel -> SkolemInfo -> HsOuterFamEqnTyVarBndrs GhcTc -> HsOuterFamEqnTyVarBndrs GhcRn -> [TcTyVar] -> Type -> WantedConstraints -> IOEnv (Env TcGblEnv TcLclEnv) ([TyCoVar], [TcTyVar]) -tcFamInsLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted = do +tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted = do -- This code (and the stuff immediately above) is very similar -- to that in tcTyFamInstEqnGuts. Maybe we should abstract the -- common code; but for the moment I concluded that it's @@ -260,8 +260,8 @@ tcFamInsLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted -- check there too! -- See Note [Type variables in type families instance decl] - ; let outer_exp_tvs = scopedSort $ expliciteOuterTyVars outer_bndrs - ; let outer_imp_tvs = impliciteOuterTyVars outer_bndrs + ; let outer_exp_tvs = scopedSort $ explicitOuterTyVars outer_bndrs + ; let outer_imp_tvs = implicitOuterTyVars outer_bndrs ; checkFamTelescope tclvl hs_outer_bndrs outer_exp_tvs ; outer_imp_wc_tvs <- liftZonkM $ zonkTcTyVarsToTcTyVarsMaybe $ outer_imp_tvs ++ wcs -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] @@ -274,7 +274,7 @@ tcFamInsLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted ; let final_tvs = scopedSort (qtvs ++ outer_exp_tvs) - ; traceTc "tcFamInsLHSBinders" $ + ; traceTc "tcFamInstLHSBinders" $ vcat [ -- ppr fam_tc text "lhs_ty:" <+> ppr lhs_ty @@ -3485,7 +3485,7 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty ; traceTc "tcTyFamInstEqnGuts 0" (ppr outer_bndrs $$ ppr skol_info) -- -- See Note [Type variables in type families instance decl] - ; (final_tvs, qtvs) <- tcFamInsLHSBinders tclvl skol_info outer_bndrs outer_hs_bndrs wcs lhs_ty wanted + ; (final_tvs, qtvs) <- tcFamInstLHSBinders tclvl skol_info outer_bndrs outer_hs_bndrs wcs lhs_ty wanted -- See Note [Error on unconstrained meta-variables] in GHC.Tc.Utils.TcMType -- Example: typecheck/should_fail/T17301 ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -1017,7 +1017,7 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity , lhs_applied_kind , res_kind ) } - ; (final_tvs, qtvs) <- tcFamInsLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted + ; (final_tvs, qtvs) <- tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted ; (final_tvs, non_user_tvs, lhs_ty, master_res_kind, instance_res_kind, stupid_theta) <- liftZonkM $ do View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/214aa94c6a723c926f581ed4157724f70daed1d0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/214aa94c6a723c926f581ed4157724f70daed1d0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/1b28655f/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 22:05:11 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 18:05:11 -0400 Subject: [Git][ghc/ghc][wip/T23675] 3 commits: ghc-toolchain: Add support for otool, install-name-tool Message-ID: <67d0b397d92d8_fb49d459bd845361@gitlab.mail> Ben Gamari pushed to branch wip/T23675 at Glasgow Haskell Compiler / GHC Commits: 0aed169e by Ben Gamari at 2025-03-11T17:32:36-04:00 ghc-toolchain: Add support for otool, install-name-tool Fixes part of ghc#23675. - - - - - 2e552175 by Ben Gamari at 2025-03-11T17:38:00-04:00 ghc-toolchain: Add support for llc, opt, llvm-as Fixes #23675. - - - - - 5ed3015e by Ben Gamari at 2025-03-11T18:03:02-04:00 configure: Don't force value of OTOOL, etc. if not present Previously if `otool` and `install_name_tool` were not present they would be overridden by `fp_settings.m4`. This logic was introduced in 4ff93292243888545da452ea4d4c1987f2343591 without explanation. - - - - - 7 changed files: - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - m4/fp_settings.m4 - m4/ghc_toolchain.m4 - m4/prep_target_file.m4 - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs Changes: ===================================== hadrian/cfg/default.host.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Nothing , tgtNm = Nm {nmProgram = Program {prgPath = "", prgFlags = []}} , tgtMergeObjs = Just (MergeObjs {mergeObjsProgram = Program {prgPath = "@LD_STAGE0@", prgFlags = ["-r"]}, mergeObjsSupportsResponseFiles = False}) +, tgtLlc = Nothing +, tgtOpt = Nothing +, tgtLlvmAs = Nothing , tgtWindres = Nothing +, tgtOtool = Nothing +, tgtInstallNameTool = Nothing } ===================================== hadrian/cfg/default.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Just (Ranlib {ranlibProgram = Program {prgPath = "@RanlibCmd@", prgFlags = []}}) , tgtNm = Nm {nmProgram = Program {prgPath = "@NmCmd@", prgFlags = []}} , tgtMergeObjs = @MergeObjsCmdMaybe@ +, tgtLlc = @LlcCmdMaybeProg@ +, tgtOpt = @OptCmdMaybeProg@ +, tgtLlvmAs = @LlvmAsCmdMaybeProg@ , tgtWindres = @WindresCmdMaybeProg@ +, tgtOtool = @OtoolCmdMaybeProg@ +, tgtInstallNameTool = @InstallNameToolCmdMaybeProg@ } ===================================== m4/fp_settings.m4 ===================================== @@ -136,14 +136,7 @@ AC_DEFUN([FP_SETTINGS], fi # Mac-only tools - if test -z "$OtoolCmd"; then - OtoolCmd="otool" - fi SettingsOtoolCommand="$OtoolCmd" - - if test -z "$InstallNameToolCmd"; then - InstallNameToolCmd="install_name_tool" - fi SettingsInstallNameToolCommand="$InstallNameToolCmd" SettingsCCompilerSupportsNoPie="$CONF_GCC_SUPPORTS_NO_PIE" ===================================== m4/ghc_toolchain.m4 ===================================== @@ -107,6 +107,9 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN], echo "--merge-objs=$MergeObjsCmd" >> acargs echo "--readelf=$READELF" >> acargs echo "--windres=$WindresCmd" >> acargs + echo "--llc=$LlcCmd" >> acargs + echo "--opt=$OptCmd" >> acargs + echo "--llvm-as=$LlvmAsCmd" >> acargs if test -n "$USER_LD"; then echo "--ld=$USER_LD" >> acargs ===================================== m4/prep_target_file.m4 ===================================== @@ -10,6 +10,38 @@ # This toolchain will additionally be used to validate the one generated by # ghc-toolchain. See Note [ghc-toolchain consistency checking]. +# PREP_LIST +# ============ +# +# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a +# space-separated list of args +# i.e. +# "arg1 arg2 arg3" +# ==> +# ["arg1","arg2","arg3"] +# +# $1 = list variable to substitute +dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'. +AC_DEFUN([PREP_LIST],[ + # shell array + set -- $$1 + $1List="@<:@" + if test "[$]#" -eq 0; then + # no arguments + true + else + $1List="${$1List}\"[$]1\"" + shift # drop first elem + for arg in "[$]@" + do + $1List="${$1List},\"$arg\"" + done + fi + $1List="${$1List}@:>@" + + AC_SUBST([$1List]) +]) + # PREP_MAYBE_SIMPLE_PROGRAM # ========================= # @@ -27,6 +59,25 @@ AC_DEFUN([PREP_MAYBE_SIMPLE_PROGRAM],[ AC_SUBST([$1MaybeProg]) ]) +# PREP_MAYBE_PROGRAM +# ========================= +# +# Introduce a substitution [$1MaybeProg] with +# * Nothing, if $$1 is empty +# * Just (Program {prgPath = "$$1", prgFlags = [elements of $$2]}), otherwise +# +# $1 = optional program path +# $2 = program arguments +AC_DEFUN([PREP_MAYBE_PROGRAM],[ + if test -z "$$1"; then + $1MaybeProg=Nothing + else + PREP_LIST([$2]) + $1MaybeProg="Just (Program {prgPath = \"$$1\", prgFlags = $$2List})" + fi + AC_SUBST([$1MaybeProg]) +]) + # PREP_MAYBE_STRING # ========================= # @@ -86,38 +137,6 @@ AC_DEFUN([PREP_NOT_BOOLEAN],[ AC_SUBST([Not$1Bool]) ]) -# PREP_LIST -# ============ -# -# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a -# space-separated list of args -# i.e. -# "arg1 arg2 arg3" -# ==> -# ["arg1","arg2","arg3"] -# -# $1 = list variable to substitute -dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'. -AC_DEFUN([PREP_LIST],[ - # shell array - set -- $$1 - $1List="@<:@" - if test "[$]#" -eq 0; then - # no arguments - true - else - $1List="${$1List}\"[$]1\"" - shift # drop first elem - for arg in "[$]@" - do - $1List="${$1List},\"$arg\"" - done - fi - $1List="${$1List}@:>@" - - AC_SUBST([$1List]) -]) - # Eventually: PREP_BUILD_TARGET_FILE, PREP_HOST_TARGET_FILE, PREP_TARGET_TARGET_FILE # Prepares required substitutions to generate the target file AC_DEFUN([PREP_TARGET_FILE],[ @@ -148,7 +167,12 @@ AC_DEFUN([PREP_TARGET_FILE],[ PREP_LIST([JavaScriptCPPArgs]) PREP_LIST([CmmCPPArgs]) PREP_LIST([CmmCPPArgs_STAGE0]) + PREP_MAYBE_SIMPLE_PROGRAM([LlcCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OptCmd]) + PREP_MAYBE_PROGRAM([LlvmAsCmd], [LlvmAsFlags]) PREP_MAYBE_SIMPLE_PROGRAM([WindresCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OtoolCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([InstallNameToolCmd]) PREP_MAYBE_STRING([TargetVendor_CPP]) PREP_MAYBE_STRING([HostVendor_CPP]) PREP_LIST([CONF_CPP_OPTS_STAGE2]) ===================================== utils/ghc-toolchain/exe/Main.hs ===================================== @@ -52,7 +52,12 @@ data Opts = Opts , optNm :: ProgOpt , optReadelf :: ProgOpt , optMergeObjs :: ProgOpt + , optLlc :: ProgOpt + , optOpt :: ProgOpt + , optLlvmAs :: ProgOpt , optWindres :: ProgOpt + , optOtool :: ProgOpt + , optInstallNameTool :: ProgOpt -- Note we don't actually configure LD into anything but -- see #23857 and #22550 for the very unfortunate story. , optLd :: ProgOpt @@ -99,8 +104,13 @@ emptyOpts = Opts , optNm = po0 , optReadelf = po0 , optMergeObjs = po0 + , optLlc = po0 + , optOpt = po0 + , optLlvmAs = po0 , optWindres = po0 , optLd = po0 + , optOtool = po0 + , optInstallNameTool = po0 , optUnregisterised = Nothing , optTablesNextToCode = Nothing , optUseLibFFIForAdjustors = Nothing @@ -112,7 +122,8 @@ emptyOpts = Opts po0 = emptyProgOpt _optCc, _optCxx, _optCpp, _optHsCpp, _optJsCpp, _optCmmCpp, _optCcLink, _optAr, - _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optWindres, _optLd + _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optLlc, _optOpt, _optLlvmAs, + _optWindres, _optLd, _optOtool, _optInstallNameTool :: Lens Opts ProgOpt _optCc = Lens optCc (\x o -> o {optCc=x}) _optCxx = Lens optCxx (\x o -> o {optCxx=x}) @@ -126,8 +137,13 @@ _optRanlib = Lens optRanlib (\x o -> o {optRanlib=x}) _optNm = Lens optNm (\x o -> o {optNm=x}) _optReadelf = Lens optReadelf (\x o -> o {optReadelf=x}) _optMergeObjs = Lens optMergeObjs (\x o -> o {optMergeObjs=x}) +_optLlc = Lens optLlc (\x o -> o {optLlc=x}) +_optOpt = Lens optOpt (\x o -> o {optOpt=x}) +_optLlvmAs = Lens optLlvmAs (\x o -> o {optLlvmAs=x}) _optWindres = Lens optWindres (\x o -> o {optWindres=x}) -_optLd = Lens optLd (\x o -> o {optLd= x}) +_optLd = Lens optLd (\x o -> o {optLd=x}) +_optOtool = Lens optOtool (\x o -> o {optOtool=x}) +_optInstallNameTool = Lens optInstallNameTool (\x o -> o {optInstallNameTool=x}) _optTriple :: Lens Opts (Maybe String) _optTriple = Lens optTriple (\x o -> o {optTriple=x}) @@ -183,8 +199,13 @@ options = , progOpts "nm" "nm archiver" _optNm , progOpts "readelf" "readelf utility" _optReadelf , progOpts "merge-objs" "linker for merging objects" _optMergeObjs + , progOpts "llc" "LLVM llc utility" _optLlc + , progOpts "opt" "LLVM opt utility" _optOpt + , progOpts "llvm-as" "Assembler used for LLVM backend (typically clang)" _optLlvmAs , progOpts "windres" "windres utility" _optWindres , progOpts "ld" "linker" _optLd + , progOpts "otool" "otool utility" _optOtool + , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool ] where progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)] @@ -434,6 +455,11 @@ mkTarget opts = do when (isNothing mergeObjs && not (arSupportsDashL ar)) $ throwE "Neither a object-merging tool (e.g. ld -r) nor an ar that supports -L is available" + -- LLVM toolchain + llc <- optional $ findProgram "llc" (optLlc opts) ["llc"] + opt <- optional $ findProgram "opt" (optOpt opts) ["opt"] + llvmAs <- optional $ findProgram "llvm assembler" (optLlvmAs opts) ["clang"] + -- Windows-specific utilities windres <- case archOS_OS archOs of @@ -442,6 +468,15 @@ mkTarget opts = do return (Just windres) _ -> return Nothing + -- Darwin-specific utilities + (otool, installNameTool) <- + case archOS_OS archOs of + OSDarwin -> do + otool <- findProgram "otool" (optOtool opts) ["otool"] + installNameTool <- findProgram "install-name-tool" (optInstallNameTool opts) ["install-name-tool"] + return (Just otool, Just installNameTool) + _ -> return (Nothing, Nothing) + -- various other properties of the platform tgtWordSize <- checkWordSize cc tgtEndianness <- checkEndianness cc @@ -478,7 +513,12 @@ mkTarget opts = do , tgtRanlib = ranlib , tgtNm = nm , tgtMergeObjs = mergeObjs + , tgtLlc = llc + , tgtOpt = opt + , tgtLlvmAs = llvmAs , tgtWindres = windres + , tgtOtool = otool + , tgtInstallNameTool = installNameTool , tgtWordSize , tgtEndianness , tgtUnregisterised ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Target.hs ===================================== @@ -72,8 +72,18 @@ data Target = Target , tgtMergeObjs :: Maybe MergeObjs -- ^ We don't need a merge objects tool if we @Ar@ supports @-L@ + -- LLVM backend toolchain + , tgtLlc :: Maybe Program + , tgtOpt :: Maybe Program + , tgtLlvmAs :: Maybe Program + -- ^ assembler used to assemble LLVM backend output; typically @clang@ + -- Windows-specific tools , tgtWindres :: Maybe Program + + -- Darwin-specific tools + , tgtOtool :: Maybe Program + , tgtInstallNameTool :: Maybe Program } deriving (Read, Eq, Ord) @@ -121,6 +131,11 @@ instance Show Target where , ", tgtRanlib = " ++ show tgtRanlib , ", tgtNm = " ++ show tgtNm , ", tgtMergeObjs = " ++ show tgtMergeObjs + , ", tgtLlc = " ++ show tgtLlc + , ", tgtOpt = " ++ show tgtOpt + , ", tgtLlvmAs = " ++ show tgtLlvmAs , ", tgtWindres = " ++ show tgtWindres + , ", tgtOtool = " ++ show tgtOtool + , ", tgtInstallNameTool = " ++ show tgtInstallNameTool , "}" ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/162094c9790a5c1b6154a118bae8b765b83f79a3...5ed3015e94abc1bca775d68b78d7f43860c8e275 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/162094c9790a5c1b6154a118bae8b765b83f79a3...5ed3015e94abc1bca775d68b78d7f43860c8e275 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/e5e43791/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 22:18:48 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 18:18:48 -0400 Subject: [Git][ghc/ghc][wip/T23675] 39 commits: Remove most of `GHC.Internal.Pack` Message-ID: <67d0b6c84cdac_108d47d4aa87369d@gitlab.mail> Ben Gamari pushed to branch wip/T23675 at Glasgow Haskell Compiler / GHC Commits: 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - c79d070d by Ben Gamari at 2025-03-11T18:18:05-04:00 configure: Don't force value of OTOOL, etc. if not present Previously if `otool` and `install_name_tool` were not present they would be overridden by `fp_settings.m4`. This logic was introduced in 4ff93292243888545da452ea4d4c1987f2343591 without explanation. - - - - - a4d9c6fd by Ben Gamari at 2025-03-11T18:18:05-04:00 ghc-toolchain: Add support for otool, install-name-tool Fixes part of ghc#23675. - - - - - 2fb1e554 by Ben Gamari at 2025-03-11T18:18:06-04:00 ghc-toolchain: Add support for llc, opt, llvm-as Fixes #23675. - - - - - 188 changed files: - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Unique.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - m4/ghc_toolchain.m4 - m4/prep_target_file.m4 - rts/include/RtsAPI.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5ed3015e94abc1bca775d68b78d7f43860c8e275...2fb1e554cc5ada6f4a318aba8a5db0e7a3f36a85 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5ed3015e94abc1bca775d68b78d7f43860c8e275...2fb1e554cc5ada6f4a318aba8a5db0e7a3f36a85 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/220a9416/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 22:21:48 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 18:21:48 -0400 Subject: [Git][ghc/ghc][wip/T23675] 2 commits: ghc-toolchain: Add support for otool, install-name-tool Message-ID: <67d0b77c89818_108d471d6fa07454a@gitlab.mail> Ben Gamari pushed to branch wip/T23675 at Glasgow Haskell Compiler / GHC Commits: 01b9273a by Ben Gamari at 2025-03-11T18:21:40-04:00 ghc-toolchain: Add support for otool, install-name-tool Fixes part of ghc#23675. - - - - - fc07b812 by Ben Gamari at 2025-03-11T18:21:40-04:00 ghc-toolchain: Add support for llc, opt, llvm-as Fixes #23675. - - - - - 7 changed files: - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - hadrian/src/Rules/Generate.hs - m4/ghc_toolchain.m4 - m4/prep_target_file.m4 - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs Changes: ===================================== hadrian/cfg/default.host.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Nothing , tgtNm = Nm {nmProgram = Program {prgPath = "", prgFlags = []}} , tgtMergeObjs = Just (MergeObjs {mergeObjsProgram = Program {prgPath = "@LD_STAGE0@", prgFlags = ["-r"]}, mergeObjsSupportsResponseFiles = False}) +, tgtLlc = Nothing +, tgtOpt = Nothing +, tgtLlvmAs = Nothing , tgtWindres = Nothing +, tgtOtool = Nothing +, tgtInstallNameTool = Nothing } ===================================== hadrian/cfg/default.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Just (Ranlib {ranlibProgram = Program {prgPath = "@RanlibCmd@", prgFlags = []}}) , tgtNm = Nm {nmProgram = Program {prgPath = "@NmCmd@", prgFlags = []}} , tgtMergeObjs = @MergeObjsCmdMaybe@ +, tgtLlc = @LlcCmdMaybeProg@ +, tgtOpt = @OptCmdMaybeProg@ +, tgtLlvmAs = @LlvmAsCmdMaybeProg@ , tgtWindres = @WindresCmdMaybeProg@ +, tgtOtool = @OtoolCmdMaybeProg@ +, tgtInstallNameTool = @InstallNameToolCmdMaybeProg@ } ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -508,9 +508,9 @@ generateSettings settingsFile = do , ("ar flags", queryTarget arFlags) , ("ar supports at file", queryTarget arSupportsAtFile') , ("ar supports -L", queryTarget arSupportsDashL') - , ("ranlib command", queryTarget ranlibPath) - , ("otool command", expr $ settingsFileSetting ToolchainSetting_OtoolCommand) - , ("install_name_tool command", expr $ settingsFileSetting ToolchainSetting_InstallNameToolCommand) + , ("ranlib command", queryTarget ranlibPath) + , ("otool command", queryTarget otoolPath) + , ("install_name_tool command", queryTarget installNameToolPath) , ("windres command", queryTarget (maybe "/bin/false" prgPath . tgtWindres)) -- TODO: /bin/false is not available on many distributions by default, but we keep it as it were before the ghc-toolchain patch. Fix-me. , ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit }))) , ("cross compiling", expr $ yesNo <$> flag CrossCompiling) @@ -525,10 +525,10 @@ generateSettings settingsFile = do , ("target has libm", expr $ lookupSystemConfig "target-has-libm") , ("Unregisterised", queryTarget (yesNo . tgtUnregisterised)) , ("LLVM target", queryTarget tgtLlvmTarget) - , ("LLVM llc command", expr $ settingsFileSetting ToolchainSetting_LlcCommand) - , ("LLVM opt command", expr $ settingsFileSetting ToolchainSetting_OptCommand) - , ("LLVM llvm-as command", expr $ settingsFileSetting ToolchainSetting_LlvmAsCommand) - , ("LLVM llvm-as flags", expr $ settingsFileSetting ToolchainSetting_LlvmAsFlags) + , ("LLVM llc command", queryTarget llcPath) + , ("LLVM opt command", queryTarget optPath) + , ("LLVM llvm-as command", queryTarget llvmAsPath) + , ("LLVM llvm-as flags", queryTarget llvmAsFlags) , ("Use inplace MinGW toolchain", expr $ settingsFileSetting ToolchainSetting_DistroMinGW) , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs) @@ -571,10 +571,16 @@ generateSettings settingsFile = do linkSupportsFilelist = yesNo . ccLinkSupportsFilelist . tgtCCompilerLink linkSupportsCompactUnwind = yesNo . ccLinkSupportsCompactUnwind . tgtCCompilerLink linkIsGnu = yesNo . ccLinkIsGnu . tgtCCompilerLink + llcPath = maybe "" prgPath . tgtLlc + optPath = maybe "" prgPath . tgtOpt + llvmAsPath = maybe "" prgPath . tgtLlvmAs + llvmAsFlags = escapeArgs . maybe [] prgFlags . tgtLlvmAs arPath = prgPath . arMkArchive . tgtAr arFlags = escapeArgs . prgFlags . arMkArchive . tgtAr arSupportsAtFile' = yesNo . arSupportsAtFile . tgtAr arSupportsDashL' = yesNo . arSupportsDashL . tgtAr + otoolPath = maybe "" prgPath . tgtOtool + installNameToolPath = maybe "" prgPath . tgtInstallNameTool ranlibPath = maybe "" (prgPath . ranlibProgram) . tgtRanlib mergeObjsSupportsResponseFiles' = maybe "NO" (yesNo . mergeObjsSupportsResponseFiles) . tgtMergeObjs ===================================== m4/ghc_toolchain.m4 ===================================== @@ -107,6 +107,9 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN], echo "--merge-objs=$MergeObjsCmd" >> acargs echo "--readelf=$READELF" >> acargs echo "--windres=$WindresCmd" >> acargs + echo "--llc=$LlcCmd" >> acargs + echo "--opt=$OptCmd" >> acargs + echo "--llvm-as=$LlvmAsCmd" >> acargs if test -n "$USER_LD"; then echo "--ld=$USER_LD" >> acargs ===================================== m4/prep_target_file.m4 ===================================== @@ -10,6 +10,38 @@ # This toolchain will additionally be used to validate the one generated by # ghc-toolchain. See Note [ghc-toolchain consistency checking]. +# PREP_LIST +# ============ +# +# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a +# space-separated list of args +# i.e. +# "arg1 arg2 arg3" +# ==> +# ["arg1","arg2","arg3"] +# +# $1 = list variable to substitute +dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'. +AC_DEFUN([PREP_LIST],[ + # shell array + set -- $$1 + $1List="@<:@" + if test "[$]#" -eq 0; then + # no arguments + true + else + $1List="${$1List}\"[$]1\"" + shift # drop first elem + for arg in "[$]@" + do + $1List="${$1List},\"$arg\"" + done + fi + $1List="${$1List}@:>@" + + AC_SUBST([$1List]) +]) + # PREP_MAYBE_SIMPLE_PROGRAM # ========================= # @@ -27,6 +59,25 @@ AC_DEFUN([PREP_MAYBE_SIMPLE_PROGRAM],[ AC_SUBST([$1MaybeProg]) ]) +# PREP_MAYBE_PROGRAM +# ========================= +# +# Introduce a substitution [$1MaybeProg] with +# * Nothing, if $$1 is empty +# * Just (Program {prgPath = "$$1", prgFlags = [elements of $$2]}), otherwise +# +# $1 = optional program path +# $2 = program arguments +AC_DEFUN([PREP_MAYBE_PROGRAM],[ + if test -z "$$1"; then + $1MaybeProg=Nothing + else + PREP_LIST([$2]) + $1MaybeProg="Just (Program {prgPath = \"$$1\", prgFlags = $$2List})" + fi + AC_SUBST([$1MaybeProg]) +]) + # PREP_MAYBE_STRING # ========================= # @@ -86,38 +137,6 @@ AC_DEFUN([PREP_NOT_BOOLEAN],[ AC_SUBST([Not$1Bool]) ]) -# PREP_LIST -# ============ -# -# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a -# space-separated list of args -# i.e. -# "arg1 arg2 arg3" -# ==> -# ["arg1","arg2","arg3"] -# -# $1 = list variable to substitute -dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'. -AC_DEFUN([PREP_LIST],[ - # shell array - set -- $$1 - $1List="@<:@" - if test "[$]#" -eq 0; then - # no arguments - true - else - $1List="${$1List}\"[$]1\"" - shift # drop first elem - for arg in "[$]@" - do - $1List="${$1List},\"$arg\"" - done - fi - $1List="${$1List}@:>@" - - AC_SUBST([$1List]) -]) - # Eventually: PREP_BUILD_TARGET_FILE, PREP_HOST_TARGET_FILE, PREP_TARGET_TARGET_FILE # Prepares required substitutions to generate the target file AC_DEFUN([PREP_TARGET_FILE],[ @@ -148,7 +167,12 @@ AC_DEFUN([PREP_TARGET_FILE],[ PREP_LIST([JavaScriptCPPArgs]) PREP_LIST([CmmCPPArgs]) PREP_LIST([CmmCPPArgs_STAGE0]) + PREP_MAYBE_SIMPLE_PROGRAM([LlcCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OptCmd]) + PREP_MAYBE_PROGRAM([LlvmAsCmd], [LlvmAsFlags]) PREP_MAYBE_SIMPLE_PROGRAM([WindresCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OtoolCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([InstallNameToolCmd]) PREP_MAYBE_STRING([TargetVendor_CPP]) PREP_MAYBE_STRING([HostVendor_CPP]) PREP_LIST([CONF_CPP_OPTS_STAGE2]) ===================================== utils/ghc-toolchain/exe/Main.hs ===================================== @@ -52,7 +52,12 @@ data Opts = Opts , optNm :: ProgOpt , optReadelf :: ProgOpt , optMergeObjs :: ProgOpt + , optLlc :: ProgOpt + , optOpt :: ProgOpt + , optLlvmAs :: ProgOpt , optWindres :: ProgOpt + , optOtool :: ProgOpt + , optInstallNameTool :: ProgOpt -- Note we don't actually configure LD into anything but -- see #23857 and #22550 for the very unfortunate story. , optLd :: ProgOpt @@ -99,8 +104,13 @@ emptyOpts = Opts , optNm = po0 , optReadelf = po0 , optMergeObjs = po0 + , optLlc = po0 + , optOpt = po0 + , optLlvmAs = po0 , optWindres = po0 , optLd = po0 + , optOtool = po0 + , optInstallNameTool = po0 , optUnregisterised = Nothing , optTablesNextToCode = Nothing , optUseLibFFIForAdjustors = Nothing @@ -112,7 +122,8 @@ emptyOpts = Opts po0 = emptyProgOpt _optCc, _optCxx, _optCpp, _optHsCpp, _optJsCpp, _optCmmCpp, _optCcLink, _optAr, - _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optWindres, _optLd + _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optLlc, _optOpt, _optLlvmAs, + _optWindres, _optLd, _optOtool, _optInstallNameTool :: Lens Opts ProgOpt _optCc = Lens optCc (\x o -> o {optCc=x}) _optCxx = Lens optCxx (\x o -> o {optCxx=x}) @@ -126,8 +137,13 @@ _optRanlib = Lens optRanlib (\x o -> o {optRanlib=x}) _optNm = Lens optNm (\x o -> o {optNm=x}) _optReadelf = Lens optReadelf (\x o -> o {optReadelf=x}) _optMergeObjs = Lens optMergeObjs (\x o -> o {optMergeObjs=x}) +_optLlc = Lens optLlc (\x o -> o {optLlc=x}) +_optOpt = Lens optOpt (\x o -> o {optOpt=x}) +_optLlvmAs = Lens optLlvmAs (\x o -> o {optLlvmAs=x}) _optWindres = Lens optWindres (\x o -> o {optWindres=x}) -_optLd = Lens optLd (\x o -> o {optLd= x}) +_optLd = Lens optLd (\x o -> o {optLd=x}) +_optOtool = Lens optOtool (\x o -> o {optOtool=x}) +_optInstallNameTool = Lens optInstallNameTool (\x o -> o {optInstallNameTool=x}) _optTriple :: Lens Opts (Maybe String) _optTriple = Lens optTriple (\x o -> o {optTriple=x}) @@ -183,8 +199,13 @@ options = , progOpts "nm" "nm archiver" _optNm , progOpts "readelf" "readelf utility" _optReadelf , progOpts "merge-objs" "linker for merging objects" _optMergeObjs + , progOpts "llc" "LLVM llc utility" _optLlc + , progOpts "opt" "LLVM opt utility" _optOpt + , progOpts "llvm-as" "Assembler used for LLVM backend (typically clang)" _optLlvmAs , progOpts "windres" "windres utility" _optWindres , progOpts "ld" "linker" _optLd + , progOpts "otool" "otool utility" _optOtool + , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool ] where progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)] @@ -434,6 +455,11 @@ mkTarget opts = do when (isNothing mergeObjs && not (arSupportsDashL ar)) $ throwE "Neither a object-merging tool (e.g. ld -r) nor an ar that supports -L is available" + -- LLVM toolchain + llc <- optional $ findProgram "llc" (optLlc opts) ["llc"] + opt <- optional $ findProgram "opt" (optOpt opts) ["opt"] + llvmAs <- optional $ findProgram "llvm assembler" (optLlvmAs opts) ["clang"] + -- Windows-specific utilities windres <- case archOS_OS archOs of @@ -442,6 +468,15 @@ mkTarget opts = do return (Just windres) _ -> return Nothing + -- Darwin-specific utilities + (otool, installNameTool) <- + case archOS_OS archOs of + OSDarwin -> do + otool <- findProgram "otool" (optOtool opts) ["otool"] + installNameTool <- findProgram "install-name-tool" (optInstallNameTool opts) ["install-name-tool"] + return (Just otool, Just installNameTool) + _ -> return (Nothing, Nothing) + -- various other properties of the platform tgtWordSize <- checkWordSize cc tgtEndianness <- checkEndianness cc @@ -478,7 +513,12 @@ mkTarget opts = do , tgtRanlib = ranlib , tgtNm = nm , tgtMergeObjs = mergeObjs + , tgtLlc = llc + , tgtOpt = opt + , tgtLlvmAs = llvmAs , tgtWindres = windres + , tgtOtool = otool + , tgtInstallNameTool = installNameTool , tgtWordSize , tgtEndianness , tgtUnregisterised ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Target.hs ===================================== @@ -22,15 +22,6 @@ data WordSize = WS4 | WS8 data Endianness = LittleEndian | BigEndian deriving (Show, Read, Eq, Ord) --- TODO(#23674): Move the remaining relevant `settings-xxx` to Target: --- * llc command --- * opt command --- * install_name_tool --- * otool command --- --- Those are all things that are put into GHC's settings, and that might be --- different across targets - -- | A 'Target' consists of: -- -- * a target architecture and operating system @@ -72,8 +63,18 @@ data Target = Target , tgtMergeObjs :: Maybe MergeObjs -- ^ We don't need a merge objects tool if we @Ar@ supports @-L@ + -- LLVM backend toolchain + , tgtLlc :: Maybe Program + , tgtOpt :: Maybe Program + , tgtLlvmAs :: Maybe Program + -- ^ assembler used to assemble LLVM backend output; typically @clang@ + -- Windows-specific tools , tgtWindres :: Maybe Program + + -- Darwin-specific tools + , tgtOtool :: Maybe Program + , tgtInstallNameTool :: Maybe Program } deriving (Read, Eq, Ord) @@ -121,6 +122,11 @@ instance Show Target where , ", tgtRanlib = " ++ show tgtRanlib , ", tgtNm = " ++ show tgtNm , ", tgtMergeObjs = " ++ show tgtMergeObjs + , ", tgtLlc = " ++ show tgtLlc + , ", tgtOpt = " ++ show tgtOpt + , ", tgtLlvmAs = " ++ show tgtLlvmAs , ", tgtWindres = " ++ show tgtWindres + , ", tgtOtool = " ++ show tgtOtool + , ", tgtInstallNameTool = " ++ show tgtInstallNameTool , "}" ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2fb1e554cc5ada6f4a318aba8a5db0e7a3f36a85...fc07b812e08289b52dd94d835a4a032364760dc8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2fb1e554cc5ada6f4a318aba8a5db0e7a3f36a85...fc07b812e08289b52dd94d835a4a032364760dc8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/50aa8df2/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 22:33:51 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 11 Mar 2025 18:33:51 -0400 Subject: [Git][ghc/ghc][wip/T25647] 104 commits: users guide: Fix typo Message-ID: <67d0ba4fe321_110595c5d142635b@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b7ac06e0 by Simon Peyton Jones at 2025-03-11T22:33:40+00:00 WIP towards #25267 - - - - - e6f340e8 by Simon Peyton Jones at 2025-03-11T22:33:40+00:00 Wibbles - - - - - ad87c5f9 by Simon Peyton Jones at 2025-03-11T22:33:40+00:00 Default tyvars in data/newtype insnstances This is what fixes #25647 - - - - - 7cb18d6f by Simon Peyton Jones at 2025-03-11T22:33:40+00:00 wibbles Including fix for #25725 - - - - - afd12256 by Simon Peyton Jones at 2025-03-11T22:33:40+00:00 Wibble - - - - - e2111440 by Patrick at 2025-03-11T22:33:40+00:00 add more tests - - - - - d4400437 by Patrick at 2025-03-11T22:33:40+00:00 Fix up T25611d with explicit kind annotation - - - - - 17bec497 by Patrick at 2025-03-11T22:33:40+00:00 fix up T25647_fail - - - - - cd29ab41 by Patrick at 2025-03-11T22:33:40+00:00 cleanup whitespace - - - - - 0095077f by Patrick at 2025-03-11T22:33:40+00:00 fix up T23512a - - - - - cbf6480c by Patrick at 2025-03-11T22:33:40+00:00 add more examples to T25647b - - - - - 9abefe96 by Patrick at 2025-03-11T22:33:40+00:00 add Dix6 to T25647_fail - - - - - ad24b4f4 by Patrick at 2025-03-11T22:33:40+00:00 add Dix7 for T25647a - - - - - 62552e63 by Patrick at 2025-03-11T22:33:40+00:00 change DefaultingStrategy of tcTyFamInstEqnGuts as well - - - - - 45e1ed99 by Patrick at 2025-03-11T22:33:40+00:00 align wildcard with named typevar on wether it is skolem - - - - - b86ec2c2 by Patrick at 2025-03-11T22:33:40+00:00 fix T17536c - - - - - 801fba89 by Patrick at 2025-03-11T22:33:40+00:00 Fix T9357 - - - - - 0ff2deb6 by Patrick at 2025-03-11T22:33:40+00:00 remove wildcard usage - - - - - 46c87176 by Patrick at 2025-03-11T22:33:40+00:00 Revert "align wildcard with named typevar on wether it is skolem" This reverts commit d1f61858328cc190de9b34c9a24e8d6b28ee5fa9. - - - - - 76ce2a21 by Patrick at 2025-03-11T22:33:40+00:00 add WildCardTv to forbid wildcard from defaulting - - - - - 9b04b9f0 by Patrick at 2025-03-11T22:33:40+00:00 Fix wildcard related tests - - - - - d815a968 by Patrick at 2025-03-11T22:33:40+00:00 add wildcards testcase for T25647a - - - - - f1beffa3 by Patrick at 2025-03-11T22:33:40+00:00 Fix T25647a - - - - - a4fdd09c by Patrick at 2025-03-11T22:33:40+00:00 Revert "Fix wildcard related tests" This reverts commit 8756ab87f4e3d74968d3937f84f811f78a861852. - - - - - 05d4bd34 by Patrick at 2025-03-11T22:33:40+00:00 limit WildCardTv to only HM_FamPat - - - - - d70f6c91 by Patrick at 2025-03-11T22:33:40+00:00 fix - - - - - 69f63d22 by Patrick at 2025-03-11T22:33:40+00:00 Revert "remove wildcard usage" This reverts commit ccc9152f23177ab7a542852ffedf626edcdcef95. - - - - - 2df6083d by Patrick at 2025-03-11T22:33:40+00:00 rename WildCardTv to NoDefTauTv - - - - - e3653b97 by Patrick at 2025-03-11T22:33:40+00:00 update note - - - - - 3aead0e8 by Patrick at 2025-03-11T22:33:40+00:00 rename isWildCardMetaTyVar to isNoDefTauMetaTyVar and fix defaultTyVarTcS - - - - - 53847779 by Patrick at 2025-03-11T22:33:40+00:00 fix comment - - - - - c5865082 by Patrick at 2025-03-11T22:33:40+00:00 format - - - - - 3ac78064 by Patrick at 2025-03-11T22:33:40+00:00 remove NonStandardDefaultingStrategy and update Note [NoDefTauTv] - - - - - 102570b7 by Patrick at 2025-03-11T22:33:40+00:00 add DixC10 to T25647a - - - - - abefc50a by Patrick at 2025-03-11T22:33:40+00:00 use TyVarTv for wildcard in HM_FamPat - - - - - 8b421622 by Patrick at 2025-03-11T22:33:40+00:00 Revert "use TyVarTv for wildcard in HM_FamPat" This reverts commit 638d6763d0b972f3c9a0e2c4218d8c7ce34dc800. - - - - - f8c558a1 by Patrick at 2025-03-11T22:33:40+00:00 Add FamArgType to in AssocInstInfo to guide the create of tv for wildcard - - - - - 29905f62 by Patrick at 2025-03-11T22:33:40+00:00 Fix mode args passing down - - - - - 35faff5a by Patrick at 2025-03-11T22:33:40+00:00 Fix under application for data fam - - - - - dd972ec0 by Patrick at 2025-03-11T22:33:40+00:00 use HM_Sig for (a :: _) in type family - - - - - 67a18f37 by Patrick at 2025-03-11T22:33:40+00:00 add and use HM_FamSig for (a :: _) in type family - - - - - 08ba204a by Patrick at 2025-03-11T22:33:40+00:00 use TyVarTv instead of SkolemTv for freeArg `_`, since we also do not default TyVarTv in defaultTyVar and defaultTyVarTcS - - - - - 85d3ef9d by Patrick at 2025-03-11T22:33:40+00:00 Revert "add and use HM_FamSig for (a :: _) in type family" and use ClassArg for _ in (a :: _) in type family This reverts commit 9ab780da39c2afbce2411c2b96fef4108d6b8b70. - - - - - d2356cf3 by Patrick at 2025-03-11T22:33:40+00:00 fix - - - - - 80ff8a93 by Patrick at 2025-03-11T22:33:40+00:00 remove unused updateHoleMode function from TcTyMode - - - - - 10dac28a by Patrick at 2025-03-11T22:33:40+00:00 flip the classVar to TyVarTv to observe any breakage - - - - - c4a81aa3 by Patrick at 2025-03-11T22:33:40+00:00 fix - - - - - ece07a03 by Patrick at 2025-03-11T22:33:40+00:00 disable DixC10 from T25647a - - - - - d9b320d5 by Patrick at 2025-03-11T22:33:40+00:00 update ExplicitForAllFams4b - - - - - c30abf32 by Patrick at 2025-03-11T22:33:40+00:00 cleanup NoDefTauTv - - - - - 56194258 by Patrick at 2025-03-11T22:33:40+00:00 move [FamArgFlavour] to tyCon - - - - - cc2bd567 by Patrick at 2025-03-11T22:33:40+00:00 add note - - - - - 04015cd7 by Patrick at 2025-03-11T22:33:40+00:00 refactor documentation for FamArgFlavour and clean up comments - - - - - dd96a62e by Patrick at 2025-03-11T22:33:40+00:00 enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging - - - - - c77bead4 by Patrick at 2025-03-11T22:33:40+00:00 Ensure wildcard behave correctly - - - - - b4a39611 by Patrick at 2025-03-11T22:33:40+00:00 Revert "update ExplicitForAllFams4b" This reverts commit 90a2858278668bc6ad66ef43a5651808d8f24a0f. - - - - - abf51bbe by Patrick at 2025-03-11T22:33:40+00:00 Add detailed notes on wildcard handling in type families and refine related documentation - - - - - 9d907f79 by Patrick at 2025-03-11T22:33:40+00:00 Refine documentation on wildcard handling in type families and clarify design choices for FamArgFlavour - - - - - 47819b2b by Patrick at 2025-03-11T22:33:40+00:00 Fix typos in documentation regarding wildcards in type families and clarify references - - - - - bf73073e by Patrick at 2025-03-11T22:33:40+00:00 Clarify wildcard handling in type families documentation and improve explanations for FamArgFlavour - - - - - 36a7fcaa by Patrick at 2025-03-11T22:33:40+00:00 Enhance documentation on FamArgFlavour handling in type families and clarify implementation details in TyCon and HsType modules - - - - - 2ceeeaed by Patrick at 2025-03-11T22:33:40+00:00 format - - - - - c76c36be by Patrick at 2025-03-11T22:33:40+00:00 Refactor documentation on wildcards in type families and clarify implementation details in TyCon, Rename, and HsType modules - - - - - 2b5926d1 by Patrick at 2025-03-11T22:33:40+00:00 Rename variable `famArgFlvs` to `fam_arg_flvs` for consistency in type inference functions - - - - - 54f359cc by Patrick at 2025-03-11T22:33:40+00:00 Improve documentation on wildcard interpretation in type families, clarifying the relationship with class arguments and enhancing the explanation of FamArgFlavour categories. - - - - - 06bde324 by Patrick at 2025-03-11T22:33:40+00:00 Add comment to clarify implementation details for wildcards in family instances - - - - - 270e7926 by Patrick at 2025-03-11T22:33:40+00:00 Refactor HsOuterTyVarBndrs to include implicit variable bindings and update related functions for consistency - - - - - 0298c37b by Patrick at 2025-03-11T22:33:40+00:00 Enhance HsOuterTyVarBndrs to support implicit variable bindings and update related functions for consistency - - - - - dc1f2793 by Patrick at 2025-03-11T22:33:40+00:00 Add new test case T25647d - - - - - 091f3d72 by Patrick at 2025-03-11T22:33:40+00:00 Remove unused implicit variable bindings from HsOuterExplicit in addHsOuterSigTyVarBinds function - - - - - 573b42fb by Patrick at 2025-03-11T22:33:40+00:00 Add forall quantifiers to MultMul type family for clarity - - - - - 3ea58357 by Patrick at 2025-03-11T22:33:40+00:00 Refactor bindHsOuterTyVarBndrs' - - - - - 70743b27 by Patrick at 2025-03-11T22:33:40+00:00 Add empty implicit variable bindings to HsOuterExplicit in mkEmptySigType - - - - - dfb12376 by Patrick at 2025-03-11T22:33:40+00:00 Add empty implicit variable bindings to HsOuterExplicit in synifyDataCon - - - - - d01357a5 by Patrick at 2025-03-11T22:33:40+00:00 Add missing implicit variable bindings to HsOuterExplicit in ExactPrint instance - - - - - 9216bcf9 by Patrick at 2025-03-11T22:33:40+00:00 Add implicit variable bindings to HsOuterExplicit in various instances - - - - - da8ce4bb by Patrick at 2025-03-11T22:33:40+00:00 Add forall quantifier to D Int newtype instance - - - - - ecd9d190 by Patrick at 2025-03-11T22:33:40+00:00 zonk_quant outer binders for families - - - - - 1d9226c8 by Patrick at 2025-03-11T22:33:40+00:00 revert to old behaviour - - - - - 079d7d2b by Patrick at 2025-03-11T22:33:40+00:00 add note and comment - - - - - 1036d373 by Patrick at 2025-03-11T22:33:40+00:00 refactor - - - - - d2194233 by Patrick at 2025-03-11T22:33:40+00:00 fix test T25647d - - - - - dbead5da by Patrick at 2025-03-11T22:33:40+00:00 handle [Naughty quantification candidates] - - - - - 7e441222 by Patrick at 2025-03-11T22:33:40+00:00 handle explicit implicit binders seperately - - - - - f5f3fcfe by Patrick at 2025-03-11T22:33:40+00:00 handle explicit implicit binders seperately fix - - - - - 272fd5d3 by Patrick at 2025-03-11T22:33:40+00:00 fix lint - - - - - 7e1ac9a3 by Patrick at 2025-03-11T22:33:40+00:00 some renaming - - - - - 120 changed files: - compiler/GHC.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/LclEnv.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/using-concurrent.rst - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/driver/junit.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - + testsuite/tests/indexed-types/should_compile/T11450a.hs - testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rename/should_fail/T23512a.stderr - + testsuite/tests/typecheck/should_compile/T25647_fail.hs - + testsuite/tests/typecheck/should_compile/T25647_fail.stderr - + testsuite/tests/typecheck/should_compile/T25647a.hs - + testsuite/tests/typecheck/should_compile/T25647b.hs - + testsuite/tests/typecheck/should_compile/T25647c.hs - + testsuite/tests/typecheck/should_compile/T25647d.hs - + testsuite/tests/typecheck/should_compile/T25647d_fail.hs - + testsuite/tests/typecheck/should_compile/T25647d_fail.stderr - + testsuite/tests/typecheck/should_compile/T25725.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/214aa94c6a723c926f581ed4157724f70daed1d0...7e1ac9a36b0b9a7cfe2cc1857958bee8780d05b9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/214aa94c6a723c926f581ed4157724f70daed1d0...7e1ac9a36b0b9a7cfe2cc1857958bee8780d05b9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/3a94c43a/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 22:42:22 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 18:42:22 -0400 Subject: [Git][ghc/ghc][wip/T25838] rts: Ensure that WinIO flag is set when --io-manager=auto Message-ID: <67d0bc4eb2465_1105954a75903052e@gitlab.mail> Ben Gamari pushed to branch wip/T25838 at Glasgow Haskell Compiler / GHC Commits: 9d680679 by GHC GitLab CI at 2025-03-11T18:42:10-04:00 rts: Ensure that WinIO flag is set when --io-manager=auto As noted in #25838, previously `selectIOManager` failed to set `rts_IOManagerIsWin32Native` in its `IO_MNGR_FLAG_AUTO`. This meant that the MIO path was taken when WinIO was supposedly selected, resulting in chaos. Fixes #25838. - - - - - 1 changed file: - rts/IOManager.c Changes: ===================================== rts/IOManager.c ===================================== @@ -233,7 +233,6 @@ void selectIOManager(void) #if defined(IOMGR_ENABLED_WINIO) case IO_MNGR_FLAG_WINIO: iomgr_type = IO_MANAGER_WINIO; - rts_IOManagerIsWin32Native = true; break; #endif @@ -246,6 +245,10 @@ void selectIOManager(void) default: barf("selectIOManager: %d", RtsFlags.MiscFlags.ioManager); } + +#if defined(mingw32_HOST_OS) + rts_IOManagerIsWin32Native = iomgr_type == IO_MANAGER_WINIO; +#endif } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9d680679be7e91f46a1f6b567b50ebf43c37f40c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9d680679be7e91f46a1f6b567b50ebf43c37f40c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/68834ca5/attachment.html> From gitlab at gitlab.haskell.org Tue Mar 11 22:44:32 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 18:44:32 -0400 Subject: [Git][ghc/ghc][wip/drop-centos] 40 commits: perf: Speed up the bytecode assembler Message-ID: <67d0bcd060a61_1105954a765833551@gitlab.mail> Ben Gamari pushed to branch wip/drop-centos at Glasgow Haskell Compiler / GHC Commits: 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 89175676 by Ben Gamari at 2025-03-11T18:44:23-04:00 gitlab-ci: Drop CentOS 7 binary distributions CentOS 7 is EoL and moreover we cannot even build images for it. See #25061. - - - - - 233 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/wasm.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bdfd0dc79de6fd740d4bc36ebcc61f08d1d90996...8917567603cce5e39294de635484287bdab70499 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bdfd0dc79de6fd740d4bc36ebcc61f08d1d90996...8917567603cce5e39294de635484287bdab70499 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/1885d365/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 22:45:19 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 18:45:19 -0400 Subject: [Git][ghc/ghc][wip/T25752] 87 commits: Use `Foldable1` where appropriate, avoiding much needless panicking. Message-ID: <67d0bcff706e7_110595249690340d8@gitlab.mail> Ben Gamari pushed to branch wip/T25752 at Glasgow Haskell Compiler / GHC Commits: 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 490ee28e by Ben Gamari at 2025-03-11T22:45:11+00:00 testsuite: Sort .T files For better or worse, the testsuite driver currently uses `exec` to execute `.T` files. This is gives rise to surprising behavior as `.T` files may introduce global bindings, which are introduced into the scope of the testsuite driver. Ultimately we should fix this by making the driver more hermetic. However, in the meantime let's at least make the process determinstic by ensuring that `.T` files are processed in sorted order. Addresses #25752. - - - - - 412 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - testsuite/driver/runtests.py - testsuite/driver/testlib.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rts/all.T - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/15e6ba50166948e9d797f26e0100d95fe95da7cd...490ee28ed79dff1c2a64621c14614b2fea37d995 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/15e6ba50166948e9d797f26e0100d95fe95da7cd...490ee28ed79dff1c2a64621c14614b2fea37d995 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/8f772418/attachment-0001.html> From gitlab at gitlab.haskell.org Tue Mar 11 23:01:46 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Mar 2025 19:01:46 -0400 Subject: [Git][ghc/ghc][wip/T23675] 20 commits: users guide: Fix typo Message-ID: <67d0c0dad38f4_11059574d038362c1@gitlab.mail> Ben Gamari pushed to branch wip/T23675 at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - 107f5ea7 by Ben Gamari at 2025-03-11T19:01:30-04:00 configure: Don't force value of OTOOL, etc. if not present Previously if `otool` and `install_name_tool` were not present they would be overridden by `fp_settings.m4`. This logic was introduced in 4ff93292243888545da452ea4d4c1987f2343591 without explanation. - - - - - ae78541f by Ben Gamari at 2025-03-11T19:01:34-04:00 ghc-toolchain: Add support for otool, install_name_tool Fixes part of ghc#23675. - - - - - 6ec47e41 by Ben Gamari at 2025-03-11T19:01:38-04:00 ghc-toolchain: Add support for llc, opt, llvm-as Fixes #23675. - - - - - 105 changed files: - compiler/GHC.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/using-concurrent.rst - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - hadrian/src/Rules/Generate.hs - m4/fp_settings.m4 - m4/ghc_toolchain.m4 - m4/prep_target_file.m4 - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/driver/junit.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fc07b812e08289b52dd94d835a4a032364760dc8...6ec47e4146926e59ca8684ba1e912057bb3df9c7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fc07b812e08289b52dd94d835a4a032364760dc8...6ec47e4146926e59ca8684ba1e912057bb3df9c7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/31658520/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 00:30:36 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Tue, 11 Mar 2025 20:30:36 -0400 Subject: [Git][ghc/ghc][wip/T25647] update tests to reflect changes in error messages Message-ID: <67d0d5acbe2f8_1302a7451168710ed@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: a3b1fedd by Patrick at 2025-03-12T08:29:52+08:00 update tests to reflect changes in error messages - - - - - 9 changed files: - testsuite/tests/indexed-types/should_fail/SimpleFail2a.hs - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.hs - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T14230a.hs - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T14246.stderr - testsuite/tests/typecheck/should_compile/T25725.hs - testsuite/tests/typecheck/should_fail/T18640b.stderr Changes: ===================================== testsuite/tests/indexed-types/should_fail/SimpleFail2a.hs ===================================== @@ -8,7 +8,8 @@ class C a where type St a :: * instance C Int where - data Sd a = MkSd -- :: * -- Looks like a nullary data instance decl + data forall a. Sd a = MkSd -- :: * -- Looks like a nullary data instance decl + data Sd a = MkSk -- same as: Sd Int = MkSk data Sd Int = SdC Char newtype Sn Int = SnC Char type St Int = Char ===================================== testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr ===================================== @@ -5,8 +5,13 @@ SimpleFail2a.hs:11:3: error: [GHC-95424] • In the associated data family instance declaration for ‘Sd’ In the instance declaration for ‘C Int’ -SimpleFail2a.hs:11:11: error: [GHC-34447] +SimpleFail2a.hs:11:21: error: [GHC-34447] Conflicting family instance declarations: - Sd a -- Defined at SimpleFail2a.hs:11:11 + Sd a -- Defined at SimpleFail2a.hs:11:21 Sd Int -- Defined at SimpleFail2a.hs:12:11 +SimpleFail2a.hs:11:21: error: [GHC-34447] + Conflicting family instance declarations: + Sd a -- Defined at SimpleFail2a.hs:11:21 + Sd Int -- Defined at SimpleFail2a.hs:13:11 + ===================================== testsuite/tests/indexed-types/should_fail/SimpleFail9.hs ===================================== @@ -10,7 +10,12 @@ class C7 a b where instance C7 Char (a, Bool) where data S7 (a, Bool) = S7_1 +-- this is fine, b can represent any type +instance C7 Char (a, String) where + data S7 (b, String) = S7_3 + -- Fails because the arg to S7 should be the -- same as that to C7 instance C7 Char (a, Int) where - data S7 (b, Int) = S7_2 + data forall b. S7 (b, Int) = S7_2 + ===================================== testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr ===================================== @@ -1,4 +1,4 @@ -SimpleFail9.hs:16:3: error: [GHC-95424] +SimpleFail9.hs:20:3: error: [GHC-95424] • Type indexes must match class instance head Expected: S7 (a, Int) Actual: S7 (b, Int) ===================================== testsuite/tests/indexed-types/should_fail/T14230a.hs ===================================== @@ -8,7 +8,7 @@ module T14230a where import Data.Kind class C a where - data CD k (a :: k) :: k -> * + data CD k (a :: k) :: k -> Type instance C (Maybe a) where - data CD k (a :: k -> *) :: (k -> *) -> * + data CD k (a :: Type) :: Type -> Type ===================================== testsuite/tests/indexed-types/should_fail/T14230a.stderr ===================================== @@ -1,7 +1,7 @@ T14230a.hs:14:3: error: [GHC-95424] • Type indexes must match class instance head Expected: CD (*) (Maybe a) - Actual: CD k a + Actual: CD (*) a • In the associated data family instance declaration for ‘CD’ In the instance declaration for ‘C (Maybe a)’ ===================================== testsuite/tests/indexed-types/should_fail/T14246.stderr ===================================== @@ -1,11 +1,11 @@ - T14246.hs:20:5: error: [GHC-91510] • Illegal polymorphic type: forall (t :: v). f t • In the equations for closed type family ‘KLN’ In the type family declaration for ‘KLN’ T14246.hs:25:27: error: [GHC-83865] - • Couldn't match kind ‘*’ with ‘L’ + • Couldn't match kind: S (KLN (f t)) + with: KLN f Expected kind ‘Vect (KLN f) L’, but ‘Cons (Label (t :: v)) l’ has kind ‘Vect (S (KLN (f t))) (*)’ • In the second argument of ‘Reveal’, namely @@ -25,3 +25,4 @@ T14246.hs:26:24: error: [GHC-83865] Expected kind ‘Vect (KLN a) L’, but ‘Nil’ has kind ‘Vect Z L’ • In the second argument of ‘Reveal’, namely ‘Nil’ In the type family declaration for ‘Reveal’ + ===================================== testsuite/tests/typecheck/should_compile/T25725.hs ===================================== @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeFamilies, PolyKinds #-} +{-# LANGUAGE TypeFamilies, PolyKinds, UnliftedNewtypes #-} module T25725 where @@ -14,4 +14,19 @@ data family Dix4 :: Type -> k data instance Dix4 Int :: TYPE r -> Type where DIn4 :: p -> Dix4 Int p +data family Dix5 :: TYPE r -> TYPE r +newtype instance Dix5 f :: TYPE c where + DIn5 :: g -> (Dix5 g :: TYPE k) + +-- data family Dix6 :: TYPE r -> TYPE r +-- newtype instance Dix6 f :: TYPE r where +-- DIn6 :: l -> Dix6 l + +-- this one would be rejected +-- in data con sig, we have (Dix6 f) :: Type, +-- but in newtype instance, we have (Dix6 f) :: TYPE r +-- we need coercion between Type and TYPE r +-- which is not possible for newtypes + + ===================================== testsuite/tests/typecheck/should_fail/T18640b.stderr ===================================== @@ -1,12 +1,12 @@ - T18640b.hs:14:10: error: [GHC-25897] - • Couldn't match kind ‘k’ with ‘a’ + • Couldn't match kind ‘a’ with ‘k’ Expected kind ‘forall b -> a’, but ‘F1’ has kind ‘forall k -> k’ - ‘k’ is a rigid type variable bound by - the type k - at T18640b.hs:14:3-11 ‘a’ is a rigid type variable bound by a family instance declaration at T18640b.hs:14:6 + ‘k’ is a rigid type variable bound by + the type k + at T18640b.hs:14:3-11 • In the type ‘F1’ In the type family declaration for ‘F3’ + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a3b1fedd205356f9e8006148c1c62b0f49927a38 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a3b1fedd205356f9e8006148c1c62b0f49927a38 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/7b9edda9/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 00:52:12 2025 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Tue, 11 Mar 2025 20:52:12 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/haddocks-for-ghc-warnings Message-ID: <67d0dabc547c_1302a77570d8718c1@gitlab.mail> Bodigrim pushed new branch wip/haddocks-for-ghc-warnings at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/haddocks-for-ghc-warnings You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/9e41bf06/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 12 02:39:48 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 22:39:48 -0400 Subject: [Git][ghc/ghc][master] We can't UNPACK multi-constructor GADTs Message-ID: <67d0f3f41c7a6_1302a712f8ec886649@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 6 changed files: - compiler/GHC/Core/DataCon.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Types/Id/Make.hs - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T Changes: ===================================== compiler/GHC/Core/DataCon.hs ===================================== @@ -1018,6 +1018,9 @@ instance Data.Data DataCon where gunfold _ _ = error "gunfold" dataTypeOf _ = mkNoRepType "DataCon" +instance Outputable HsSrcBang where + ppr (HsSrcBang _source_text bang) = ppr bang + instance Outputable HsBang where ppr (HsBang prag mark) = ppr prag <+> ppr mark ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -4817,6 +4817,8 @@ checkValidDataCon dflags existential_ok tc con ; traceTc "Done validity of data con" $ vcat [ ppr con , text "Datacon wrapper type:" <+> ppr (dataConWrapperType con) + , text "Datacon src bangs:" <+> ppr (dataConSrcBangs con) + , text "Datacon impl bangs:" <+> ppr (dataConImplBangs con) , text "Datacon rep type:" <+> ppr (dataConRepType con) , text "Datacon display type:" <+> ppr data_con_display_type , text "Rep typcon binders:" <+> ppr (tyConBinders (dataConTyCon con)) ===================================== compiler/GHC/Types/Id/Make.hs ===================================== @@ -1540,39 +1540,87 @@ shouldUnpackArgTy bang_opts prag fam_envs arg_ty --- Given a type already assumed to have been normalized by topNormaliseType, --- unpackable_type_datacons ty = Just datacons --- iff ty is of the form --- T ty1 .. tyn --- and T is an algebraic data type (not newtype), in which no data --- constructors have existentials, and datacons is the list of data --- constructors of T. unpackable_type_datacons :: Type -> Maybe [DataCon] +-- Given a type already assumed to have been normalized by topNormaliseType, +-- unpackable_type_datacons (T ty1 .. tyn) = Just datacons +-- iff the type can be unpacked (see Note [Unpacking GADTs and existentials]) +-- and `datacons` are the data constructors of T unpackable_type_datacons ty | Just (tc, _) <- splitTyConApp_maybe ty - , not (isNewTyCon tc) -- Even though `ty` has been normalised, it could still - -- be a /recursive/ newtype, so we must check for that + , not (isNewTyCon tc) + -- isNewTyCon: even though `ty` has been normalised, whic includes looking + -- through newtypes, it could still be a /recursive/ newtype, so we must + -- check for that case , Just cons <- tyConDataCons_maybe tc - , not (null cons) -- Don't upack nullary sums; no need. - -- They already take zero bits - , all (null . dataConExTyCoVars) cons - = Just cons -- See Note [Unpacking GADTs and existentials] + , unpackable_cons cons + = Just cons | otherwise = Nothing + where + unpackable_cons :: [DataCon] -> Bool + -- True if we can unpack a value of type (T t1 .. tn), + -- where T is an algebraic data type with these constructors + -- See Note [Unpacking GADTs and existentials] + unpackable_cons [] -- Don't unpack nullary sums; no need. + = False -- They already take zero bits; see (UC0) + + unpackable_cons [con] -- Exactly one data constructor; see (UC1) + = null (dataConExTyCoVars con) + + unpackable_cons cons -- More than one data constructor; see (UC2) + = all isVanillaDataCon cons {- Note [Unpacking GADTs and existentials] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -There is nothing stopping us unpacking a data type with equality -components, like - data Equal a b where - Equal :: Equal a a - -And it'd be fine to unpack a product type with existential components -too, but that would require a bit more plumbing, so currently we don't. +Can we unpack a value of an algebraic data type T? For example + data D a = MkD {-# UNPACK #-} (T a) +Can we unpack that (T a) field? + +Three cases to consider in `unpackable_cons` + +(UC0) No data constructors; a nullary sum type. This already takes zero + bits so there is no point in unpacking it. + +(UC1) Single-constructor types (products). We can just represent it by + its fields. For example, if `T` is defined as: + data T a = MkT a a Int + then we can unpack it as follows. The worker for MkD takes three unpacked fields: + data D a = MkD a a Int + $MkD :: T a -> D a + $MkD (MkT a1 a2 i) = MkD a1 a2 i + + We currently /can't/ do this if T has existentially-bound type variables, + hence: null (dataConExTyCoVars con) in `unpackable_cons`. + But see also (UC3) below. + + But we /can/ do it for (some) GADTs, such as: + data Equal a b where { Equal :: Equal a a } + data Wom a where { Wom1 :: Int -> Wom Bool } + We will get a MkD constructor that includes some coercion arguments, + but that is fine. See #14978. We still can't accommodate existentials, + but these particular examples don't use existentials. + +(UC2) Multi-constructor types, e.g. + data T a = T1 a | T2 Int a + Here we unpack the field to an unboxed sum type, thus: + data D a = MkD (# a | (# Int, a #) #) + + However, now we can't deal with GADTs at all, because we'd need an + unboxed sum whose component was a unboxed tuple, whose component(s) + have kind (CONSTRAINT r); and that's not well-kinded. Hence the + all isVanillaDataCon + condition in `unpackable_cons`. See #25672. + +(UC3) For single-constructor types, with some more plumbing we could + allow existentials. e.g. + data T a = forall b. MkT a (b->Int) b + could unpack to + data D a = forall b. MkD a (b->Int) b + $MkD :: T a -> D a + $MkD (MkT @b x f y) = MkD @b x f y + Eminently possible, but more plumbing needed. -So for now we require: null (dataConExTyCoVars data_con) -See #14978 Note [Unpack one-wide fields] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== testsuite/tests/simplCore/should_fail/T25672.hs ===================================== @@ -0,0 +1,15 @@ +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE GADTs #-} + +module T25672 where + +data IntOrWord (isInt :: Bool) where + Int :: !Int -> IntOrWord True + Word :: !Word -> IntOrWord False + +data WrapIntOrWord (isInt :: Bool) + = WrapIntOrWord {lit :: {-# UNPACK #-} !(IntOrWord isInt)} + +boom :: WrapIntOrWord True +boom = WrapIntOrWord (Int 1) ===================================== testsuite/tests/simplCore/should_fail/T25672.stderr ===================================== @@ -0,0 +1,6 @@ +T25672.hs:12:7: warning: [GHC-40091] + • Ignoring unusable UNPACK pragma + on the first argument of ‘WrapIntOrWord’ + • In the definition of data constructor ‘WrapIntOrWord’ + In the data type declaration for ‘WrapIntOrWord’ + ===================================== testsuite/tests/simplCore/should_fail/all.T ===================================== @@ -1,3 +1,6 @@ test('T7411', [expect_broken_for(7411, ['optasm', 'optllvm', 'threaded2', 'dyn']), exit_code(1)], compile_and_run, ['']) + +# This one produces a warning +test('T25672', normal, compile, ['-O']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6d5b09103dea97351774c5ab34082165504b997 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6d5b09103dea97351774c5ab34082165504b997 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/775de916/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 02:40:36 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 22:40:36 -0400 Subject: [Git][ghc/ghc][master] 2 commits: template-haskell: Add explicit exports lists to all remaining modules Message-ID: <67d0f4243bf00_1302a7129500891248@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 7 changed files: - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html Changes: ===================================== libraries/template-haskell/Language/Haskell/TH/Ppr.hs ===================================== @@ -1,9 +1,91 @@ {-# LANGUAGE Safe #-} --- | contains a prettyprinter for the --- Template Haskell datatypes -module Language.Haskell.TH.Ppr - ( module GHC.Boot.TH.Ppr ) - where +{- | contains a prettyprinter for the +Template Haskell datatypes +-} +module Language.Haskell.TH.Ppr ( + appPrec, + bar, + bytesToString, + commaSep, + commaSepApplied, + commaSepWith, + fromTANormal, + funPrec, + hashParens, + isStarT, + isSymOcc, + nestDepth, + noPrec, + opPrec, + parensIf, + pprBangType, + pprBndrVis, + pprBody, + pprClause, + pprCtxWith, + pprCxt, + pprExp, + pprFields, + pprFixity, + pprForall, + pprForall', + pprForallVis, + pprFunArgType, + pprGadtRHS, + pprGuarded, + pprInfixExp, + pprInfixT, + pprLit, + pprMatchPat, + pprMaybeExp, + pprNamespaceSpecifier, + pprParendType, + pprParendTypeArg, + pprPat, + pprPatSynSig, + pprPatSynType, + pprPrefixOcc, + pprRecFields, + pprStrictType, + pprString, + pprTyApp, + pprTyLit, + pprType, + pprVarBangType, + pprVarStrictType, + ppr_bndrs, + ppr_ctx_preds_with, + ppr_cxt_preds, + ppr_data, + ppr_dec, + ppr_deriv_clause, + ppr_deriv_strategy, + ppr_newtype, + ppr_overlap, + ppr_sig, + ppr_tf_head, + ppr_tySyn, + ppr_type_data, + ppr_typedef, + pprint, + qualPrec, + quoteParens, + semiSep, + semiSepWith, + sepWith, + showtextl, + sigPrec, + split, + unboxedSumBars, + unopPrec, + where_clause, + ForallVisFlag (..), + Ppr (..), + PprFlag (..), + Precedence, + TypeArg (..), +) +where import GHC.Boot.TH.Ppr ===================================== libraries/template-haskell/Language/Haskell/TH/PprLib.hs ===================================== @@ -1,8 +1,56 @@ {-# LANGUAGE Safe #-} -- | Monadic front-end to Text.PrettyPrint -module Language.Haskell.TH.PprLib - ( module GHC.Boot.TH.PprLib ) - where +module Language.Haskell.TH.PprLib ( + ($$), + ($+$), + (<+>), + (<>), + arrow, + braces, + brackets, + cat, + char, + colon, + comma, + dcolon, + double, + doubleQuotes, + empty, + equals, + fcat, + float, + fsep, + hang, + hcat, + hsep, + int, + integer, + isEmpty, + lbrace, + lbrack, + lparen, + nest, + parens, + pprName, + pprName', + ptext, + punctuate, + quotes, + rational, + rbrace, + rbrack, + rparen, + semi, + sep, + space, + text, + to_HPJ_Doc, + vcat, + Doc, + PprM, +) +where +import Prelude hiding ((<>)) import GHC.Boot.TH.PprLib ===================================== libraries/template-haskell/Language/Haskell/TH/Syntax.hs ===================================== @@ -1,22 +1,206 @@ {-# LANGUAGE MagicHash #-} -{-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TemplateHaskellQuotes #-} {-# LANGUAGE Trustworthy #-} -module Language.Haskell.TH.Syntax - ( module GHC.Boot.TH.Syntax - , makeRelativeToProject - , module GHC.Boot.TH.Lift - , addrToByteArrayName - , addrToByteArray - ) +{-# LANGUAGE UnboxedTuples #-} + +module Language.Haskell.TH.Syntax ( + Quote (..), + Exp (..), + Match (..), + Clause (..), + Q (..), + Pat (..), + Stmt (..), + Con (..), + Type (..), + Dec (..), + BangType, + VarBangType, + FieldExp, + FieldPat, + Name (..), + FunDep (..), + Pred, + RuleBndr (..), + TySynEqn (..), + InjectivityAnn (..), + Kind, + Overlap (..), + DerivClause (..), + DerivStrategy (..), + Code (..), + ModName (..), + addCorePlugin, + addDependentFile, + addForeignFile, + addForeignFilePath, + addForeignSource, + addModFinalizer, + addTempFile, + addTopDecls, + badIO, + bindCode, + bindCode_, + cmpEq, + compareBytes, + counter, + defaultFixity, + eqBytes, + extsEnabled, + getDoc, + getPackageRoot, + getQ, + get_cons_names, + hoistCode, + isExtEnabled, + isInstance, + joinCode, + liftCode, + location, + lookupName, + lookupTypeName, + lookupValueName, + manyName, + maxPrecedence, + memcmp, + mkNameG, + mkNameU, + mkOccName, + mkPkgName, + mk_tup_name, + mkName, + mkNameG_v, + mkNameG_d, + mkNameG_tc, + mkNameL, + mkNameS, + unTypeCode, + mkModName, + unsafeCodeCoerce, + mkNameQ, + mkNameG_fld, + modString, + nameBase, + nameModule, + namePackage, + nameSpace, + newDeclarationGroup, + newNameIO, + occString, + oneName, + pkgString, + putDoc, + putQ, + recover, + reify, + reifyAnnotations, + reifyConStrictness, + reifyFixity, + reifyInstances, + reifyModule, + reifyRoles, + reifyType, + report, + reportError, + reportWarning, + runIO, + sequenceQ, + runQ, + showName, + showName', + thenCmp, + tupleDataName, + tupleTypeName, + unTypeQ, + unboxedSumDataName, + unboxedSumTypeName, + unboxedTupleDataName, + unboxedTupleTypeName, + unsafeTExpCoerce, + ForeignSrcLang (..), + Extension (..), + AnnLookup (..), + AnnTarget (..), + Arity, + Bang (..), + BndrVis (..), + Body (..), + Bytes (..), + Callconv (..), + CharPos, + Cxt, + DecidedStrictness (..), + DocLoc (..), + FamilyResultSig (..), + Fixity (..), + FixityDirection (..), + Foreign (..), + Guard (..), + Info (..), + Inline (..), + InstanceDec, + Lit (..), + Loc (..), + Module (..), + ModuleInfo (..), + NameFlavour (..), + NameIs (..), + NameSpace (..), + NamespaceSpecifier (..), + OccName (..), + ParentName, + PatSynArgs (..), + PatSynDir (..), + PatSynType, + Phases (..), + PkgName (..), + Pragma (..), + Quasi (..), + Range (..), + Role (..), + RuleMatch (..), + Safety (..), + SourceStrictness (..), + SourceUnpackedness (..), + Specificity (..), + Strict, + StrictType, + SumAlt, + SumArity, + TExp (..), + TyLit (..), + TyVarBndr (..), + TypeFamilyHead (..), + Uniq, + Unlifted, + VarStrictType, + makeRelativeToProject, + liftString, + Lift (..), + dataToCodeQ, + dataToExpQ, + dataToPatQ, + dataToQa, + falseName, + justName, + leftName, + liftData, + liftDataTyped, + nonemptyName, + nothingName, + rightName, + trueName, + addrToByteArrayName, + addrToByteArray, +) where -import GHC.Boot.TH.Syntax -import GHC.Boot.TH.Lift -import System.FilePath import Data.Array.Byte +import GHC.Boot.TH.Lift +import GHC.Boot.TH.Syntax import GHC.Exts import GHC.ST +import System.FilePath -- This module completely re-exports 'GHC.Boot.TH.Syntax', -- and exports additionally functions that depend on filepath. @@ -41,4 +225,3 @@ addrToByteArray (I# len) addr = runST $ ST $ (# s', mb #) -> case copyAddrToByteArray# addr mb 0# len s' of s'' -> case unsafeFreezeByteArray# mb s'' of (# s''', ret #) -> (# s''', ByteArray ret #) - ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -53,6 +53,10 @@ Library build-depends: base >= 4.11 && < 4.22, + -- We don't directly depend on any of the modules from `ghc-internal` + -- But we need to depend on it to work around a hadrian bug. + -- See: https://gitlab.haskell.org/ghc/ghc/-/issues/25705 + ghc-internal == @ProjectVersionForLib at .*, ghc-boot-th == @ProjectVersionMunged@ other-modules: ===================================== utils/haddock/html-test/ref/QuasiExpr.html ===================================== @@ -335,9 +335,9 @@ >parseExprExp</a > :: <a href="#" title="Data.String" >String</a - > -> <a href="#" title="Language.Haskell.TH" + > -> <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a > <a href="#" class="selflink" >#</a ===================================== utils/haddock/html-test/ref/TH.html ===================================== @@ -55,9 +55,9 @@ ><p class="src" ><a id="v:decl" class="def" >decl</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > [<a href="#" title="Language.Haskell.TH" + > [<a href="#" title="Language.Haskell.TH.Syntax" >Dec</a >] <a href="#" class="selflink" >#</a ===================================== utils/haddock/html-test/ref/Threaded_TH.html ===================================== @@ -67,9 +67,9 @@ ><li class="src short" ><a href="#" >forkTH</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a ></li ></ul @@ -82,9 +82,9 @@ ><p class="src" ><a id="v:forkTH" class="def" >forkTH</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a > <a href="#" class="selflink" >#</a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b6d5b09103dea97351774c5ab34082165504b997...db621b58640e65f836c9f7c045fe76ac57ec8641 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b6d5b09103dea97351774c5ab34082165504b997...db621b58640e65f836c9f7c045fe76ac57ec8641 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/b4a03a8b/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 03:11:58 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Mar 2025 23:11:58 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: We can't UNPACK multi-constructor GADTs Message-ID: <67d0fb7ea1cc1_1302a71a54a7894658@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 59e77cf4 by Ben Gamari at 2025-03-11T23:11:39-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - df68f43d by Ben Gamari at 2025-03-11T23:11:40-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 16 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Core/DataCon.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Types/Id/Make.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - rts/HeapStackCheck.cmm - rts/PrimOps.cmm - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html Changes: ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -43,10 +43,9 @@ import json import urllib.parse import fetch_gitlab -def eprint(*args, **kwargs): +def eprint(*args, **kwargs) -> None: print(*args, file=sys.stderr, **kwargs) - gl = gitlab.Gitlab('https://gitlab.haskell.org', per_page=100) # TODO: Take this file as an argument @@ -60,6 +59,10 @@ with open(metadata_file, 'r') as f: eprint(f"Supported platforms: {job_mapping.keys()}") +# Mapping from job name to its corresponding Job +JobMap = Dict[str, gitlab.Job] + +GhcupDist = object # Artifact precisely specifies a job what the bindist to download is called. class Artifact(NamedTuple): @@ -86,32 +89,32 @@ test_artifact = Artifact('source-tarball' , 'ghc-{version}/testsuite' , 'ghc{version}-testsuite') -def debian(n, arch='x86_64'): - return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n)) - -def darwin(arch): +def darwin(arch: str) -> PlatformSpec: return PlatformSpec ( '{arch}-darwin'.format(arch=arch) , 'ghc-{version}-{arch}-apple-darwin'.format(arch=arch, version="{version}") ) windowsArtifact = PlatformSpec ( 'x86_64-windows' , 'ghc-{version}-x86_64-unknown-mingw32' ) -def centos(n, arch='x86_64'): +def debian(n: int, arch: str='x86_64') -> PlatformSpec: + return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n)) + +def centos(n: int, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-centos{n}".format(n=n,arch=arch)) -def fedora(n, arch='x86_64'): +def fedora(n: int, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-fedora{n}".format(n=n,arch=arch)) -def alpine(n, arch='x86_64'): +def alpine(n: str, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-alpine{n}".format(n=n,arch=arch)) -def rocky(n, arch='x86_64'): +def rocky(n: int, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-rocky{n}".format(n=n,arch=arch)) -def ubuntu(n, arch='x86_64'): +def ubuntu(n: str, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-ubuntu{n}".format(n=n,arch=arch)) -def linux_platform(arch, opsys): +def linux_platform(arch: str, opsys: str) -> PlatformSpec: return PlatformSpec( opsys, 'ghc-{version}-{arch}-unknown-linux'.format(version="{version}", arch=arch) ) @@ -135,10 +138,10 @@ def download_and_hash(url): hash_cache[url] = digest return digest -uri_to_anchor_cache=dict() +uri_to_anchor_cache = {} # type: Dict[str, str] # Make the metadata for one platform. -def mk_one_metadata(release_mode, version, job_map, artifact): +def mk_one_metadata(release_mode: bool, version: str, job_map: JobMap, artifact: Artifact) -> GhcupDist: job_id = job_map[artifact.job_name].id url = base_url.format(job_id=job_id, artifact_name=urllib.parse.quote_plus(artifact.download_name.format(version=version))) @@ -181,7 +184,7 @@ def mk_one_metadata(release_mode, version, job_map, artifact): # Turns a platform into an Artifact respecting pipeline_type # Looks up the right job to use from the .gitlab/jobs-metadata.json file -def mk_from_platform(pipeline_type, platform): +def mk_from_platform(pipeline_type: str, platform: PlatformSpec) -> Artifact: info = job_mapping[platform.name][pipeline_type] eprint(f"From {platform.name} / {pipeline_type} selecting {info['name']}") return Artifact(info['name'] @@ -192,7 +195,7 @@ def mk_from_platform(pipeline_type, platform): # Generate the new metadata for a specific GHC mode etc -def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): +def mk_new_yaml(release_mode: bool, version: str, date: str, pipeline_type, job_map: JobMap) -> object: def mk(platform): eprint("\n=== " + platform.name + " " + ('=' * (75 - len(platform.name)))) return mk_one_metadata(release_mode, version, job_map, mk_from_platform(pipeline_type, platform)) @@ -201,7 +204,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): ubuntu1804 = mk(ubuntu("18_04")) ubuntu2004 = mk(ubuntu("20_04")) ubuntu2204 = mk(ubuntu("22_04")) - rocky8 = mk(rocky("8")) + rocky8 = mk(rocky(8)) centos7 = mk(centos(7)) fedora33 = mk(fedora(33)) darwin_x86 = mk(darwin("x86_64")) @@ -301,14 +304,14 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): } -def setNightlyTags(ghcup_metadata): +def setNightlyTags(ghcup_metadata: dict) -> None: for version in ghcup_metadata['ghcupDownloads']['GHC']: if "LatestNightly" in ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"]: ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].remove("LatestNightly") ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].append("Nightly") -def mk_dumper(version): +def mk_dumper(version: str) -> yaml.Dumper: class CustomAliasDumper(yaml.Dumper): def __init__(self, *args, **kwargs): super().__init__(*args, **kwargs) ===================================== compiler/GHC/Core/DataCon.hs ===================================== @@ -1018,6 +1018,9 @@ instance Data.Data DataCon where gunfold _ _ = error "gunfold" dataTypeOf _ = mkNoRepType "DataCon" +instance Outputable HsSrcBang where + ppr (HsSrcBang _source_text bang) = ppr bang + instance Outputable HsBang where ppr (HsBang prag mark) = ppr prag <+> ppr mark ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -4817,6 +4817,8 @@ checkValidDataCon dflags existential_ok tc con ; traceTc "Done validity of data con" $ vcat [ ppr con , text "Datacon wrapper type:" <+> ppr (dataConWrapperType con) + , text "Datacon src bangs:" <+> ppr (dataConSrcBangs con) + , text "Datacon impl bangs:" <+> ppr (dataConImplBangs con) , text "Datacon rep type:" <+> ppr (dataConRepType con) , text "Datacon display type:" <+> ppr data_con_display_type , text "Rep typcon binders:" <+> ppr (tyConBinders (dataConTyCon con)) ===================================== compiler/GHC/Types/Id/Make.hs ===================================== @@ -1540,39 +1540,87 @@ shouldUnpackArgTy bang_opts prag fam_envs arg_ty --- Given a type already assumed to have been normalized by topNormaliseType, --- unpackable_type_datacons ty = Just datacons --- iff ty is of the form --- T ty1 .. tyn --- and T is an algebraic data type (not newtype), in which no data --- constructors have existentials, and datacons is the list of data --- constructors of T. unpackable_type_datacons :: Type -> Maybe [DataCon] +-- Given a type already assumed to have been normalized by topNormaliseType, +-- unpackable_type_datacons (T ty1 .. tyn) = Just datacons +-- iff the type can be unpacked (see Note [Unpacking GADTs and existentials]) +-- and `datacons` are the data constructors of T unpackable_type_datacons ty | Just (tc, _) <- splitTyConApp_maybe ty - , not (isNewTyCon tc) -- Even though `ty` has been normalised, it could still - -- be a /recursive/ newtype, so we must check for that + , not (isNewTyCon tc) + -- isNewTyCon: even though `ty` has been normalised, whic includes looking + -- through newtypes, it could still be a /recursive/ newtype, so we must + -- check for that case , Just cons <- tyConDataCons_maybe tc - , not (null cons) -- Don't upack nullary sums; no need. - -- They already take zero bits - , all (null . dataConExTyCoVars) cons - = Just cons -- See Note [Unpacking GADTs and existentials] + , unpackable_cons cons + = Just cons | otherwise = Nothing + where + unpackable_cons :: [DataCon] -> Bool + -- True if we can unpack a value of type (T t1 .. tn), + -- where T is an algebraic data type with these constructors + -- See Note [Unpacking GADTs and existentials] + unpackable_cons [] -- Don't unpack nullary sums; no need. + = False -- They already take zero bits; see (UC0) + + unpackable_cons [con] -- Exactly one data constructor; see (UC1) + = null (dataConExTyCoVars con) + + unpackable_cons cons -- More than one data constructor; see (UC2) + = all isVanillaDataCon cons {- Note [Unpacking GADTs and existentials] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -There is nothing stopping us unpacking a data type with equality -components, like - data Equal a b where - Equal :: Equal a a - -And it'd be fine to unpack a product type with existential components -too, but that would require a bit more plumbing, so currently we don't. +Can we unpack a value of an algebraic data type T? For example + data D a = MkD {-# UNPACK #-} (T a) +Can we unpack that (T a) field? + +Three cases to consider in `unpackable_cons` + +(UC0) No data constructors; a nullary sum type. This already takes zero + bits so there is no point in unpacking it. + +(UC1) Single-constructor types (products). We can just represent it by + its fields. For example, if `T` is defined as: + data T a = MkT a a Int + then we can unpack it as follows. The worker for MkD takes three unpacked fields: + data D a = MkD a a Int + $MkD :: T a -> D a + $MkD (MkT a1 a2 i) = MkD a1 a2 i + + We currently /can't/ do this if T has existentially-bound type variables, + hence: null (dataConExTyCoVars con) in `unpackable_cons`. + But see also (UC3) below. + + But we /can/ do it for (some) GADTs, such as: + data Equal a b where { Equal :: Equal a a } + data Wom a where { Wom1 :: Int -> Wom Bool } + We will get a MkD constructor that includes some coercion arguments, + but that is fine. See #14978. We still can't accommodate existentials, + but these particular examples don't use existentials. + +(UC2) Multi-constructor types, e.g. + data T a = T1 a | T2 Int a + Here we unpack the field to an unboxed sum type, thus: + data D a = MkD (# a | (# Int, a #) #) + + However, now we can't deal with GADTs at all, because we'd need an + unboxed sum whose component was a unboxed tuple, whose component(s) + have kind (CONSTRAINT r); and that's not well-kinded. Hence the + all isVanillaDataCon + condition in `unpackable_cons`. See #25672. + +(UC3) For single-constructor types, with some more plumbing we could + allow existentials. e.g. + data T a = forall b. MkT a (b->Int) b + could unpack to + data D a = forall b. MkD a (b->Int) b + $MkD :: T a -> D a + $MkD (MkT @b x f y) = MkD @b x f y + Eminently possible, but more plumbing needed. -So for now we require: null (dataConExTyCoVars data_con) -See #14978 Note [Unpack one-wide fields] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== libraries/template-haskell/Language/Haskell/TH/Ppr.hs ===================================== @@ -1,9 +1,91 @@ {-# LANGUAGE Safe #-} --- | contains a prettyprinter for the --- Template Haskell datatypes -module Language.Haskell.TH.Ppr - ( module GHC.Boot.TH.Ppr ) - where +{- | contains a prettyprinter for the +Template Haskell datatypes +-} +module Language.Haskell.TH.Ppr ( + appPrec, + bar, + bytesToString, + commaSep, + commaSepApplied, + commaSepWith, + fromTANormal, + funPrec, + hashParens, + isStarT, + isSymOcc, + nestDepth, + noPrec, + opPrec, + parensIf, + pprBangType, + pprBndrVis, + pprBody, + pprClause, + pprCtxWith, + pprCxt, + pprExp, + pprFields, + pprFixity, + pprForall, + pprForall', + pprForallVis, + pprFunArgType, + pprGadtRHS, + pprGuarded, + pprInfixExp, + pprInfixT, + pprLit, + pprMatchPat, + pprMaybeExp, + pprNamespaceSpecifier, + pprParendType, + pprParendTypeArg, + pprPat, + pprPatSynSig, + pprPatSynType, + pprPrefixOcc, + pprRecFields, + pprStrictType, + pprString, + pprTyApp, + pprTyLit, + pprType, + pprVarBangType, + pprVarStrictType, + ppr_bndrs, + ppr_ctx_preds_with, + ppr_cxt_preds, + ppr_data, + ppr_dec, + ppr_deriv_clause, + ppr_deriv_strategy, + ppr_newtype, + ppr_overlap, + ppr_sig, + ppr_tf_head, + ppr_tySyn, + ppr_type_data, + ppr_typedef, + pprint, + qualPrec, + quoteParens, + semiSep, + semiSepWith, + sepWith, + showtextl, + sigPrec, + split, + unboxedSumBars, + unopPrec, + where_clause, + ForallVisFlag (..), + Ppr (..), + PprFlag (..), + Precedence, + TypeArg (..), +) +where import GHC.Boot.TH.Ppr ===================================== libraries/template-haskell/Language/Haskell/TH/PprLib.hs ===================================== @@ -1,8 +1,56 @@ {-# LANGUAGE Safe #-} -- | Monadic front-end to Text.PrettyPrint -module Language.Haskell.TH.PprLib - ( module GHC.Boot.TH.PprLib ) - where +module Language.Haskell.TH.PprLib ( + ($$), + ($+$), + (<+>), + (<>), + arrow, + braces, + brackets, + cat, + char, + colon, + comma, + dcolon, + double, + doubleQuotes, + empty, + equals, + fcat, + float, + fsep, + hang, + hcat, + hsep, + int, + integer, + isEmpty, + lbrace, + lbrack, + lparen, + nest, + parens, + pprName, + pprName', + ptext, + punctuate, + quotes, + rational, + rbrace, + rbrack, + rparen, + semi, + sep, + space, + text, + to_HPJ_Doc, + vcat, + Doc, + PprM, +) +where +import Prelude hiding ((<>)) import GHC.Boot.TH.PprLib ===================================== libraries/template-haskell/Language/Haskell/TH/Syntax.hs ===================================== @@ -1,22 +1,206 @@ {-# LANGUAGE MagicHash #-} -{-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TemplateHaskellQuotes #-} {-# LANGUAGE Trustworthy #-} -module Language.Haskell.TH.Syntax - ( module GHC.Boot.TH.Syntax - , makeRelativeToProject - , module GHC.Boot.TH.Lift - , addrToByteArrayName - , addrToByteArray - ) +{-# LANGUAGE UnboxedTuples #-} + +module Language.Haskell.TH.Syntax ( + Quote (..), + Exp (..), + Match (..), + Clause (..), + Q (..), + Pat (..), + Stmt (..), + Con (..), + Type (..), + Dec (..), + BangType, + VarBangType, + FieldExp, + FieldPat, + Name (..), + FunDep (..), + Pred, + RuleBndr (..), + TySynEqn (..), + InjectivityAnn (..), + Kind, + Overlap (..), + DerivClause (..), + DerivStrategy (..), + Code (..), + ModName (..), + addCorePlugin, + addDependentFile, + addForeignFile, + addForeignFilePath, + addForeignSource, + addModFinalizer, + addTempFile, + addTopDecls, + badIO, + bindCode, + bindCode_, + cmpEq, + compareBytes, + counter, + defaultFixity, + eqBytes, + extsEnabled, + getDoc, + getPackageRoot, + getQ, + get_cons_names, + hoistCode, + isExtEnabled, + isInstance, + joinCode, + liftCode, + location, + lookupName, + lookupTypeName, + lookupValueName, + manyName, + maxPrecedence, + memcmp, + mkNameG, + mkNameU, + mkOccName, + mkPkgName, + mk_tup_name, + mkName, + mkNameG_v, + mkNameG_d, + mkNameG_tc, + mkNameL, + mkNameS, + unTypeCode, + mkModName, + unsafeCodeCoerce, + mkNameQ, + mkNameG_fld, + modString, + nameBase, + nameModule, + namePackage, + nameSpace, + newDeclarationGroup, + newNameIO, + occString, + oneName, + pkgString, + putDoc, + putQ, + recover, + reify, + reifyAnnotations, + reifyConStrictness, + reifyFixity, + reifyInstances, + reifyModule, + reifyRoles, + reifyType, + report, + reportError, + reportWarning, + runIO, + sequenceQ, + runQ, + showName, + showName', + thenCmp, + tupleDataName, + tupleTypeName, + unTypeQ, + unboxedSumDataName, + unboxedSumTypeName, + unboxedTupleDataName, + unboxedTupleTypeName, + unsafeTExpCoerce, + ForeignSrcLang (..), + Extension (..), + AnnLookup (..), + AnnTarget (..), + Arity, + Bang (..), + BndrVis (..), + Body (..), + Bytes (..), + Callconv (..), + CharPos, + Cxt, + DecidedStrictness (..), + DocLoc (..), + FamilyResultSig (..), + Fixity (..), + FixityDirection (..), + Foreign (..), + Guard (..), + Info (..), + Inline (..), + InstanceDec, + Lit (..), + Loc (..), + Module (..), + ModuleInfo (..), + NameFlavour (..), + NameIs (..), + NameSpace (..), + NamespaceSpecifier (..), + OccName (..), + ParentName, + PatSynArgs (..), + PatSynDir (..), + PatSynType, + Phases (..), + PkgName (..), + Pragma (..), + Quasi (..), + Range (..), + Role (..), + RuleMatch (..), + Safety (..), + SourceStrictness (..), + SourceUnpackedness (..), + Specificity (..), + Strict, + StrictType, + SumAlt, + SumArity, + TExp (..), + TyLit (..), + TyVarBndr (..), + TypeFamilyHead (..), + Uniq, + Unlifted, + VarStrictType, + makeRelativeToProject, + liftString, + Lift (..), + dataToCodeQ, + dataToExpQ, + dataToPatQ, + dataToQa, + falseName, + justName, + leftName, + liftData, + liftDataTyped, + nonemptyName, + nothingName, + rightName, + trueName, + addrToByteArrayName, + addrToByteArray, +) where -import GHC.Boot.TH.Syntax -import GHC.Boot.TH.Lift -import System.FilePath import Data.Array.Byte +import GHC.Boot.TH.Lift +import GHC.Boot.TH.Syntax import GHC.Exts import GHC.ST +import System.FilePath -- This module completely re-exports 'GHC.Boot.TH.Syntax', -- and exports additionally functions that depend on filepath. @@ -41,4 +225,3 @@ addrToByteArray (I# len) addr = runST $ ST $ (# s', mb #) -> case copyAddrToByteArray# addr mb 0# len s' of s'' -> case unsafeFreezeByteArray# mb s'' of (# s''', ret #) -> (# s''', ByteArray ret #) - ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -53,6 +53,10 @@ Library build-depends: base >= 4.11 && < 4.22, + -- We don't directly depend on any of the modules from `ghc-internal` + -- But we need to depend on it to work around a hadrian bug. + -- See: https://gitlab.haskell.org/ghc/ghc/-/issues/25705 + ghc-internal == @ProjectVersionForLib at .*, ghc-boot-th == @ProjectVersionMunged@ other-modules: ===================================== rts/HeapStackCheck.cmm ===================================== @@ -14,9 +14,6 @@ #include "Updates.h" #include "SMPClosureOps.h" -#if defined(__PIC__) -import pthread_mutex_unlock; -#endif import AcquireSRWLockExclusive; import ReleaseSRWLockExclusives; ===================================== rts/PrimOps.cmm ===================================== @@ -25,10 +25,6 @@ #include "MachDeps.h" #include "SMPClosureOps.h" -#if defined(__PIC__) -import pthread_mutex_lock; -import pthread_mutex_unlock; -#endif import CLOSURE ghczminternal_GHCziInternalziControlziExceptionziBase_nestedAtomically_closure; import CLOSURE ghczminternal_GHCziInternalziIOziException_heapOverflow_closure; import CLOSURE ghczminternal_GHCziInternalziIOziException_blockedIndefinitelyOnMVar_closure; ===================================== testsuite/tests/simplCore/should_fail/T25672.hs ===================================== @@ -0,0 +1,15 @@ +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE GADTs #-} + +module T25672 where + +data IntOrWord (isInt :: Bool) where + Int :: !Int -> IntOrWord True + Word :: !Word -> IntOrWord False + +data WrapIntOrWord (isInt :: Bool) + = WrapIntOrWord {lit :: {-# UNPACK #-} !(IntOrWord isInt)} + +boom :: WrapIntOrWord True +boom = WrapIntOrWord (Int 1) ===================================== testsuite/tests/simplCore/should_fail/T25672.stderr ===================================== @@ -0,0 +1,6 @@ +T25672.hs:12:7: warning: [GHC-40091] + • Ignoring unusable UNPACK pragma + on the first argument of ‘WrapIntOrWord’ + • In the definition of data constructor ‘WrapIntOrWord’ + In the data type declaration for ‘WrapIntOrWord’ + ===================================== testsuite/tests/simplCore/should_fail/all.T ===================================== @@ -1,3 +1,6 @@ test('T7411', [expect_broken_for(7411, ['optasm', 'optllvm', 'threaded2', 'dyn']), exit_code(1)], compile_and_run, ['']) + +# This one produces a warning +test('T25672', normal, compile, ['-O']) ===================================== utils/haddock/html-test/ref/QuasiExpr.html ===================================== @@ -335,9 +335,9 @@ >parseExprExp</a > :: <a href="#" title="Data.String" >String</a - > -> <a href="#" title="Language.Haskell.TH" + > -> <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a > <a href="#" class="selflink" >#</a ===================================== utils/haddock/html-test/ref/TH.html ===================================== @@ -55,9 +55,9 @@ ><p class="src" ><a id="v:decl" class="def" >decl</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > [<a href="#" title="Language.Haskell.TH" + > [<a href="#" title="Language.Haskell.TH.Syntax" >Dec</a >] <a href="#" class="selflink" >#</a ===================================== utils/haddock/html-test/ref/Threaded_TH.html ===================================== @@ -67,9 +67,9 @@ ><li class="src short" ><a href="#" >forkTH</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a ></li ></ul @@ -82,9 +82,9 @@ ><p class="src" ><a id="v:forkTH" class="def" >forkTH</a - > :: <a href="#" title="Language.Haskell.TH" + > :: <a href="#" title="Language.Haskell.TH.Syntax" >Q</a - > <a href="#" title="Language.Haskell.TH" + > <a href="#" title="Language.Haskell.TH.Syntax" >Exp</a > <a href="#" class="selflink" >#</a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a1c2a7a98ba3feff2bf81181807d98ead79c776e...df68f43dfa93e97e70f226671588bfec45d891c4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a1c2a7a98ba3feff2bf81181807d98ead79c776e...df68f43dfa93e97e70f226671588bfec45d891c4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/85918894/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 11:12:17 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Mar 2025 07:12:17 -0400 Subject: [Git][ghc/ghc][master] mk-ghcup-metadata: Clean up and add type annotations Message-ID: <67d16c11ae077_1f9693d009894639@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - 1 changed file: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py Changes: ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -43,10 +43,9 @@ import json import urllib.parse import fetch_gitlab -def eprint(*args, **kwargs): +def eprint(*args, **kwargs) -> None: print(*args, file=sys.stderr, **kwargs) - gl = gitlab.Gitlab('https://gitlab.haskell.org', per_page=100) # TODO: Take this file as an argument @@ -60,6 +59,10 @@ with open(metadata_file, 'r') as f: eprint(f"Supported platforms: {job_mapping.keys()}") +# Mapping from job name to its corresponding Job +JobMap = Dict[str, gitlab.Job] + +GhcupDist = object # Artifact precisely specifies a job what the bindist to download is called. class Artifact(NamedTuple): @@ -86,32 +89,32 @@ test_artifact = Artifact('source-tarball' , 'ghc-{version}/testsuite' , 'ghc{version}-testsuite') -def debian(n, arch='x86_64'): - return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n)) - -def darwin(arch): +def darwin(arch: str) -> PlatformSpec: return PlatformSpec ( '{arch}-darwin'.format(arch=arch) , 'ghc-{version}-{arch}-apple-darwin'.format(arch=arch, version="{version}") ) windowsArtifact = PlatformSpec ( 'x86_64-windows' , 'ghc-{version}-x86_64-unknown-mingw32' ) -def centos(n, arch='x86_64'): +def debian(n: int, arch: str='x86_64') -> PlatformSpec: + return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n)) + +def centos(n: int, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-centos{n}".format(n=n,arch=arch)) -def fedora(n, arch='x86_64'): +def fedora(n: int, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-fedora{n}".format(n=n,arch=arch)) -def alpine(n, arch='x86_64'): +def alpine(n: str, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-alpine{n}".format(n=n,arch=arch)) -def rocky(n, arch='x86_64'): +def rocky(n: int, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-rocky{n}".format(n=n,arch=arch)) -def ubuntu(n, arch='x86_64'): +def ubuntu(n: str, arch='x86_64') -> PlatformSpec: return linux_platform(arch, "{arch}-linux-ubuntu{n}".format(n=n,arch=arch)) -def linux_platform(arch, opsys): +def linux_platform(arch: str, opsys: str) -> PlatformSpec: return PlatformSpec( opsys, 'ghc-{version}-{arch}-unknown-linux'.format(version="{version}", arch=arch) ) @@ -135,10 +138,10 @@ def download_and_hash(url): hash_cache[url] = digest return digest -uri_to_anchor_cache=dict() +uri_to_anchor_cache = {} # type: Dict[str, str] # Make the metadata for one platform. -def mk_one_metadata(release_mode, version, job_map, artifact): +def mk_one_metadata(release_mode: bool, version: str, job_map: JobMap, artifact: Artifact) -> GhcupDist: job_id = job_map[artifact.job_name].id url = base_url.format(job_id=job_id, artifact_name=urllib.parse.quote_plus(artifact.download_name.format(version=version))) @@ -181,7 +184,7 @@ def mk_one_metadata(release_mode, version, job_map, artifact): # Turns a platform into an Artifact respecting pipeline_type # Looks up the right job to use from the .gitlab/jobs-metadata.json file -def mk_from_platform(pipeline_type, platform): +def mk_from_platform(pipeline_type: str, platform: PlatformSpec) -> Artifact: info = job_mapping[platform.name][pipeline_type] eprint(f"From {platform.name} / {pipeline_type} selecting {info['name']}") return Artifact(info['name'] @@ -192,7 +195,7 @@ def mk_from_platform(pipeline_type, platform): # Generate the new metadata for a specific GHC mode etc -def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): +def mk_new_yaml(release_mode: bool, version: str, date: str, pipeline_type, job_map: JobMap) -> object: def mk(platform): eprint("\n=== " + platform.name + " " + ('=' * (75 - len(platform.name)))) return mk_one_metadata(release_mode, version, job_map, mk_from_platform(pipeline_type, platform)) @@ -201,7 +204,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): ubuntu1804 = mk(ubuntu("18_04")) ubuntu2004 = mk(ubuntu("20_04")) ubuntu2204 = mk(ubuntu("22_04")) - rocky8 = mk(rocky("8")) + rocky8 = mk(rocky(8)) centos7 = mk(centos(7)) fedora33 = mk(fedora(33)) darwin_x86 = mk(darwin("x86_64")) @@ -301,14 +304,14 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): } -def setNightlyTags(ghcup_metadata): +def setNightlyTags(ghcup_metadata: dict) -> None: for version in ghcup_metadata['ghcupDownloads']['GHC']: if "LatestNightly" in ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"]: ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].remove("LatestNightly") ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].append("Nightly") -def mk_dumper(version): +def mk_dumper(version: str) -> yaml.Dumper: class CustomAliasDumper(yaml.Dumper): def __init__(self, *args, **kwargs): super().__init__(*args, **kwargs) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64ea68d9a206ec4db5020b0a3fc563199ab18be3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64ea68d9a206ec4db5020b0a3fc563199ab18be3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/74e5b7c3/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 11:12:47 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Mar 2025 07:12:47 -0400 Subject: [Git][ghc/ghc][master] rts: Drop imports of pthreads functions in cmm sources Message-ID: <67d16c2fe7e85_1f9693d007097293@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 2 changed files: - rts/HeapStackCheck.cmm - rts/PrimOps.cmm Changes: ===================================== rts/HeapStackCheck.cmm ===================================== @@ -14,9 +14,6 @@ #include "Updates.h" #include "SMPClosureOps.h" -#if defined(__PIC__) -import pthread_mutex_unlock; -#endif import AcquireSRWLockExclusive; import ReleaseSRWLockExclusives; ===================================== rts/PrimOps.cmm ===================================== @@ -25,10 +25,6 @@ #include "MachDeps.h" #include "SMPClosureOps.h" -#if defined(__PIC__) -import pthread_mutex_lock; -import pthread_mutex_unlock; -#endif import CLOSURE ghczminternal_GHCziInternalziControlziExceptionziBase_nestedAtomically_closure; import CLOSURE ghczminternal_GHCziInternalziIOziException_heapOverflow_closure; import CLOSURE ghczminternal_GHCziInternalziIOziException_blockedIndefinitelyOnMVar_closure; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3f80b07d3057f28eb5f42e35f78fcff9331198b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3f80b07d3057f28eb5f42e35f78fcff9331198b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/d4415b0c/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 13:40:41 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 12 Mar 2025 09:40:41 -0400 Subject: [Git][ghc/ghc][wip/T24359] 81 commits: LLVM: account for register type in funPrologue Message-ID: <67d18ed956265_21cc0a3ad43c98131@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 22e09e89 by sheaf at 2025-03-12T14:18:43+01:00 Fix buglet in isEmptyWorkList There was a missing case in GHC.Tc.Solver.InertSet.isEmptyWorkList; it mistakenly ignored the 'wl_rw_eqs' field. This commit simplifies fixes that. No test case. - - - - - 3ce0c4dc by sheaf at 2025-03-12T14:20:43+01:00 Add mapMaybeTM method to TrieMap class This commit adds a new method to the TrieMap class, mapMaybeTM, and adds implementations to all the instances. mapMaybeTM is useful when filtering containers that contain other containers. - - - - - e760bf24 by Simon Peyton Jones at 2025-03-12T14:38:41+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - def06b41 by Simon Peyton Jones at 2025-03-12T14:38:44+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 490 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.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/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - docs/users_guide/exts/pragmas.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/using-warnings.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libraries/array - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - m4/fp_settings.m4 - rts/Interpreter.c - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3b41904511e9fa60fd4436b8f17f4f23c3681998...def06b415cfc6dd6cfcbfa49acaa11c83a3c5433 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3b41904511e9fa60fd4436b8f17f4f23c3681998...def06b415cfc6dd6cfcbfa49acaa11c83a3c5433 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/06e31aa8/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 13:41:38 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 12 Mar 2025 09:41:38 -0400 Subject: [Git][ghc/ghc][wip/T24359] 4 commits: Fix buglet in isEmptyWorkList Message-ID: <67d18f12c33f0_21cc0a42e7089906c@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 32dc9b3a by sheaf at 2025-03-12T14:41:18+01:00 Fix buglet in isEmptyWorkList There was a missing case in GHC.Tc.Solver.InertSet.isEmptyWorkList; it mistakenly ignored the 'wl_rw_eqs' field. This commit simply fixes that. No test case. - - - - - 8f16175e by sheaf at 2025-03-12T14:41:28+01:00 Add mapMaybeTM method to TrieMap class This commit adds a new method to the TrieMap class, mapMaybeTM, and adds implementations to all the instances. mapMaybeTM is useful when filtering containers that contain other containers. - - - - - a24117c4 by Simon Peyton Jones at 2025-03-12T14:41:28+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - e155de41 by Simon Peyton Jones at 2025-03-12T14:41:29+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 163 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - + compiler/GHC/Tc/Solver/Solve.hs-boot - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/def06b415cfc6dd6cfcbfa49acaa11c83a3c5433...e155de41ce827cfd1ea0bc42dd1fb277ce8bcf78 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/def06b415cfc6dd6cfcbfa49acaa11c83a3c5433...e155de41ce827cfd1ea0bc42dd1fb277ce8bcf78 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/90b4a493/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 13:47:32 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 12 Mar 2025 09:47:32 -0400 Subject: [Git][ghc/ghc][wip/T24359] Add -Wrule-lhs-equalities warning Message-ID: <67d1907477350_21cc0a3ad4501013b7@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 10f59a44 by Simon Peyton Jones at 2025-03-12T14:47:18+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 13 changed files: - compiler/GHC/Core/Rules.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Types/Error/Codes.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/using-warnings.rst - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -1001,17 +1001,17 @@ In short, it is Very Deeply Suspicious for a rule to quantify over a coercion variable. And SpecConstr no longer does so: see Note [SpecConstr and casts] in SpecConstr. -It is, however, OK for a cast to appear in a template. For example - newtype N a = MkN (a,a) -- Axiom ax:N a :: (a,a) ~R N a - f :: N a -> bah - RULE forall b x:b y:b. f @b ((x,y) |> (axN @b)) = ... - -When matching we can just move these casts to the other side: - match (tmpl |> co) tgt --> match tmpl (tgt |> sym co) -See matchTemplateCast. - Wrinkles: +(CT0) It is, however, OK for a cast to appear in a template provided the cast mentions + none of the template variables. For example + newtype N a = MkN (a,a) -- Axiom ax:N a :: (a,a) ~R N a + f :: N a -> bah + RULE forall b x:b y:b. f @b ((x,y) |> (axN @b)) = ... + When matching we can just move these casts to the other side: + match (tmpl |> co) tgt --> match tmpl (tgt |> sym co) + See matchTemplateCast. + (CT1) We need to be careful about scoping, and to match left-to-right, so that we know the substitution [a :-> b] before we meet (co :: (a,a) ~R N a), and so we can apply that substitition @@ -1496,11 +1496,12 @@ matchTemplateCast renv subst e1 co1 e2 mco filterFV (`elemVarSet` rv_tmpls renv) $ -- Check that the coercion does not tyCoFVsOfCo substed_co -- mention any of the template variables = -- This is the good path - -- See Note [Casts in the template] + -- See Note [Casts in the template] wrinkle (CT0) match renv subst e1 e2 (checkReflexiveMCo (mkTransMCoL mco (mkSymCo substed_co))) | otherwise = -- This is the Deeply Suspicious Path + -- See Note [Casts in the template] do { let co2 = case mco of MRefl -> mkRepReflCo (exprType e2) MCo co2 -> co2 ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1080,6 +1080,7 @@ data WarningFlag = | Opt_WarnViewPatternSignatures -- Since 9.12 | Opt_WarnUselessSpecialisations -- Since 9.14 | Opt_WarnDeprecatedPragmas -- Since 9.14 + | Opt_WarnRuleLhsEqualities -- Since 9.14 deriving (Eq, Ord, Show, Enum, Bounded) -- | Return the names of a WarningFlag @@ -1198,6 +1199,7 @@ warnFlagNames wflag = case wflag of Opt_WarnViewPatternSignatures -> "view-pattern-signatures" :| [] Opt_WarnUselessSpecialisations -> "useless-specialisations" :| ["useless-specializations"] Opt_WarnDeprecatedPragmas -> "deprecated-pragmas" :| [] + Opt_WarnRuleLhsEqualities -> "rule-lhs-equalities" :| [] -- ----------------------------------------------------------------------------- -- Standard sets of warning options @@ -1341,7 +1343,8 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnTypeEqualityOutOfScope, Opt_WarnViewPatternSignatures, Opt_WarnUselessSpecialisations, - Opt_WarnDeprecatedPragmas + Opt_WarnDeprecatedPragmas, + Opt_WarnRuleLhsEqualities ] -- | Things you get with -W ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2360,6 +2360,7 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnViewPatternSignatures -> warnSpec x Opt_WarnUselessSpecialisations -> warnSpec x Opt_WarnDeprecatedPragmas -> warnSpec x + Opt_WarnRuleLhsEqualities -> warnSpec x warningGroupsDeps :: [(Deprecation, FlagSpec WarningGroup)] warningGroupsDeps = map mk warningGroups ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -996,7 +996,13 @@ prepareSpecLHS poly_id evs the_call = go qevs (bind:acc) e | otherwise - = go (qevs `extendVarSetList` bndrs) acc e + = pprPanic "prepareSpecLHS" $ + vcat [ text "poly_id:" <+> ppr poly_id + , text "the_call:" <+> ppr the_call + , text "bind:" <+> ppr bind + , text "bndrs:" <+> ppr bndrs + ] + --go (qevs `extendVarSetList` bndrs) acc e where bndrs = bindersOf bind ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1426,6 +1426,14 @@ instance Diagnostic TcRnMessage where err = case errReason of UnboundVariable uv nis -> pprScopeError uv nis IllegalExpression -> text "Illegal expression:" <+> ppr bad_e + TcRnRuleLhsEqualities ruleName _lhs cts -> mkSimpleDecorated $ + text "Discarding RULE" <+> doubleQuotes (ftext ruleName) <> dot + $$ + hang + (sep [ text "The LHS of this rule gave rise to equality constraints" + , text "that GHC was unable to quantify over:" ] + ) + 4 (pprWithArising $ NE.toList cts) TcRnDuplicateRoleAnnot list -> mkSimpleDecorated $ hang (text "Duplicate role annotations for" <+> quotes (ppr $ roleAnnotDeclName first_decl) <> colon) @@ -2424,6 +2432,8 @@ instance Diagnostic TcRnMessage where -> ErrorWithoutFlag TcRnIllegalRuleLhs{} -> ErrorWithoutFlag + TcRnRuleLhsEqualities{} + -> WarningWithFlag Opt_WarnRuleLhsEqualities TcRnDuplicateRoleAnnot{} -> ErrorWithoutFlag TcRnDuplicateKindSig{} @@ -3097,6 +3107,8 @@ instance Diagnostic TcRnMessage where -> [suggestExtension LangExt.StandaloneKindSignatures] TcRnIllegalRuleLhs{} -> noHints + TcRnRuleLhsEqualities{} + -> noHints TcRnDuplicateRoleAnnot{} -> noHints TcRnDuplicateKindSig{} ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -3302,9 +3302,21 @@ data TcRnMessage where -} TcRnIllegalRuleLhs :: RuleLhsErrReason - -> FastString -- Rule name - -> LHsExpr GhcRn -- Full expression - -> HsExpr GhcRn -- Bad expression + -> FastString -- ^ Rule name + -> LHsExpr GhcRn -- ^ Full expression + -> HsExpr GhcRn -- ^ Bad expression + -> TcRnMessage + + {-| TcRnRuleLhsEqualities is a warning, controlled by '-Wrule-lhs-equalities', + that is triggered by a RULE whose LHS contains equality constraints + (of a certain form, such as @F a ~ b@ for a type family @F@). + + Test case: typecheck/should_compile/RuleEqs + -} + TcRnRuleLhsEqualities + :: FastString -- ^ rule name + -> LHsExpr GhcRn -- ^ LHS expression + -> NE.NonEmpty Ct -- ^ LHS equality constraints -> TcRnMessage {-| TcRnDuplicateRoleAnnot is an error triggered by two or more role ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -61,6 +61,7 @@ import GHC.Core.Type import GHC.Core.Multiplicity import GHC.Core.Predicate import GHC.Core.TyCo.Rep( mkNakedFunTy ) +import GHC.Core.TyCon( isTypeFamilyTyCon ) import GHC.Types.Var import GHC.Types.Var.Set @@ -81,9 +82,10 @@ import GHC.Utils.Panic import GHC.Data.Bag import GHC.Data.Maybe( orElse, whenIsJust ) -import Data.Maybe( mapMaybe ) -import qualified Data.List.NonEmpty as NE import Control.Monad( unless ) +import Data.Foldable ( toList ) +import qualified Data.List.NonEmpty as NE +import Data.Maybe( mapMaybe ) {- ------------------------------------------------------------- Note [Overview of type signatures] @@ -1278,23 +1280,35 @@ tcRule (HsRule { rd_ext = ext vcat [ ppr id <+> dcolon <+> ppr (idType id) | id <- tpl_ids ] ]) - -- SimplfyRule Plan, step 5 + -- /Temporarily/ deal with the fact that we previously accepted + -- rules that quantify over certain equality constraints. + -- + -- See Note [Quantifying over equalities in RULES]. + ; case allPreviouslyQuantifiableEqualities residual_lhs_wanted of { + Just cts | not (insolubleWC rhs_wanted) + -> do { addDiagnostic $ TcRnRuleLhsEqualities name lhs cts + ; return Nothing } ; + _ -> + + do { -- SimplifyRule Plan, step 5 -- Simplify the LHS and RHS constraints: -- For the LHS constraints we must solve the remaining constraints -- (a) so that we report insoluble ones -- (b) so that we bind any soluble ones - ; (lhs_implic, lhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs + (lhs_implic, lhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs residual_lhs_wanted ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted + ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ Just $ HsRule { rd_ext = ext - , rd_name = rname - , rd_act = act - , rd_bndrs = bndrs { rb_ext = qtkvs ++ tpl_ids } - , rd_lhs = mkHsDictLet lhs_binds lhs' - , rd_rhs = mkHsDictLet rhs_binds rhs' } } + ; return $ Just $ + HsRule { rd_ext = ext + , rd_name = rname + , rd_act = act + , rd_bndrs = bndrs { rb_ext = qtkvs ++ tpl_ids } + , rd_lhs = mkHsDictLet lhs_binds lhs' + , rd_rhs = mkHsDictLet rhs_binds rhs' } } } } {- ******************************************************************************** * * @@ -1453,7 +1467,6 @@ RHS constraints. Actually much of this is done by the on-the-fly constraint solving, so the same order must be observed in tcRule. - Note [RULE quantification over equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ At the moment a RULE never quantifies over an equality; see `rule_quant_ct` @@ -1467,6 +1480,14 @@ in `getRuleQuantCts`. Why not? (b) because if such things end up in 'givens' we get a bogus "inaccessible code" error + * Matching on coercions is Deeply Suspicious. We don't want to generate a + RULE like + forall a (co :: F a ~ Int). + foo (x |> Sym co) = ...co... + because matching on that template, to bind `co`, would require us to + match on the /structure/ of a coercion, which we must never do. + See GHC.Core.Rules Note [Casts in the template] + * Equality constraints are unboxed, and that leads to complications For example equality constraints from the LHS will emit coercion hole Wanteds. These don't have a name, so we can't quantify over them directly. @@ -1595,3 +1616,91 @@ getRuleQuantCts wc = case classifyPredType (ctPred ct) of EqPred {} -> False -- Note [RULE quantification over equalities] _ -> tyCoVarsOfCt ct `disjointVarSet` skol_tvs + +{- Note [Quantifying over equalities in RULES] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Up until version 9.12 (included), GHC would happily quantify over certain Wanted +equalities in the LHS of a RULE. This was incorrect behaviour that lead to a +RULE that would never fire, so GHC 9.14 and above no longer allow such RULES. +However, instead of throwing an error, GHC will /temporarily/ emit a warning +and drop the rule instead, in order to ease migration for library maintainers +(NB: this warning is not emitted when the RHS constraints are insoluble; in that +case we simply report those constraints as errors instead). + +The function 'allPreviouslyQuantifiableEqualities' computes the equality +constraints that previous (<= 9.12) versions of GHC accepted quantifying over. + + + Example (test case 'RuleEqs', extracted from the 'mono-traversable' library): + + type family Element mono + type instance Element [a] = a + + class MonoFoldable mono where + otoList :: mono -> [Element mono] + instance MonoFoldable [a] where + otoList = id + + ointercalate :: (MonoFoldable mono, Monoid (Element mono)) + => Element mono -> mono -> Element mono + {-# RULES "ointercalate list" forall x. ointercalate x = Data.List.intercalate x . otoList #-} + + Now, because Data.List.intercalate has the type signature + + forall a. [a] -> [[a]] -> [a] + + typechecking the LHS of this rule would give rise to the Wanted equality + + [W] Element mono ~ [a] + + Due to the type family, GHC 9.12 and below accepted to quantify over this + equality, which would lead to a rule LHS template of the form: + + forall (@mono) (@a) + ($dMonoFoldable :: MonoFoldable mono) + ($dMonoid :: Monoid (Element mono)) + (co :: [a] ~ Element mono) + (x :: [a]). + ointercalate @mono $dMonoFoldable $dMonoid + (x `cast` (Sub co)) + + Matching against this template would match on the structure of a coercion, + which goes against Note [Casts in the template] in GHC.Core.Rules. + In practice, this meant that this RULE would never fire. +-} + +-- | Computes all equality constraints that GHC doesn't accept, but previously +-- did accept (until GHC 9.12 (included)), when deciding what to quantify over +-- in the LHS of a RULE. +-- +-- See Note [Quantifying over equalities in RULES]. +allPreviouslyQuantifiableEqualities :: WantedConstraints -> Maybe (NE.NonEmpty Ct) +allPreviouslyQuantifiableEqualities wc = go emptyVarSet wc + where + go :: TyVarSet -> WantedConstraints -> Maybe (NE.NonEmpty Ct) + go skol_tvs (WC { wc_simple = simples, wc_impl = implics }) + = do { cts1 <- mapM (go_simple skol_tvs) simples + ; cts2 <- concatMapM (go_implic skol_tvs) implics + ; NE.nonEmpty $ toList cts1 ++ toList cts2 } + + go_simple :: TyVarSet -> Ct -> Maybe Ct + go_simple skol_tvs ct + | not (tyCoVarsOfCt ct `disjointVarSet` skol_tvs) + = Nothing + | EqPred _ t1 t2 <- classifyPredType (ctPred ct), ok_eq t1 t2 + = Just ct + | otherwise + = Nothing + + go_implic :: TyVarSet -> Implication -> Maybe [Ct] + go_implic skol_tvs (Implic { ic_skols = skols, ic_wanted = wc }) + = fmap toList $ go (skol_tvs `extendVarSetList` skols) wc + + ok_eq t1 t2 + | t1 `tcEqType` t2 = False + | otherwise = is_fun_app t1 || is_fun_app t2 + + is_fun_app ty -- ty is of form (F tys) where F is a type function + = case tyConAppTyCon_maybe ty of + Just tc -> isTypeFamilyTyCon tc + Nothing -> False ===================================== compiler/GHC/Types/Error/Codes.hs ===================================== @@ -610,6 +610,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "TcRnUnusedVariableInRuleDecl" = 65669 GhcDiagnosticCode "TcRnUnexpectedStandaloneKindSig" = 45906 GhcDiagnosticCode "TcRnIllegalRuleLhs" = 63294 + GhcDiagnosticCode "TcRnRuleLhsEqualities" = 53522 GhcDiagnosticCode "TcRnDuplicateRoleAnnot" = 97170 GhcDiagnosticCode "TcRnDuplicateKindSig" = 43371 GhcDiagnosticCode "TcRnIllegalDerivStrategy" = 87139 ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -25,9 +25,17 @@ Language This deprecation is controlled by the newly introduced ``-Wdeprecated-pragmas`` flag in ``-Wdefault``. -* A new flag, `-Wuseless-specialisations`, controls warnings emitted when GHC +* A new flag, ``-Wuseless-specialisations``, controls warnings emitted when GHC determines that a SPECIALISE pragma would have no effect. +* A new flag, ``-Wrule-lhs-equalities``, controls warnings emitted for RULES + whose left-hand side attempts to quantify over equality constraints that + previous GHC versions accepted quantifying over. GHC will now drop such RULES, + emitting a warning message controlled by this flag. + + This warning is intended to give visibility to the fact that the RULES that + previous GHC versions generated in such circumstances could never fire. + * ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified by `GHC Proposal 516: add warning for incomplete record selectors <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0516-incomplete-record-selectors.rst>`_. Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library. ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -436,6 +436,24 @@ of ``-W(no-)*``. uses multiple comma-separated type signatures (deprecated and scheduled to be removed in GHC 9.18). +.. ghc-flag:: -Wrule-lhs-equalities + :shortdesc: warn about rules whose LHS contains equality constraints + :type: dynamic + :reverse: -Wno-rule-lhs-equalities + :category: + + :since: 9.14 + + :default: on + + When GHC encounters a RULE whose left-hand side gives rise to equality + constraints that previous GHC versions (``<= 9.12``) accepted quantifying + over, GHC will instead drop the rule and emit a warning message, with the + warning message being controlled by this flag. + + This warning is intended to give visibility to the fact that the RULES that + previous GHC versions generated in such circumstances could never fire. + .. ghc-flag:: -Wmissed-specialisations :shortdesc: warn when specialisation of an imported, overloaded function fails. ===================================== testsuite/tests/typecheck/should_compile/RuleEqs.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} + +module RuleEqs where + +import qualified Data.List + +type family Element mono +type instance Element [a] = a + +class MonoFoldable mono where + otoList :: mono -> [Element mono] + +instance MonoFoldable [a] where + otoList = id + +ointercalate :: (MonoFoldable mono, Monoid (Element mono)) + => Element mono + -> mono + -> Element mono +ointercalate x = mconcat . Data.List.intersperse x . otoList +{-# INLINE [0] ointercalate #-} +{-# RULES "ointercalate list" forall x. ointercalate x = Data.List.intercalate x . otoList #-} ===================================== testsuite/tests/typecheck/should_compile/RuleEqs.stderr ===================================== @@ -0,0 +1,6 @@ +RuleEqs.hs:24:11: warning: [GHC-53522] [-Wrule-lhs-equalities (in -Wdefault)] + Discarding RULE "ointercalate list". + The LHS of this rule gave rise to equality constraints + that GHC was unable to quantify over: + [a0] ~ Element mono0 + ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -739,6 +739,7 @@ test('ExplicitSpecificityA1', normal, compile, ['']) test('ExplicitSpecificityA2', normal, compile, ['']) test('ExplicitSpecificity4', normal, compile, ['']) test('TcSpecPragmas', normal, compile, ['']) +test('RuleEqs', normal, compile, ['']) test('T17775-viewpats-a', normal, compile, ['']) test('T17775-viewpats-b', normal, compile_fail, ['']) test('T17775-viewpats-c', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/10f59a447c4061804cb5e8f52f3c640b93e68cf4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/10f59a447c4061804cb5e8f52f3c640b93e68cf4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/e0ab602e/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 13:47:50 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 12 Mar 2025 09:47:50 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/backports-9.12 Message-ID: <67d19086c7731_21cc0a4330f01022c6@gitlab.mail> Ben Gamari pushed new branch wip/backports-9.12 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports-9.12 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/7f7ef27d/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 12 13:48:48 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 12 Mar 2025 09:48:48 -0400 Subject: [Git][ghc/ghc][wip/T24359] Add -Wrule-lhs-equalities warning Message-ID: <67d190c0dba8b_21cc0a3fb2cc10374f@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: c78007eb by Simon Peyton Jones at 2025-03-12T14:48:34+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 12 changed files: - compiler/GHC/Core/Rules.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Types/Error/Codes.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/using-warnings.rst - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -1001,17 +1001,17 @@ In short, it is Very Deeply Suspicious for a rule to quantify over a coercion variable. And SpecConstr no longer does so: see Note [SpecConstr and casts] in SpecConstr. -It is, however, OK for a cast to appear in a template. For example - newtype N a = MkN (a,a) -- Axiom ax:N a :: (a,a) ~R N a - f :: N a -> bah - RULE forall b x:b y:b. f @b ((x,y) |> (axN @b)) = ... - -When matching we can just move these casts to the other side: - match (tmpl |> co) tgt --> match tmpl (tgt |> sym co) -See matchTemplateCast. - Wrinkles: +(CT0) It is, however, OK for a cast to appear in a template provided the cast mentions + none of the template variables. For example + newtype N a = MkN (a,a) -- Axiom ax:N a :: (a,a) ~R N a + f :: N a -> bah + RULE forall b x:b y:b. f @b ((x,y) |> (axN @b)) = ... + When matching we can just move these casts to the other side: + match (tmpl |> co) tgt --> match tmpl (tgt |> sym co) + See matchTemplateCast. + (CT1) We need to be careful about scoping, and to match left-to-right, so that we know the substitution [a :-> b] before we meet (co :: (a,a) ~R N a), and so we can apply that substitition @@ -1496,11 +1496,12 @@ matchTemplateCast renv subst e1 co1 e2 mco filterFV (`elemVarSet` rv_tmpls renv) $ -- Check that the coercion does not tyCoFVsOfCo substed_co -- mention any of the template variables = -- This is the good path - -- See Note [Casts in the template] + -- See Note [Casts in the template] wrinkle (CT0) match renv subst e1 e2 (checkReflexiveMCo (mkTransMCoL mco (mkSymCo substed_co))) | otherwise = -- This is the Deeply Suspicious Path + -- See Note [Casts in the template] do { let co2 = case mco of MRefl -> mkRepReflCo (exprType e2) MCo co2 -> co2 ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1080,6 +1080,7 @@ data WarningFlag = | Opt_WarnViewPatternSignatures -- Since 9.12 | Opt_WarnUselessSpecialisations -- Since 9.14 | Opt_WarnDeprecatedPragmas -- Since 9.14 + | Opt_WarnRuleLhsEqualities -- Since 9.14 deriving (Eq, Ord, Show, Enum, Bounded) -- | Return the names of a WarningFlag @@ -1198,6 +1199,7 @@ warnFlagNames wflag = case wflag of Opt_WarnViewPatternSignatures -> "view-pattern-signatures" :| [] Opt_WarnUselessSpecialisations -> "useless-specialisations" :| ["useless-specializations"] Opt_WarnDeprecatedPragmas -> "deprecated-pragmas" :| [] + Opt_WarnRuleLhsEqualities -> "rule-lhs-equalities" :| [] -- ----------------------------------------------------------------------------- -- Standard sets of warning options @@ -1341,7 +1343,8 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnTypeEqualityOutOfScope, Opt_WarnViewPatternSignatures, Opt_WarnUselessSpecialisations, - Opt_WarnDeprecatedPragmas + Opt_WarnDeprecatedPragmas, + Opt_WarnRuleLhsEqualities ] -- | Things you get with -W ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2360,6 +2360,7 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnViewPatternSignatures -> warnSpec x Opt_WarnUselessSpecialisations -> warnSpec x Opt_WarnDeprecatedPragmas -> warnSpec x + Opt_WarnRuleLhsEqualities -> warnSpec x warningGroupsDeps :: [(Deprecation, FlagSpec WarningGroup)] warningGroupsDeps = map mk warningGroups ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1426,6 +1426,14 @@ instance Diagnostic TcRnMessage where err = case errReason of UnboundVariable uv nis -> pprScopeError uv nis IllegalExpression -> text "Illegal expression:" <+> ppr bad_e + TcRnRuleLhsEqualities ruleName _lhs cts -> mkSimpleDecorated $ + text "Discarding RULE" <+> doubleQuotes (ftext ruleName) <> dot + $$ + hang + (sep [ text "The LHS of this rule gave rise to equality constraints" + , text "that GHC was unable to quantify over:" ] + ) + 4 (pprWithArising $ NE.toList cts) TcRnDuplicateRoleAnnot list -> mkSimpleDecorated $ hang (text "Duplicate role annotations for" <+> quotes (ppr $ roleAnnotDeclName first_decl) <> colon) @@ -2424,6 +2432,8 @@ instance Diagnostic TcRnMessage where -> ErrorWithoutFlag TcRnIllegalRuleLhs{} -> ErrorWithoutFlag + TcRnRuleLhsEqualities{} + -> WarningWithFlag Opt_WarnRuleLhsEqualities TcRnDuplicateRoleAnnot{} -> ErrorWithoutFlag TcRnDuplicateKindSig{} @@ -3097,6 +3107,8 @@ instance Diagnostic TcRnMessage where -> [suggestExtension LangExt.StandaloneKindSignatures] TcRnIllegalRuleLhs{} -> noHints + TcRnRuleLhsEqualities{} + -> noHints TcRnDuplicateRoleAnnot{} -> noHints TcRnDuplicateKindSig{} ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -3302,9 +3302,21 @@ data TcRnMessage where -} TcRnIllegalRuleLhs :: RuleLhsErrReason - -> FastString -- Rule name - -> LHsExpr GhcRn -- Full expression - -> HsExpr GhcRn -- Bad expression + -> FastString -- ^ Rule name + -> LHsExpr GhcRn -- ^ Full expression + -> HsExpr GhcRn -- ^ Bad expression + -> TcRnMessage + + {-| TcRnRuleLhsEqualities is a warning, controlled by '-Wrule-lhs-equalities', + that is triggered by a RULE whose LHS contains equality constraints + (of a certain form, such as @F a ~ b@ for a type family @F@). + + Test case: typecheck/should_compile/RuleEqs + -} + TcRnRuleLhsEqualities + :: FastString -- ^ rule name + -> LHsExpr GhcRn -- ^ LHS expression + -> NE.NonEmpty Ct -- ^ LHS equality constraints -> TcRnMessage {-| TcRnDuplicateRoleAnnot is an error triggered by two or more role ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -61,6 +61,7 @@ import GHC.Core.Type import GHC.Core.Multiplicity import GHC.Core.Predicate import GHC.Core.TyCo.Rep( mkNakedFunTy ) +import GHC.Core.TyCon( isTypeFamilyTyCon ) import GHC.Types.Var import GHC.Types.Var.Set @@ -81,9 +82,10 @@ import GHC.Utils.Panic import GHC.Data.Bag import GHC.Data.Maybe( orElse, whenIsJust ) -import Data.Maybe( mapMaybe ) -import qualified Data.List.NonEmpty as NE import Control.Monad( unless ) +import Data.Foldable ( toList ) +import qualified Data.List.NonEmpty as NE +import Data.Maybe( mapMaybe ) {- ------------------------------------------------------------- Note [Overview of type signatures] @@ -1278,23 +1280,35 @@ tcRule (HsRule { rd_ext = ext vcat [ ppr id <+> dcolon <+> ppr (idType id) | id <- tpl_ids ] ]) - -- SimplfyRule Plan, step 5 + -- /Temporarily/ deal with the fact that we previously accepted + -- rules that quantify over certain equality constraints. + -- + -- See Note [Quantifying over equalities in RULES]. + ; case allPreviouslyQuantifiableEqualities residual_lhs_wanted of { + Just cts | not (insolubleWC rhs_wanted) + -> do { addDiagnostic $ TcRnRuleLhsEqualities name lhs cts + ; return Nothing } ; + _ -> + + do { -- SimplifyRule Plan, step 5 -- Simplify the LHS and RHS constraints: -- For the LHS constraints we must solve the remaining constraints -- (a) so that we report insoluble ones -- (b) so that we bind any soluble ones - ; (lhs_implic, lhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs + (lhs_implic, lhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs residual_lhs_wanted ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted + ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ Just $ HsRule { rd_ext = ext - , rd_name = rname - , rd_act = act - , rd_bndrs = bndrs { rb_ext = qtkvs ++ tpl_ids } - , rd_lhs = mkHsDictLet lhs_binds lhs' - , rd_rhs = mkHsDictLet rhs_binds rhs' } } + ; return $ Just $ + HsRule { rd_ext = ext + , rd_name = rname + , rd_act = act + , rd_bndrs = bndrs { rb_ext = qtkvs ++ tpl_ids } + , rd_lhs = mkHsDictLet lhs_binds lhs' + , rd_rhs = mkHsDictLet rhs_binds rhs' } } } } {- ******************************************************************************** * * @@ -1453,7 +1467,6 @@ RHS constraints. Actually much of this is done by the on-the-fly constraint solving, so the same order must be observed in tcRule. - Note [RULE quantification over equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ At the moment a RULE never quantifies over an equality; see `rule_quant_ct` @@ -1467,6 +1480,14 @@ in `getRuleQuantCts`. Why not? (b) because if such things end up in 'givens' we get a bogus "inaccessible code" error + * Matching on coercions is Deeply Suspicious. We don't want to generate a + RULE like + forall a (co :: F a ~ Int). + foo (x |> Sym co) = ...co... + because matching on that template, to bind `co`, would require us to + match on the /structure/ of a coercion, which we must never do. + See GHC.Core.Rules Note [Casts in the template] + * Equality constraints are unboxed, and that leads to complications For example equality constraints from the LHS will emit coercion hole Wanteds. These don't have a name, so we can't quantify over them directly. @@ -1595,3 +1616,91 @@ getRuleQuantCts wc = case classifyPredType (ctPred ct) of EqPred {} -> False -- Note [RULE quantification over equalities] _ -> tyCoVarsOfCt ct `disjointVarSet` skol_tvs + +{- Note [Quantifying over equalities in RULES] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Up until version 9.12 (included), GHC would happily quantify over certain Wanted +equalities in the LHS of a RULE. This was incorrect behaviour that lead to a +RULE that would never fire, so GHC 9.14 and above no longer allow such RULES. +However, instead of throwing an error, GHC will /temporarily/ emit a warning +and drop the rule instead, in order to ease migration for library maintainers +(NB: this warning is not emitted when the RHS constraints are insoluble; in that +case we simply report those constraints as errors instead). + +The function 'allPreviouslyQuantifiableEqualities' computes the equality +constraints that previous (<= 9.12) versions of GHC accepted quantifying over. + + + Example (test case 'RuleEqs', extracted from the 'mono-traversable' library): + + type family Element mono + type instance Element [a] = a + + class MonoFoldable mono where + otoList :: mono -> [Element mono] + instance MonoFoldable [a] where + otoList = id + + ointercalate :: (MonoFoldable mono, Monoid (Element mono)) + => Element mono -> mono -> Element mono + {-# RULES "ointercalate list" forall x. ointercalate x = Data.List.intercalate x . otoList #-} + + Now, because Data.List.intercalate has the type signature + + forall a. [a] -> [[a]] -> [a] + + typechecking the LHS of this rule would give rise to the Wanted equality + + [W] Element mono ~ [a] + + Due to the type family, GHC 9.12 and below accepted to quantify over this + equality, which would lead to a rule LHS template of the form: + + forall (@mono) (@a) + ($dMonoFoldable :: MonoFoldable mono) + ($dMonoid :: Monoid (Element mono)) + (co :: [a] ~ Element mono) + (x :: [a]). + ointercalate @mono $dMonoFoldable $dMonoid + (x `cast` (Sub co)) + + Matching against this template would match on the structure of a coercion, + which goes against Note [Casts in the template] in GHC.Core.Rules. + In practice, this meant that this RULE would never fire. +-} + +-- | Computes all equality constraints that GHC doesn't accept, but previously +-- did accept (until GHC 9.12 (included)), when deciding what to quantify over +-- in the LHS of a RULE. +-- +-- See Note [Quantifying over equalities in RULES]. +allPreviouslyQuantifiableEqualities :: WantedConstraints -> Maybe (NE.NonEmpty Ct) +allPreviouslyQuantifiableEqualities wc = go emptyVarSet wc + where + go :: TyVarSet -> WantedConstraints -> Maybe (NE.NonEmpty Ct) + go skol_tvs (WC { wc_simple = simples, wc_impl = implics }) + = do { cts1 <- mapM (go_simple skol_tvs) simples + ; cts2 <- concatMapM (go_implic skol_tvs) implics + ; NE.nonEmpty $ toList cts1 ++ toList cts2 } + + go_simple :: TyVarSet -> Ct -> Maybe Ct + go_simple skol_tvs ct + | not (tyCoVarsOfCt ct `disjointVarSet` skol_tvs) + = Nothing + | EqPred _ t1 t2 <- classifyPredType (ctPred ct), ok_eq t1 t2 + = Just ct + | otherwise + = Nothing + + go_implic :: TyVarSet -> Implication -> Maybe [Ct] + go_implic skol_tvs (Implic { ic_skols = skols, ic_wanted = wc }) + = fmap toList $ go (skol_tvs `extendVarSetList` skols) wc + + ok_eq t1 t2 + | t1 `tcEqType` t2 = False + | otherwise = is_fun_app t1 || is_fun_app t2 + + is_fun_app ty -- ty is of form (F tys) where F is a type function + = case tyConAppTyCon_maybe ty of + Just tc -> isTypeFamilyTyCon tc + Nothing -> False ===================================== compiler/GHC/Types/Error/Codes.hs ===================================== @@ -610,6 +610,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "TcRnUnusedVariableInRuleDecl" = 65669 GhcDiagnosticCode "TcRnUnexpectedStandaloneKindSig" = 45906 GhcDiagnosticCode "TcRnIllegalRuleLhs" = 63294 + GhcDiagnosticCode "TcRnRuleLhsEqualities" = 53522 GhcDiagnosticCode "TcRnDuplicateRoleAnnot" = 97170 GhcDiagnosticCode "TcRnDuplicateKindSig" = 43371 GhcDiagnosticCode "TcRnIllegalDerivStrategy" = 87139 ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -25,9 +25,17 @@ Language This deprecation is controlled by the newly introduced ``-Wdeprecated-pragmas`` flag in ``-Wdefault``. -* A new flag, `-Wuseless-specialisations`, controls warnings emitted when GHC +* A new flag, ``-Wuseless-specialisations``, controls warnings emitted when GHC determines that a SPECIALISE pragma would have no effect. +* A new flag, ``-Wrule-lhs-equalities``, controls warnings emitted for RULES + whose left-hand side attempts to quantify over equality constraints that + previous GHC versions accepted quantifying over. GHC will now drop such RULES, + emitting a warning message controlled by this flag. + + This warning is intended to give visibility to the fact that the RULES that + previous GHC versions generated in such circumstances could never fire. + * ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified by `GHC Proposal 516: add warning for incomplete record selectors <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0516-incomplete-record-selectors.rst>`_. Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library. ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -436,6 +436,24 @@ of ``-W(no-)*``. uses multiple comma-separated type signatures (deprecated and scheduled to be removed in GHC 9.18). +.. ghc-flag:: -Wrule-lhs-equalities + :shortdesc: warn about rules whose LHS contains equality constraints + :type: dynamic + :reverse: -Wno-rule-lhs-equalities + :category: + + :since: 9.14 + + :default: on + + When GHC encounters a RULE whose left-hand side gives rise to equality + constraints that previous GHC versions (``<= 9.12``) accepted quantifying + over, GHC will instead drop the rule and emit a warning message, with the + warning message being controlled by this flag. + + This warning is intended to give visibility to the fact that the RULES that + previous GHC versions generated in such circumstances could never fire. + .. ghc-flag:: -Wmissed-specialisations :shortdesc: warn when specialisation of an imported, overloaded function fails. ===================================== testsuite/tests/typecheck/should_compile/RuleEqs.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} + +module RuleEqs where + +import qualified Data.List + +type family Element mono +type instance Element [a] = a + +class MonoFoldable mono where + otoList :: mono -> [Element mono] + +instance MonoFoldable [a] where + otoList = id + +ointercalate :: (MonoFoldable mono, Monoid (Element mono)) + => Element mono + -> mono + -> Element mono +ointercalate x = mconcat . Data.List.intersperse x . otoList +{-# INLINE [0] ointercalate #-} +{-# RULES "ointercalate list" forall x. ointercalate x = Data.List.intercalate x . otoList #-} ===================================== testsuite/tests/typecheck/should_compile/RuleEqs.stderr ===================================== @@ -0,0 +1,6 @@ +RuleEqs.hs:24:11: warning: [GHC-53522] [-Wrule-lhs-equalities (in -Wdefault)] + Discarding RULE "ointercalate list". + The LHS of this rule gave rise to equality constraints + that GHC was unable to quantify over: + [a0] ~ Element mono0 + ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -739,6 +739,7 @@ test('ExplicitSpecificityA1', normal, compile, ['']) test('ExplicitSpecificityA2', normal, compile, ['']) test('ExplicitSpecificity4', normal, compile, ['']) test('TcSpecPragmas', normal, compile, ['']) +test('RuleEqs', normal, compile, ['']) test('T17775-viewpats-a', normal, compile, ['']) test('T17775-viewpats-b', normal, compile_fail, ['']) test('T17775-viewpats-c', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c78007eb6fbc40a55a0259dc3d75e82785d4f4ed -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c78007eb6fbc40a55a0259dc3d75e82785d4f4ed You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/ee0df079/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 14:03:50 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 12 Mar 2025 10:03:50 -0400 Subject: [Git][ghc/ghc][wip/T23675] 2 commits: ghc-toolchain: Add support for otool, install_name_tool Message-ID: <67d19446af6e8_232250c5c9c24168@gitlab.mail> Ben Gamari pushed to branch wip/T23675 at Glasgow Haskell Compiler / GHC Commits: 5b08131d by Ben Gamari at 2025-03-12T10:03:37-04:00 ghc-toolchain: Add support for otool, install_name_tool Fixes part of ghc#23675. - - - - - c5bfeafb by Ben Gamari at 2025-03-12T10:03:37-04:00 ghc-toolchain: Add support for llc, opt, llvm-as Fixes #23675. - - - - - 8 changed files: - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - hadrian/cfg/system.config.in - hadrian/src/Rules/Generate.hs - m4/ghc_toolchain.m4 - m4/prep_target_file.m4 - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs Changes: ===================================== hadrian/cfg/default.host.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Nothing , tgtNm = Nm {nmProgram = Program {prgPath = "", prgFlags = []}} , tgtMergeObjs = Just (MergeObjs {mergeObjsProgram = Program {prgPath = "@LD_STAGE0@", prgFlags = ["-r"]}, mergeObjsSupportsResponseFiles = False}) +, tgtLlc = Nothing +, tgtOpt = Nothing +, tgtLlvmAs = Nothing , tgtWindres = Nothing +, tgtOtool = Nothing +, tgtInstallNameTool = Nothing } ===================================== hadrian/cfg/default.target.in ===================================== @@ -38,5 +38,10 @@ Target , tgtRanlib = Just (Ranlib {ranlibProgram = Program {prgPath = "@RanlibCmd@", prgFlags = []}}) , tgtNm = Nm {nmProgram = Program {prgPath = "@NmCmd@", prgFlags = []}} , tgtMergeObjs = @MergeObjsCmdMaybe@ +, tgtLlc = @LlcCmdMaybeProg@ +, tgtOpt = @OptCmdMaybeProg@ +, tgtLlvmAs = @LlvmAsCmdMaybeProg@ , tgtWindres = @WindresCmdMaybeProg@ +, tgtOtool = @OtoolCmdMaybeProg@ +, tgtInstallNameTool = @InstallNameToolCmdMaybeProg@ } ===================================== hadrian/cfg/system.config.in ===================================== @@ -79,13 +79,6 @@ project-git-commit-id = @ProjectGitCommitId@ # generated by configure, to generated being by the build system. Many of these # might become redundant. # See Note [tooldir: How GHC finds mingw on Windows] - -settings-otool-command = @SettingsOtoolCommand@ -settings-install_name_tool-command = @SettingsInstallNameToolCommand@ -settings-llc-command = @SettingsLlcCommand@ -settings-opt-command = @SettingsOptCommand@ -settings-llvm-as-command = @SettingsLlvmAsCommand@ -settings-llvm-as-flags = @SettingsLlvmAsFlags@ settings-use-distro-mingw = @SettingsUseDistroMINGW@ target-has-libm = @TargetHasLibm@ ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -508,9 +508,9 @@ generateSettings settingsFile = do , ("ar flags", queryTarget arFlags) , ("ar supports at file", queryTarget arSupportsAtFile') , ("ar supports -L", queryTarget arSupportsDashL') - , ("ranlib command", queryTarget ranlibPath) - , ("otool command", expr $ settingsFileSetting ToolchainSetting_OtoolCommand) - , ("install_name_tool command", expr $ settingsFileSetting ToolchainSetting_InstallNameToolCommand) + , ("ranlib command", queryTarget ranlibPath) + , ("otool command", queryTarget otoolPath) + , ("install_name_tool command", queryTarget installNameToolPath) , ("windres command", queryTarget (maybe "/bin/false" prgPath . tgtWindres)) -- TODO: /bin/false is not available on many distributions by default, but we keep it as it were before the ghc-toolchain patch. Fix-me. , ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit }))) , ("cross compiling", expr $ yesNo <$> flag CrossCompiling) @@ -525,10 +525,10 @@ generateSettings settingsFile = do , ("target has libm", expr $ lookupSystemConfig "target-has-libm") , ("Unregisterised", queryTarget (yesNo . tgtUnregisterised)) , ("LLVM target", queryTarget tgtLlvmTarget) - , ("LLVM llc command", expr $ settingsFileSetting ToolchainSetting_LlcCommand) - , ("LLVM opt command", expr $ settingsFileSetting ToolchainSetting_OptCommand) - , ("LLVM llvm-as command", expr $ settingsFileSetting ToolchainSetting_LlvmAsCommand) - , ("LLVM llvm-as flags", expr $ settingsFileSetting ToolchainSetting_LlvmAsFlags) + , ("LLVM llc command", queryTarget llcPath) + , ("LLVM opt command", queryTarget optPath) + , ("LLVM llvm-as command", queryTarget llvmAsPath) + , ("LLVM llvm-as flags", queryTarget llvmAsFlags) , ("Use inplace MinGW toolchain", expr $ settingsFileSetting ToolchainSetting_DistroMinGW) , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs) @@ -571,10 +571,16 @@ generateSettings settingsFile = do linkSupportsFilelist = yesNo . ccLinkSupportsFilelist . tgtCCompilerLink linkSupportsCompactUnwind = yesNo . ccLinkSupportsCompactUnwind . tgtCCompilerLink linkIsGnu = yesNo . ccLinkIsGnu . tgtCCompilerLink + llcPath = maybe "" prgPath . tgtLlc + optPath = maybe "" prgPath . tgtOpt + llvmAsPath = maybe "" prgPath . tgtLlvmAs + llvmAsFlags = escapeArgs . maybe [] prgFlags . tgtLlvmAs arPath = prgPath . arMkArchive . tgtAr arFlags = escapeArgs . prgFlags . arMkArchive . tgtAr arSupportsAtFile' = yesNo . arSupportsAtFile . tgtAr arSupportsDashL' = yesNo . arSupportsDashL . tgtAr + otoolPath = maybe "" prgPath . tgtOtool + installNameToolPath = maybe "" prgPath . tgtInstallNameTool ranlibPath = maybe "" (prgPath . ranlibProgram) . tgtRanlib mergeObjsSupportsResponseFiles' = maybe "NO" (yesNo . mergeObjsSupportsResponseFiles) . tgtMergeObjs ===================================== m4/ghc_toolchain.m4 ===================================== @@ -107,6 +107,9 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN], echo "--merge-objs=$MergeObjsCmd" >> acargs echo "--readelf=$READELF" >> acargs echo "--windres=$WindresCmd" >> acargs + echo "--llc=$LlcCmd" >> acargs + echo "--opt=$OptCmd" >> acargs + echo "--llvm-as=$LlvmAsCmd" >> acargs if test -n "$USER_LD"; then echo "--ld=$USER_LD" >> acargs ===================================== m4/prep_target_file.m4 ===================================== @@ -10,6 +10,38 @@ # This toolchain will additionally be used to validate the one generated by # ghc-toolchain. See Note [ghc-toolchain consistency checking]. +# PREP_LIST +# ============ +# +# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a +# space-separated list of args +# i.e. +# "arg1 arg2 arg3" +# ==> +# ["arg1","arg2","arg3"] +# +# $1 = list variable to substitute +dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'. +AC_DEFUN([PREP_LIST],[ + # shell array + set -- $$1 + $1List="@<:@" + if test "[$]#" -eq 0; then + # no arguments + true + else + $1List="${$1List}\"[$]1\"" + shift # drop first elem + for arg in "[$]@" + do + $1List="${$1List},\"$arg\"" + done + fi + $1List="${$1List}@:>@" + + AC_SUBST([$1List]) +]) + # PREP_MAYBE_SIMPLE_PROGRAM # ========================= # @@ -27,6 +59,25 @@ AC_DEFUN([PREP_MAYBE_SIMPLE_PROGRAM],[ AC_SUBST([$1MaybeProg]) ]) +# PREP_MAYBE_PROGRAM +# ========================= +# +# Introduce a substitution [$1MaybeProg] with +# * Nothing, if $$1 is empty +# * Just (Program {prgPath = "$$1", prgFlags = [elements of $$2]}), otherwise +# +# $1 = optional program path +# $2 = program arguments +AC_DEFUN([PREP_MAYBE_PROGRAM],[ + if test -z "$$1"; then + $1MaybeProg=Nothing + else + PREP_LIST([$2]) + $1MaybeProg="Just (Program {prgPath = \"$$1\", prgFlags = $$2List})" + fi + AC_SUBST([$1MaybeProg]) +]) + # PREP_MAYBE_STRING # ========================= # @@ -86,38 +137,6 @@ AC_DEFUN([PREP_NOT_BOOLEAN],[ AC_SUBST([Not$1Bool]) ]) -# PREP_LIST -# ============ -# -# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a -# space-separated list of args -# i.e. -# "arg1 arg2 arg3" -# ==> -# ["arg1","arg2","arg3"] -# -# $1 = list variable to substitute -dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'. -AC_DEFUN([PREP_LIST],[ - # shell array - set -- $$1 - $1List="@<:@" - if test "[$]#" -eq 0; then - # no arguments - true - else - $1List="${$1List}\"[$]1\"" - shift # drop first elem - for arg in "[$]@" - do - $1List="${$1List},\"$arg\"" - done - fi - $1List="${$1List}@:>@" - - AC_SUBST([$1List]) -]) - # Eventually: PREP_BUILD_TARGET_FILE, PREP_HOST_TARGET_FILE, PREP_TARGET_TARGET_FILE # Prepares required substitutions to generate the target file AC_DEFUN([PREP_TARGET_FILE],[ @@ -148,7 +167,12 @@ AC_DEFUN([PREP_TARGET_FILE],[ PREP_LIST([JavaScriptCPPArgs]) PREP_LIST([CmmCPPArgs]) PREP_LIST([CmmCPPArgs_STAGE0]) + PREP_MAYBE_SIMPLE_PROGRAM([LlcCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OptCmd]) + PREP_MAYBE_PROGRAM([LlvmAsCmd], [LlvmAsFlags]) PREP_MAYBE_SIMPLE_PROGRAM([WindresCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([OtoolCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([InstallNameToolCmd]) PREP_MAYBE_STRING([TargetVendor_CPP]) PREP_MAYBE_STRING([HostVendor_CPP]) PREP_LIST([CONF_CPP_OPTS_STAGE2]) ===================================== utils/ghc-toolchain/exe/Main.hs ===================================== @@ -52,7 +52,12 @@ data Opts = Opts , optNm :: ProgOpt , optReadelf :: ProgOpt , optMergeObjs :: ProgOpt + , optLlc :: ProgOpt + , optOpt :: ProgOpt + , optLlvmAs :: ProgOpt , optWindres :: ProgOpt + , optOtool :: ProgOpt + , optInstallNameTool :: ProgOpt -- Note we don't actually configure LD into anything but -- see #23857 and #22550 for the very unfortunate story. , optLd :: ProgOpt @@ -99,8 +104,13 @@ emptyOpts = Opts , optNm = po0 , optReadelf = po0 , optMergeObjs = po0 + , optLlc = po0 + , optOpt = po0 + , optLlvmAs = po0 , optWindres = po0 , optLd = po0 + , optOtool = po0 + , optInstallNameTool = po0 , optUnregisterised = Nothing , optTablesNextToCode = Nothing , optUseLibFFIForAdjustors = Nothing @@ -112,7 +122,8 @@ emptyOpts = Opts po0 = emptyProgOpt _optCc, _optCxx, _optCpp, _optHsCpp, _optJsCpp, _optCmmCpp, _optCcLink, _optAr, - _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optWindres, _optLd + _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optLlc, _optOpt, _optLlvmAs, + _optWindres, _optLd, _optOtool, _optInstallNameTool :: Lens Opts ProgOpt _optCc = Lens optCc (\x o -> o {optCc=x}) _optCxx = Lens optCxx (\x o -> o {optCxx=x}) @@ -126,8 +137,13 @@ _optRanlib = Lens optRanlib (\x o -> o {optRanlib=x}) _optNm = Lens optNm (\x o -> o {optNm=x}) _optReadelf = Lens optReadelf (\x o -> o {optReadelf=x}) _optMergeObjs = Lens optMergeObjs (\x o -> o {optMergeObjs=x}) +_optLlc = Lens optLlc (\x o -> o {optLlc=x}) +_optOpt = Lens optOpt (\x o -> o {optOpt=x}) +_optLlvmAs = Lens optLlvmAs (\x o -> o {optLlvmAs=x}) _optWindres = Lens optWindres (\x o -> o {optWindres=x}) -_optLd = Lens optLd (\x o -> o {optLd= x}) +_optLd = Lens optLd (\x o -> o {optLd=x}) +_optOtool = Lens optOtool (\x o -> o {optOtool=x}) +_optInstallNameTool = Lens optInstallNameTool (\x o -> o {optInstallNameTool=x}) _optTriple :: Lens Opts (Maybe String) _optTriple = Lens optTriple (\x o -> o {optTriple=x}) @@ -183,8 +199,13 @@ options = , progOpts "nm" "nm archiver" _optNm , progOpts "readelf" "readelf utility" _optReadelf , progOpts "merge-objs" "linker for merging objects" _optMergeObjs + , progOpts "llc" "LLVM llc utility" _optLlc + , progOpts "opt" "LLVM opt utility" _optOpt + , progOpts "llvm-as" "Assembler used for LLVM backend (typically clang)" _optLlvmAs , progOpts "windres" "windres utility" _optWindres , progOpts "ld" "linker" _optLd + , progOpts "otool" "otool utility" _optOtool + , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool ] where progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)] @@ -434,6 +455,11 @@ mkTarget opts = do when (isNothing mergeObjs && not (arSupportsDashL ar)) $ throwE "Neither a object-merging tool (e.g. ld -r) nor an ar that supports -L is available" + -- LLVM toolchain + llc <- optional $ findProgram "llc" (optLlc opts) ["llc"] + opt <- optional $ findProgram "opt" (optOpt opts) ["opt"] + llvmAs <- optional $ findProgram "llvm assembler" (optLlvmAs opts) ["clang"] + -- Windows-specific utilities windres <- case archOS_OS archOs of @@ -442,6 +468,15 @@ mkTarget opts = do return (Just windres) _ -> return Nothing + -- Darwin-specific utilities + (otool, installNameTool) <- + case archOS_OS archOs of + OSDarwin -> do + otool <- findProgram "otool" (optOtool opts) ["otool"] + installNameTool <- findProgram "install_name_tool" (optInstallNameTool opts) ["install_name_tool"] + return (Just otool, Just installNameTool) + _ -> return (Nothing, Nothing) + -- various other properties of the platform tgtWordSize <- checkWordSize cc tgtEndianness <- checkEndianness cc @@ -478,7 +513,12 @@ mkTarget opts = do , tgtRanlib = ranlib , tgtNm = nm , tgtMergeObjs = mergeObjs + , tgtLlc = llc + , tgtOpt = opt + , tgtLlvmAs = llvmAs , tgtWindres = windres + , tgtOtool = otool + , tgtInstallNameTool = installNameTool , tgtWordSize , tgtEndianness , tgtUnregisterised ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Target.hs ===================================== @@ -22,15 +22,6 @@ data WordSize = WS4 | WS8 data Endianness = LittleEndian | BigEndian deriving (Show, Read, Eq, Ord) --- TODO(#23674): Move the remaining relevant `settings-xxx` to Target: --- * llc command --- * opt command --- * install_name_tool --- * otool command --- --- Those are all things that are put into GHC's settings, and that might be --- different across targets - -- | A 'Target' consists of: -- -- * a target architecture and operating system @@ -72,8 +63,18 @@ data Target = Target , tgtMergeObjs :: Maybe MergeObjs -- ^ We don't need a merge objects tool if we @Ar@ supports @-L@ + -- LLVM backend toolchain + , tgtLlc :: Maybe Program + , tgtOpt :: Maybe Program + , tgtLlvmAs :: Maybe Program + -- ^ assembler used to assemble LLVM backend output; typically @clang@ + -- Windows-specific tools , tgtWindres :: Maybe Program + + -- Darwin-specific tools + , tgtOtool :: Maybe Program + , tgtInstallNameTool :: Maybe Program } deriving (Read, Eq, Ord) @@ -121,6 +122,11 @@ instance Show Target where , ", tgtRanlib = " ++ show tgtRanlib , ", tgtNm = " ++ show tgtNm , ", tgtMergeObjs = " ++ show tgtMergeObjs + , ", tgtLlc = " ++ show tgtLlc + , ", tgtOpt = " ++ show tgtOpt + , ", tgtLlvmAs = " ++ show tgtLlvmAs , ", tgtWindres = " ++ show tgtWindres + , ", tgtOtool = " ++ show tgtOtool + , ", tgtInstallNameTool = " ++ show tgtInstallNameTool , "}" ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ec47e4146926e59ca8684ba1e912057bb3df9c7...c5bfeafbbe057413e0fd9eb17308c626a25f4f5d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ec47e4146926e59ca8684ba1e912057bb3df9c7...c5bfeafbbe057413e0fd9eb17308c626a25f4f5d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/40c5036b/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 14:04:36 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 12 Mar 2025 10:04:36 -0400 Subject: [Git][ghc/ghc][wip/romes/better-main] driver: Move DynFlags consistency fixes off Main Message-ID: <67d1947468a99_232250c5da0248b7@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/better-main at Glasgow Haskell Compiler / GHC Commits: 077c9ff8 by Rodrigo Mesquita at 2025-03-12T14:04:21+00:00 driver: Move DynFlags consistency fixes off Main These consistency fixes found in Main.hs are required for the proper functioning of the compiler and should live together with all remaining fixes in `makeDynFlagsConsistent`. This is especially relevant to GHC applications that shouldn't have to copy/fix themselves possibly inconsistent DynFlags. Additionally, outputs information when verbosity is high about these consistency fixes that were previously quiet, adds information to the Note on consistency of DynFlags, and improves one of the fixes that incorrectly used `dynNow`. - - - - - 7 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - ghc/GHCi/UI.hs - ghc/Main.hs - utils/check-exact/Parsers.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -918,7 +918,7 @@ parseDynamicFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) parseDynamicFlags logger dflags cmdline = do - (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine dflags cmdline + (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine logger dflags cmdline -- flags that have just been read are used by the logger when loading package -- env (this is checked by T16318) let logger1 = setLogFlags logger (initLogFlags dflags1) @@ -1015,11 +1015,13 @@ normalise_hyp fp checkNewDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags checkNewDynFlags logger dflags = do -- See Note [DynFlags consistency] - let (dflags', warnings) = makeDynFlagsConsistent dflags + let (dflags', warnings, infoverb) = makeDynFlagsConsistent dflags let diag_opts = initDiagOpts dflags print_config = initPrintConfig dflags liftIO $ printOrThrowDiagnostics logger print_config diag_opts $ fmap GhcDriverMessage $ warnsToMessages diag_opts warnings + when (logVerbAtLeast logger 3) $ + mapM_ (\(L _loc m) -> liftIO $ logInfo logger m) infoverb return dflags' checkNewInteractiveDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -100,8 +100,9 @@ doBackpack [src_filename] = do dflags0 <- getDynFlags let dflags1 = dflags0 let parser_opts1 = initParserOpts dflags1 + logger0 <- getLogger (p_warns, src_opts) <- liftIO $ getOptionsFromFile parser_opts1 (supportedLanguagePragmas dflags1) src_filename - (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma dflags1 src_opts + (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma logger0 dflags1 src_opts modifySession (hscSetFlags dflags) logger <- getLogger -- Get the logger after having set the session flags, -- so that logger options are correctly set. ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -655,10 +655,11 @@ runUnlitPhase hsc_env input_fn output_fn = do getFileArgs :: HscEnv -> FilePath -> IO ((DynFlags, Messages PsMessage, Messages DriverMessage)) getFileArgs hsc_env input_fn = do let dflags0 = hsc_dflags hsc_env + logger = hsc_logger hsc_env parser_opts = initParserOpts dflags0 (warns0, src_opts) <- getOptionsFromFile parser_opts (supportedLanguagePragmas dflags0) input_fn (dflags1, unhandled_flags, warns) - <- parseDynamicFilePragma dflags0 src_opts + <- parseDynamicFilePragma logger dflags0 src_opts checkProcessArgsResult unhandled_flags return (dflags1, warns0, warns) ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -247,6 +247,7 @@ import GHC.Driver.Plugins.External import GHC.Settings.Config import GHC.Core.Unfold import GHC.Driver.CmdLine +import GHC.Utils.Logger import GHC.Utils.Panic import GHC.Utils.Misc import GHC.Utils.Constants (debugIsOn) @@ -265,7 +266,7 @@ import GHC.Data.FastString import GHC.Utils.TmpFs import GHC.Utils.Fingerprint import GHC.Utils.Outputable -import GHC.Utils.Error (emptyDiagOpts) +import GHC.Utils.Error (emptyDiagOpts, logInfo) import GHC.Settings import GHC.CmmToAsm.CFG.Weight import GHC.Core.Opt.CallerCC @@ -806,7 +807,7 @@ updOptLevel n = fst . updOptLevelChanged n -- the parsed 'DynFlags', the left-over arguments, and a list of warnings. -- Throws a 'UsageError' if errors occurred during parsing (such as unknown -- flags or missing arguments). -parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] +parseDynamicFlagsCmdLine :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -816,7 +817,7 @@ parseDynamicFlagsCmdLine = parseDynamicFlagsFull flagsAll True -- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags -- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db). -- Used to parse flags set in a modules pragma. -parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] +parseDynamicFilePragma :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -865,10 +866,11 @@ parseDynamicFlagsFull :: forall m. MonadIO m => [Flag (CmdLineP DynFlags)] -- ^ valid flags to match against -> Bool -- ^ are the arguments from the command line? + -> Logger -- ^ logger -> DynFlags -- ^ current dynamic flags -> [Located String] -- ^ arguments to parse -> m (DynFlags, [Located String], Messages DriverMessage) -parseDynamicFlagsFull activeFlags cmdline dflags0 args = do +parseDynamicFlagsFull activeFlags cmdline logger dflags0 args = do ((leftover, errs, cli_warns), dflags1) <- processCmdLineP activeFlags dflags0 args -- See Note [Handling errors when parsing command-line flags] @@ -884,7 +886,7 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do throwGhcExceptionIO (CmdLineError ("combination not supported: " ++ intercalate "/" (map wayDesc (Set.toAscList theWays)))) - let (dflags3, consistency_warnings) = makeDynFlagsConsistent dflags2 + let (dflags3, consistency_warnings, infoverb) = makeDynFlagsConsistent dflags2 -- Set timer stats & heap size when (enableTimeStats dflags3) $ liftIO enableTimingStats @@ -898,6 +900,9 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do let diag_opts = initDiagOpts dflags3 warns = warnsToMessages diag_opts $ mconcat [consistency_warnings, sh_warns, cli_warns] + when (logVerbAtLeast logger 3) $ + mapM_ (\(L _loc m) -> liftIO $ logInfo logger m) infoverb + return (dflags3, leftover, warns) -- | Check (and potentially disable) any extensions that aren't allowed @@ -3491,12 +3496,35 @@ combination when parsing flags, we also need to check when we update the flags; this is because API clients may parse flags but update the DynFlags afterwords, before finally running code inside a session (see T10052 and #10052). + +Host ways vs Build ways mismatch +-------------------------------- +Many consistency checks aim to fix the situation where the wanted build ways +are not compatible with the ways the compiler is built in. This happens when +using the interpreter, TH, and the runtime linker, where the compiler cannot +load objects compiled for ways not matching its own. + +For instance, a profiled-dynamic object can only be loaded by a +profiled-dynamic compiler (and not any other kind of compiler). + +This incompatibility is traditionally solved in either of two ways: + +(1) Force the "wanted" build ways to match the compiler ways exactly, + guaranteeing they match. + +(2) Force the use of the external interpreter. When interpreting is offloaded + to the external interpreter it no longer matters what are the host compiler ways. + +In the checks and fixes performed by `makeDynFlagsConsistent`, the choice +between the two does not seem uniform. TODO: Make this choice more evident and uniform. -} -- | Resolve any internal inconsistencies in a set of 'DynFlags'. -- Returns the consistent 'DynFlags' as well as a list of warnings --- to report to the user. -makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn]) +-- to report to the user, and a list of verbose info msgs. +-- +-- See Note [DynFlags consistency] +makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn], [Located SDoc]) -- Whenever makeDynFlagsConsistent does anything, it starts over, to -- ensure that a later change doesn't invalidate an earlier check. -- Be careful not to introduce potential loops! @@ -3587,13 +3615,41 @@ makeDynFlagsConsistent dflags | LinkMergedObj <- ghcLink dflags , Nothing <- outputFile dflags - = pgmError "--output must be specified when using --merge-objs" + = pgmError "--output must be specified when using --merge-objs" + + -- When we do ghci, force using dyn ways if the target RTS linker + -- only supports dynamic code + | LinkInMemory <- ghcLink dflags + , sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags + , not (ways dflags `hasWay` WayDyn && gopt Opt_ExternalInterpreter dflags) + = flip loopNoWarn "Forcing dynamic way because target RTS linker only supports dynamic code" $ + -- See checkOptions, -fexternal-interpreter is + -- required when using --interactive with a non-standard + -- way (-prof, -static, or -dynamic). + setGeneralFlag' Opt_ExternalInterpreter $ + addWay' WayDyn dflags - | otherwise = (dflags, mempty) + | LinkInMemory <- ghcLink dflags + , not (gopt Opt_ExternalInterpreter dflags) + , targetWays_ dflags /= hostFullWays + = flip loopNoWarn "Forcing build ways to match the compiler ways because we're using the internal interpreter" $ + let dflags_a = dflags { targetWays_ = hostFullWays } + dflags_b = foldl gopt_set dflags_a + $ concatMap (wayGeneralFlags platform) + hostFullWays + dflags_c = foldl gopt_unset dflags_b + $ concatMap (wayUnsetGeneralFlags platform) + hostFullWays + in dflags_c + + | otherwise = (dflags, mempty, mempty) where loc = mkGeneralSrcSpan (fsLit "when making flags consistent") loop updated_dflags warning = case makeDynFlagsConsistent updated_dflags of - (dflags', ws) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws) + (dflags', ws, is) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws, is) + loopNoWarn updated_dflags doc + = case makeDynFlagsConsistent updated_dflags of + (dflags', ws, is) -> (dflags', ws, L loc (text doc):is) platform = targetPlatform dflags arch = platformArch platform os = platformOS platform ===================================== ghc/GHCi/UI.hs ===================================== @@ -3148,7 +3148,7 @@ newDynFlags interactive_only minus_opts = do logger <- getLogger idflags0 <- GHC.getInteractiveDynFlags - (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine idflags0 lopts + (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine logger idflags0 lopts liftIO $ printOrThrowDiagnostics logger (initPrintConfig idflags1) (initDiagOpts idflags1) (GhcDriverMessage <$> warns) when (not $ null leftovers) (unknownFlagsErr $ map unLoc leftovers) @@ -3161,7 +3161,7 @@ newDynFlags interactive_only minus_opts = do dflags0 <- getDynFlags when (not interactive_only) $ do - (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine dflags0 lopts + (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine logger dflags0 lopts must_reload <- GHC.setProgramDynFlags dflags1 -- if the package flags changed, reset the context and link ===================================== ghc/Main.hs ===================================== @@ -224,41 +224,9 @@ main' postLoadMode units dflags0 args flagWarnings = do -- The rest of the arguments are "dynamic" -- Leftover ones are presumably files - (dflags3', fileish_args, dynamicFlagWarnings) <- + (dflags4, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags logger2 dflags2 args' - -- When we do ghci, force using dyn ways if the target RTS linker - -- only supports dynamic code - let dflags3 - | LinkInMemory <- link, - sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags3' - = setDynamicNow $ - -- See checkOptions below, -fexternal-interpreter is - -- required when using --interactive with a non-standard - -- way (-prof, -static, or -dynamic). - setGeneralFlag' Opt_ExternalInterpreter $ - -- Use .o for dynamic object, otherwise it gets dropped - -- with "Warning: ignoring unrecognised input", see - -- objish_suffixes - dflags3' { dynObjectSuf_ = objectSuf dflags3' } - | otherwise - = dflags3' - - let dflags4 = if backendNeedsFullWays bcknd && - not (gopt Opt_ExternalInterpreter dflags3) - then - let platform = targetPlatform dflags3 - dflags3a = dflags3 { targetWays_ = hostFullWays } - dflags3b = foldl gopt_set dflags3a - $ concatMap (wayGeneralFlags platform) - hostFullWays - dflags3c = foldl gopt_unset dflags3b - $ concatMap (wayUnsetGeneralFlags platform) - hostFullWays - in dflags3c - else - dflags3 - let logger4 = setLogFlags logger2 (initLogFlags dflags4) GHC.prettyPrintGhcErrors logger4 $ do @@ -804,7 +772,7 @@ initMulti unitArgsFiles = do dynFlagsAndSrcs <- forM unitArgsFiles $ \f -> do when (verbosity initial_dflags > 2) (liftIO $ print f) args <- liftIO $ expandResponse [f] - (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine initial_dflags (map (mkGeneralLocated f) (removeRTS args)) + (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine logger initial_dflags (map (mkGeneralLocated f) (removeRTS args)) handleSourceError (\e -> do GHC.printException e liftIO $ exitWith (ExitFailure 1)) $ do ===================================== utils/check-exact/Parsers.hs ===================================== @@ -348,12 +348,14 @@ initDynFlags file = do -- Based on GHC backpack driver doBackPack dflags0 <- GHC.getSessionDynFlags let parser_opts0 = GHC.initParserOpts dflags0 + logger <- GHC.getLogger (_, src_opts) <- GHC.liftIO $ GHC.getOptionsFromFile parser_opts0 (GHC.supportedLanguagePragmas dflags0) file - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 src_opts + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 src_opts -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 @@ -375,13 +377,15 @@ initDynFlagsPure fp s = do -- as long as `parseDynamicFilePragma` is impure there seems to be -- no reason to use it. dflags0 <- GHC.getSessionDynFlags + logger <- GHC.getLogger let parser_opts0 = GHC.initParserOpts dflags0 let (_, pragmaInfo) = GHC.getOptions parser_opts0 (GHC.supportedLanguagePragmas dflags0) (GHC.stringToStringBuffer $ s) fp - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 pragmaInfo + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 pragmaInfo -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/077c9ff8fd7ed561983a18813f84056e1cc2967c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/077c9ff8fd7ed561983a18813f84056e1cc2967c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/dde0663b/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 15:49:19 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Mar 2025 11:49:19 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] Do rules both before and after [skip ci] Message-ID: <67d1acff8bba9_25223654b668790f1@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: f5ebf251 by Simon Peyton Jones at 2025-03-12T15:45:13+00:00 Do rules both before and after [skip ci] Before iff there is an active unfolding. But always after. Consider not doing after if before fails. Typically if the rule applies the unfolding is inactive Goal (in T24984) augment f (augment g (augment h (build k))) --> augment f (augment g (build..)) --> augment f (build..) --> augment f (build..) Want to do this in one pass. Work in progress - - - - - 6 changed files: - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/CoreToStg/Prep.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Env.hs ===================================== @@ -30,7 +30,7 @@ module GHC.Core.Opt.Simplify.Env ( -- * Simplifying 'Id' binders simplNonRecBndr, simplNonRecJoinBndr, simplRecBndrs, simplRecJoinBndrs, simplBinder, simplBinders, - substTy, substTyVar, getSubst, + substTy, substTyVar, getFullSubst, getTCvSubst, substCo, substCoVar, -- * Floats @@ -58,8 +58,9 @@ import GHC.Core.Opt.Simplify.Monad import GHC.Core.Rules.Config ( RuleOpts(..) ) import GHC.Core import GHC.Core.Utils +import GHC.Core.Subst( substExprSC ) import GHC.Core.Unfold -import GHC.Core.TyCo.Subst (emptyIdSubstEnv) +import GHC.Core.TyCo.Subst (emptyIdSubstEnv, mkSubst) import GHC.Core.Multiplicity( Scaled(..), mkMultMul ) import GHC.Core.Make ( mkWildValBinder, mkCoreLet ) import GHC.Core.Type hiding ( substTy, substTyVar, substTyVarBndr, substCo @@ -1258,33 +1259,47 @@ See also Note [Return type for join points] and Note [Join points and case-of-ca ************************************************************************ -} -getSubst :: SimplEnv -> Subst -getSubst (SimplEnv { seInScope = in_scope, seTvSubst = tv_env, seCvSubst = cv_env }) - = mkTCvSubst in_scope tv_env cv_env +getTCvSubst :: SimplEnv -> Subst +getTCvSubst (SimplEnv { seInScope = in_scope, seTvSubst = tv_env, seCvSubst = cv_env }) + = mkSubst in_scope emptyVarEnv tv_env cv_env + +getFullSubst :: SimplEnv -> Subst +getFullSubst (SimplEnv { seInScope = in_scope, seIdSubst = id_env, seTvSubst = tv_env, seCvSubst = cv_env }) + = mk_full_subst in_scope tv_env cv_env id_env + +mk_full_subst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> SimplIdSubst -> Subst +mk_full_subst in_scope tv_env cv_env id_env + = mkSubst in_scope (mapVarEnv to_expr id_env) tv_env cv_env + where + to_expr :: SimplSR -> CoreExpr + -- A tiresome impedence-matcher + to_expr (DoneEx e _) = e + to_expr (DoneId v) = Var v + to_expr (ContEx tvs cvs ids e) = GHC.Core.Subst.substExprSC (mk_full_subst in_scope tvs cvs ids) e substTy :: HasDebugCallStack => SimplEnv -> Type -> Type -substTy env ty = Type.substTy (getSubst env) ty +substTy env ty = Type.substTy (getTCvSubst env) ty substTyVar :: SimplEnv -> TyVar -> Type -substTyVar env tv = Type.substTyVar (getSubst env) tv +substTyVar env tv = Type.substTyVar (getTCvSubst env) tv substTyVarBndr :: SimplEnv -> TyVar -> (SimplEnv, TyVar) substTyVarBndr env tv - = case Type.substTyVarBndr (getSubst env) tv of + = case Type.substTyVarBndr (getTCvSubst env) tv of (Subst in_scope' _ tv_env' cv_env', tv') -> (env { seInScope = in_scope', seTvSubst = tv_env', seCvSubst = cv_env' }, tv') substCoVar :: SimplEnv -> CoVar -> Coercion -substCoVar env tv = Coercion.substCoVar (getSubst env) tv +substCoVar env tv = Coercion.substCoVar (getTCvSubst env) tv substCoVarBndr :: SimplEnv -> CoVar -> (SimplEnv, CoVar) substCoVarBndr env cv - = case Coercion.substCoVarBndr (getSubst env) cv of + = case Coercion.substCoVarBndr (getTCvSubst env) cv of (Subst in_scope' _ tv_env' cv_env', cv') -> (env { seInScope = in_scope', seTvSubst = tv_env', seCvSubst = cv_env' }, cv') substCo :: SimplEnv -> Coercion -> Coercion -substCo env co = Coercion.substCo (getSubst env) co +substCo env co = Coercion.substCo (getTCvSubst env) co ------------------ substIdType :: SimplEnv -> Id -> Id ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -1159,14 +1159,14 @@ simplExprF :: SimplEnv -> SimplM (SimplFloats, OutExpr) simplExprF !env e !cont -- See Note [Bangs in the Simplifier] - = {- pprTrace "simplExprF" (vcat - [ ppr e - , text "cont =" <+> ppr cont - , text "inscope =" <+> ppr (seInScope env) - , text "tvsubst =" <+> ppr (seTvSubst env) - , text "idsubst =" <+> ppr (seIdSubst env) - , text "cvsubst =" <+> ppr (seCvSubst env) - ]) $ -} + = -- pprTrace "simplExprF" (vcat + -- [ ppr e + -- , text "cont =" <+> ppr cont + -- , text "inscope =" <+> ppr (seInScope env) + -- , text "tvsubst =" <+> ppr (seTvSubst env) + -- , text "idsubst =" <+> ppr (seIdSubst env) + -- , text "cvsubst =" <+> ppr (seCvSubst env) + -- ]) $ simplExprF1 env e cont simplExprF1 :: HasDebugCallStack @@ -1358,7 +1358,7 @@ simplCoercion env co -- See Note [Inline depth] in GHC.Core.Opt.Simplify.Env ; seqCo opt_co `seq` return opt_co } where - subst = getSubst env + subst = getTCvSubst env opts = seOptCoercionOpts env ----------------------------------- @@ -2261,11 +2261,64 @@ simplInId env var cont --------------------------------------------------------- simplOutId :: SimplEnv -> OutId -> SimplCont -> SimplM (SimplFloats, OutExpr) + +---------- The runRW# rule ------ +-- See Note [Simplification of runRW#] in GHC.CoreToSTG.Prep. +-- +-- runRW# :: forall (r :: RuntimeRep) (o :: TYPE r). (State# RealWorld -> o) -> o +-- K[ runRW# @rr @hole_ty body ] --> runRW @rr' @ty' (\s. K[ body s ]) +simplOutId env fun cont + | fun `hasKey` runRWKey + , ApplyToTy { sc_cont = cont1 } <- cont + , ApplyToTy { sc_cont = cont2, sc_arg_ty = hole_ty } <- cont1 + , ApplyToVal { sc_cont = cont3, sc_arg = arg + , sc_env = arg_se, sc_hole_ty = fun_ty } <- cont2 + -- Do this even if (contIsStop cont), or if seCaseCase is off. + -- See Note [No eta-expansion in runRW#] + = do { let arg_env = arg_se `setInScopeFromE` env + + overall_res_ty = contResultType cont3 + -- hole_ty is the type of the current runRW# application + (outer_cont, new_runrw_res_ty, inner_cont) + | seCaseCase env = (mkBoringStop overall_res_ty, overall_res_ty, cont3) + | otherwise = (cont3, hole_ty, mkBoringStop hole_ty) + -- Only when case-of-case is on. See GHC.Driver.Config.Core.Opt.Simplify + -- Note [Case-of-case and full laziness] + + -- If the argument is a literal lambda already, take a short cut + -- This isn't just efficiency: + -- * If we don't do this we get a beta-redex every time, so the + -- simplifier keeps doing more iterations. + -- * Even more important: see Note [No eta-expansion in runRW#] + ; arg' <- case arg of + Lam s body -> do { (env', s') <- simplBinder arg_env s + ; body' <- simplExprC env' body inner_cont + ; return (Lam s' body') } + -- Important: do not try to eta-expand this lambda + -- See Note [No eta-expansion in runRW#] + + _ -> do { s' <- newId (fsLit "s") ManyTy realWorldStatePrimTy + ; let (m,_,_) = splitFunTy fun_ty + env' = arg_env `addNewInScopeIds` [s'] + cont' = ApplyToVal { sc_dup = Simplified, sc_arg = Var s' + , sc_env = env', sc_cont = inner_cont + , sc_hole_ty = mkVisFunTy m realWorldStatePrimTy new_runrw_res_ty } + -- cont' applies to s', then K + ; body' <- simplExprC env' arg cont' + ; return (Lam s' body') } + + ; let rr' = getRuntimeRep new_runrw_res_ty + call' = mkApps (Var fun) [mkTyArg rr', mkTyArg new_runrw_res_ty, arg'] + ; rebuild env call' outer_cont } + + simplOutId env fun cont = do { rule_base <- getSimplRules ; let rules_for_me = getRules rule_base fun - ; mb_match <- tryRules zapped_env rules_for_me fun cont1 + ; mb_match <- if activeUnfolding (seMode env) fun + then tryRules zapped_env rules_for_me fun cont1 + else return Nothing ; case mb_match of { Just (rhs, cont2) -> simplExprF zapped_env rhs cont2 ; Nothing -> @@ -2365,54 +2418,6 @@ rebuildCall env info (CastIt { sc_co = co, sc_opt = opt, sc_cont = cont }) rebuildCall env info (ApplyToTy { sc_arg_ty = arg_ty, sc_hole_ty = hole_ty, sc_cont = cont }) = rebuildCall env (addTyArgTo info arg_ty hole_ty) cont ----------- The runRW# rule. Do this after absorbing all arguments ------ --- See Note [Simplification of runRW#] in GHC.CoreToSTG.Prep. --- --- runRW# :: forall (r :: RuntimeRep) (o :: TYPE r). (State# RealWorld -> o) -> o --- K[ runRW# rr ty body ] --> runRW rr' ty' (\s. K[ body s ]) -rebuildCall env (ArgInfo { ai_fun = fun_id, ai_args = rev_args }) - (ApplyToVal { sc_arg = arg, sc_env = arg_se - , sc_cont = cont, sc_hole_ty = fun_ty }) - | fun_id `hasKey` runRWKey - , [ TyArg { as_arg_ty = hole_ty }, TyArg {} ] <- rev_args - -- Do this even if (contIsStop cont), or if seCaseCase is off. - -- See Note [No eta-expansion in runRW#] - = do { let arg_env = arg_se `setInScopeFromE` env - - overall_res_ty = contResultType cont - -- hole_ty is the type of the current runRW# application - (outer_cont, new_runrw_res_ty, inner_cont) - | seCaseCase env = (mkBoringStop overall_res_ty, overall_res_ty, cont) - | otherwise = (cont, hole_ty, mkBoringStop hole_ty) - -- Only when case-of-case is on. See GHC.Driver.Config.Core.Opt.Simplify - -- Note [Case-of-case and full laziness] - - -- If the argument is a literal lambda already, take a short cut - -- This isn't just efficiency: - -- * If we don't do this we get a beta-redex every time, so the - -- simplifier keeps doing more iterations. - -- * Even more important: see Note [No eta-expansion in runRW#] - ; arg' <- case arg of - Lam s body -> do { (env', s') <- simplBinder arg_env s - ; body' <- simplExprC env' body inner_cont - ; return (Lam s' body') } - -- Important: do not try to eta-expand this lambda - -- See Note [No eta-expansion in runRW#] - - _ -> do { s' <- newId (fsLit "s") ManyTy realWorldStatePrimTy - ; let (m,_,_) = splitFunTy fun_ty - env' = arg_env `addNewInScopeIds` [s'] - cont' = ApplyToVal { sc_dup = Simplified, sc_arg = Var s' - , sc_env = env', sc_cont = inner_cont - , sc_hole_ty = mkVisFunTy m realWorldStatePrimTy new_runrw_res_ty } - -- cont' applies to s', then K - ; body' <- simplExprC env' arg cont' - ; return (Lam s' body') } - - ; let rr' = getRuntimeRep new_runrw_res_ty - call' = mkApps (Var fun_id) [mkTyArg rr', mkTyArg new_runrw_res_ty, arg'] - ; rebuild env call' outer_cont } - ---------- Simplify value arguments -------------------- rebuildCall env fun_info (ApplyToVal { sc_arg = arg, sc_env = arg_se @@ -2443,8 +2448,12 @@ rebuildCall env fun_info ; rebuildCall env (addValArgTo fun_info arg' fun_ty) cont } ---------- No further useful info, revert to generic rebuild ------------ -rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args }) cont +rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) cont + | null rules = rebuild env (argInfoExpr fun rev_args) cont + | otherwise -- Try rules again + = do { let args = argInfoAppArgs rev_args + ; mb_match <- tryRules env rules run args ----------------------------------- tryInlining :: SimplEnv -> Logger -> OutId -> SimplCont -> SimplM (Maybe OutExpr) @@ -2612,12 +2621,11 @@ tryRules env rules fn cont | null rules = return Nothing - | Just (rule, rule_rhs) <- pprTrace "tryRules" (ppr fn) $ - lookupRule ropts (getUnfoldingInRuleMatch env) - (activeRule (seMode env)) fn - (contOutArgs cont) rules + | Just (rule, rule_rhs) <- -- pprTrace "tryRules" (ppr fn) $ + lookupRule ropts in_scope_env + act_fun fn out_args rules -- Fire a rule for the function - = pprTrace "tryRules:success" (ppr fn) $ + = -- pprTrace "tryRules:success" (ppr fn) $ do { logger <- getLogger ; checkedTick (RuleFired (ruleName rule)) ; let cont' = dropContArgs (ruleArity rule) cont @@ -2632,13 +2640,16 @@ tryRules env rules fn cont -- hence zapping the environment | otherwise -- No rule fires - = pprTrace "tryRules:fail" (ppr fn) $ + = -- pprTrace "tryRules:fail" (ppr fn) $ do { logger <- getLogger ; nodump logger -- This ensures that an empty file is written ; return Nothing } where - ropts = seRuleOpts env + ropts = seRuleOpts env :: RuleOpts + in_scope_env = getUnfoldingInRuleMatch env :: InScopeEnv + out_args = contOutArgs cont :: [OutExpr] + act_fun = activeRule (seMode env) :: Activation -> Bool printRuleModule rule = parens (maybe (text "BUILTIN") ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -85,7 +85,6 @@ import Control.Monad ( when ) import Data.List ( sortBy ) import GHC.Types.Name.Env import Data.Graph -import Data.Maybe {- ********************************************************************* * * @@ -283,9 +282,9 @@ instance Outputable SimplCont where = (text "TickIt" <+> ppr t) $$ ppr cont ppr (ApplyToTy { sc_arg_ty = ty, sc_cont = cont }) = (text "ApplyToTy" <+> pprParendType ty) $$ ppr cont - ppr (ApplyToVal { sc_arg = arg, sc_dup = dup, sc_cont = cont, sc_hole_ty = hole_ty }) - = (hang (text "ApplyToVal" <+> ppr dup <+> text "hole" <+> ppr hole_ty) - 2 (pprParendExpr arg)) + ppr (ApplyToVal { sc_arg = arg, sc_dup = dup, sc_cont = cont, sc_hole_ty = hole_ty, sc_env = env }) + = (hang (text "ApplyToVal" <+> ppr dup <+> text "hole-ty:" <+> pprParendType hole_ty) + 2 (ppr (seIdSubst env) $$ pprParendExpr arg)) $$ ppr cont ppr (StrictBind { sc_bndr = b, sc_cont = cont }) = (text "StrictBind" <+> ppr b) $$ ppr cont @@ -326,9 +325,10 @@ data ArgInfo ai_args :: [ArgSpec], -- ...applied to these args (which are in *reverse* order) -- NB: all these argumennts are already simplified - ai_rewrite :: RewriteCall, -- What transformation to try next for this call - -- See Note [Rewrite rules and inlining] in GHC.Core.Opt.Simplify.Iteration +-- ai_rewrite :: RewriteCall, -- What transformation to try next for this call +-- -- See Note [Rewrite rules and inlining] in GHC.Core.Opt.Simplify.Iteration + ai_rules :: [CoreRule], -- Rules for this function ai_encl :: Bool, -- Flag saying whether this function -- or an enclosing one has rules (recursively) -- True => be keener to inline in all args @@ -596,7 +596,8 @@ contOutArgs (ApplyToVal { sc_dup = dup, sc_arg = arg, sc_env = env, sc_cont = co | isSimplified dup = arg : contOutArgs cont | otherwise - = GHC.Core.Subst.substExprSC (getSubst env) arg : contOutArgs cont + = -- pprTrace "contOutArgs" (ppr arg $$ ppr (seIdSubst env)) $ + GHC.Core.Subst.substExprSC (getFullSubst env) arg : contOutArgs cont contOutArgs _ = [] @@ -642,20 +643,19 @@ mkArgInfo :: SimplEnv -> [CoreRule] -> Id -> SimplCont -> ArgInfo mkArgInfo env rules_for_fun fun cont | n_val_args < idArity fun -- Note [Unsaturated functions] = ArgInfo { ai_fun = fun, ai_args = [] - , ai_rewrite = fun_rewrite + , ai_rules = rules_for_fun , ai_encl = False , ai_dmds = vanilla_dmds , ai_discs = vanilla_discounts } | otherwise = ArgInfo { ai_fun = fun , ai_args = [] - , ai_rewrite = fun_rewrite + , ai_rules = rules_for_fun , ai_encl = fun_has_rules || contHasRules cont , ai_dmds = add_type_strictness (idType fun) arg_dmds , ai_discs = arg_discounts } where n_val_args = countValArgs cont - fun_rewrite = TryNothing fun_has_rules = not (null rules_for_fun) @@ -1474,10 +1474,6 @@ preInlineUnconditionally -- Reason: we don't want to inline single uses, or discard dead bindings, -- for unlifted, side-effect-ful bindings preInlineUnconditionally env top_lvl bndr rhs rhs_env - = pprTrace "preInlineUnconditionally" (ppr bndr <+> ppr (isJust res)) $ - res - where - res | not pre_inline_unconditionally = Nothing | not active = Nothing | isTopLevel top_lvl && isDeadEndId bndr = Nothing -- Note [Top-level bottoming Ids] ===================================== compiler/GHC/Core/Subst.hs ===================================== @@ -239,11 +239,7 @@ substExprSC :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr -- their canonical representatives in the in-scope set substExprSC subst orig_expr | isEmptySubst subst = orig_expr - | otherwise = pprTrace "enter subst-expr" (ppr subst $$ ppr orig_expr) $ - pprTrace "result subst-expr" (ppr res) $ - res - where - res = substExpr subst orig_expr + | otherwise = substExpr subst orig_expr -- | substExpr applies a substitution to an entire 'CoreExpr'. Remember, -- you may only apply the substitution /once/: ===================================== compiler/GHC/Core/TyCo/Subst.hs ===================================== @@ -13,7 +13,7 @@ module GHC.Core.TyCo.Subst Subst(..), TvSubstEnv, CvSubstEnv, IdSubstEnv, emptyIdSubstEnv, emptyTvSubstEnv, emptyCvSubstEnv, composeTCvSubst, emptySubst, mkEmptySubst, isEmptyTCvSubst, isEmptySubst, - mkTCvSubst, mkTvSubst, mkCvSubst, mkIdSubst, + mkSubst, mkTCvSubst, mkTvSubst, mkCvSubst, mkIdSubst, getTvSubstEnv, getIdSubstEnv, getCvSubstEnv, substInScopeSet, setInScope, getSubstRangeTyCoFVs, isInScope, elemSubst, notElemSubst, zapSubst, @@ -273,6 +273,9 @@ isEmptyTCvSubst :: Subst -> Bool isEmptyTCvSubst (Subst _ _ tv_env cv_env) = isEmptyVarEnv tv_env && isEmptyVarEnv cv_env +mkSubst :: InScopeSet -> IdSubstEnv -> TvSubstEnv -> CvSubstEnv -> Subst +mkSubst = Subst + mkTCvSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> Subst mkTCvSubst in_scope tvs cvs = Subst in_scope emptyIdSubstEnv tvs cvs ===================================== compiler/GHC/CoreToStg/Prep.hs ===================================== @@ -1492,7 +1492,6 @@ The former had the CPR property, and so should the latter. Other considered designs ------------------------ - One design that was rejected was to *require* that runRW#'s continuation be headed by a lambda. However, this proved to be quite fragile. For instance, SetLevels is very eager to float bottoming expressions. For instance given View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f5ebf251ef975b977d1772fe679a499479010f92 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f5ebf251ef975b977d1772fe679a499479010f92 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/a4086bc9/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 16:16:28 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Mar 2025 12:16:28 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: mk-ghcup-metadata: Clean up and add type annotations Message-ID: <67d1b35cc3efc_252236856d1c85850@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 6e89cee9 by Matthew Pickering at 2025-03-12T12:16:22-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 5346c9c6 by Matthew Craven at 2025-03-12T12:16:23-04:00 Add interface-stability test for ghc-prim - - - - - 37 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - libraries/ghc-boot/GHC/Serialized.hs - rts/HeapStackCheck.cmm - rts/PrimOps.cmm - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - utils/dump-decls/Main.hs - utils/haddock/haddock-api/src/Haddock/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/df68f43dfa93e97e70f226671588bfec45d891c4...5346c9c653dc5a65f3f476956ac18ed21af3049c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/df68f43dfa93e97e70f226671588bfec45d891c4...5346c9c653dc5a65f3f476956ac18ed21af3049c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/7c09f4e1/attachment.html> From gitlab at gitlab.haskell.org Wed Mar 12 17:07:48 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 12 Mar 2025 13:07:48 -0400 Subject: [Git][ghc/ghc][wip/backports-9.10] 5 commits: Expand LLVM version matching regex for compability with bsd systems Message-ID: <67d1bf64c1d76_26cace190e4c456ab@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC Commits: 291860da by Matthew Pickering at 2025-03-11T09:35:06-04:00 Expand LLVM version matching regex for compability with bsd systems 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 (cherry picked from commit 77ce65a5e9b14c29f8f47bfbe452b1d6296c45e8) - - - - - cac7c45d by Ben Gamari at 2025-03-11T09:35:06-04:00 ghc-internal: Update CHANGELOG to reflect current version (cherry picked from commit 580fef7b1be1ea7247e9c7bc7ce0e3150b03fc36) - - - - - 04cf8504 by Ben Gamari at 2025-03-11T09:35:06-04:00 ghc-internal: Update prologue.txt to reflect package description (cherry picked from commit 391ecff5ced86e52089c5a5c46158a22755312a9) - - - - - 7348dfc2 by Matthew Pickering at 2025-03-11T09:35:06-04:00 Remove accidentally committed test.hs (cherry picked from commit e8724327d995a67d3eb066dfe4f9ee03e64dd6b5) - - - - - f2e63a12 by Matthew Pickering at 2025-03-11T09:35:06-04:00 libraries: Update os-string to 2.0.4 This updates the os-string submodule to 2.0.4 which removes the usage of `TemplateHaskell` pragma. (cherry picked from commit 37139b17f44cc489cc42cdac4e1b5b04b502d1b4) - - - - - 5 changed files: - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/prologue.txt - libraries/os-string - m4/find_llvm_prog.m4 - − test.hs Changes: ===================================== libraries/ghc-internal/CHANGELOG.md ===================================== @@ -1,5 +1,5 @@ # Revision history for `ghc-internal` -## 0.1.0.0 -- YYYY-mm-dd +## 9.1001.0 -- 2024-05-01 -* First version. Released on an unsuspecting world. +* Package created containing implementation moved from `base`. ===================================== libraries/ghc-internal/prologue.txt ===================================== @@ -1,3 +1,2 @@ -This package contains the @Prelude@ and its support libraries, and a large -collection of useful libraries ranging from data structures to parsing -combinators and debugging utilities. +This package contains the implementation of GHC's standard libraries and is +not intended for use by end-users. ===================================== libraries/os-string ===================================== @@ -1 +1 @@ -Subproject commit e1dd3bcfab56a6616c73ee9220de425d55545bc8 +Subproject commit 6d31aafde2f7b8c3050ffee7dd9f658225cfd1a4 ===================================== m4/find_llvm_prog.m4 ===================================== @@ -14,7 +14,7 @@ AC_DEFUN([FIND_LLVM_PROG],[ PROG_VERSION_CANDIDATES=$(for llvmVersion in `seq $(($4-1)) -1 $3`; do echo "$2-$llvmVersion $2-$llvmVersion.0 $2$llvmVersion"; done) AC_CHECK_TOOLS([$1], [$PROG_VERSION_CANDIDATES $2], []) AS_IF([test x"$$1" != x],[ - PROG_VERSION=`$$1 --version | sed -n -e 's/.*version \(\([[0-9]]\+\.\)\+[[0-9]]\+\).*/\1/gp'` + PROG_VERSION=`$$1 --version | sed -n -e 's/.*version \(\([[0-9]][[0-9]]*\.\)\([[0-9]][[0-9]]*\.\)*[[0-9]][[0-9]]*\).*/\1/gp'` AS_IF([test x"$PROG_VERSION" = x], [AC_MSG_RESULT(no) $1="" ===================================== test.hs deleted ===================================== @@ -1,14 +0,0 @@ -import Data.Char -import Data.Foldable --- | Just like 'GHC.ResponseFile.escapeArg', but it is not exposed from base. -escapeArg :: String -> String -escapeArg = reverse . foldl' escape [] - -escape :: String -> Char -> String -escape cs c - | isSpace c - || '\\' == c - || '\'' == c - || '"' == c = c:'\\':cs -- n.b., our caller must reverse the result - | otherwise = c:cs - View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ade5ae4f12f81eb0841e6a1627eb03cc762b803b...f2e63a12313687e3aaeb052aa80ee8d7817052ec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ade5ae4f12f81eb0841e6a1627eb03cc762b803b...f2e63a12313687e3aaeb052aa80ee8d7817052ec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/e782c37e/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 17:38:14 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Wed, 12 Mar 2025 13:38:14 -0400 Subject: [Git][ghc/ghc][wip/T25365] 20 commits: users guide: Fix typo Message-ID: <67d1c686c1148_2792121cd93c40339@gitlab.mail> Ben Gamari pushed to branch wip/T25365 at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b148dbcf by Ben Gamari at 2025-03-12T13:37:57-04:00 ghc-internal: Move STM utilities out of GHC.Internal.Conc.Sync This is necessary to avoid an import cycle on Windows when importing `GHC.Internal.Exception.Context` in `GHC.Internal.Conc.Sync`. On the road to address #25365. - - - - - f974a0c8 by Ben Gamari at 2025-03-12T13:37:57-04:00 base: Capture backtrace from throwSTM Implements core-libraries-committee#297. Fixes #25365. - - - - - 6d92486b by Ben Gamari at 2025-03-12T13:37:57-04:00 base: Annotate rethrown exceptions in catchSTM with WhileHandling Implements core-libraries-committee#298 - - - - - 111 changed files: - compiler/GHC.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/using-concurrent.rst - libraries/base/changelog.md - libraries/base/src/GHC/Conc.hs - libraries/base/src/GHC/Conc/Sync.hs - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/Conc/IO.hs - libraries/ghc-internal/src/GHC/Internal/Conc/POSIX.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs - libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs-boot - libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs - + libraries/ghc-internal/src/GHC/Internal/STM.hs - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/driver/junit.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/79ebe7230b38e6478b1d516b54cbd1d104396f40...6d92486b8974ffe7d896d2a170faf633ecf03846 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/79ebe7230b38e6478b1d516b54cbd1d104396f40...6d92486b8974ffe7d896d2a170faf633ecf03846 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/e3b1a64f/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 17:42:07 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Mar 2025 13:42:07 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] More WIP [skip ci] Message-ID: <67d1c76f7aa8a_27921257cb784289b@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: b86769ca by Simon Peyton Jones at 2025-03-12T17:41:46+00:00 More WIP [skip ci] - - - - - 2 changed files: - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -69,6 +69,7 @@ import GHC.Utils.Misc import Control.Monad import Data.List.NonEmpty (NonEmpty (..)) +import Data.Maybe {- The guts of the simplifier is in this module, but the driver loop for @@ -1827,7 +1828,8 @@ simpl_lam env bndr body (ApplyToVal { sc_arg = arg, sc_env = arg_se -- It's wrong to err in either direction -- But fun_ty is an OutType, so is fully substituted - ; if | Just env' <- preInlineUnconditionally env NotTopLevel bndr arg arg_se + ; if | Just env' <- let res = preInlineUnconditionally env NotTopLevel bndr arg arg_se + in pprTrace "simpl_lam" (ppr arg $$ ppr (isJust res)) res , not (needsCaseBindingL arg_levity arg) , not ( isSimplified dup && not (exprIsTrivial arg) && @@ -1838,7 +1840,8 @@ simpl_lam env bndr body (ApplyToVal { sc_arg = arg, sc_env = arg_se tick (PreInlineUnconditionally bndr) ; simplLam env' body cont } - | isSimplified dup -- Don't re-simplify if we've simplified it once + | pprTrace "simpl_lam2" (ppr arg) $ + isSimplified dup -- Don't re-simplify if we've simplified it once -- Including don't preInlineUnconditionally -- See Note [Avoiding simplifying repeatedly] -> completeBindX env from_what bndr arg body cont @@ -2452,8 +2455,11 @@ rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) | null rules = rebuild env (argInfoExpr fun rev_args) cont | otherwise -- Try rules again - = do { let args = argInfoAppArgs rev_args - ; mb_match <- tryRules env rules run args + = do { let full_cont = pushSimplifiedRevArgs env rev_args cont + ; mb_match <- tryRules env rules fun full_cont + ; case mb_match of + Just (rhs, cont2) -> simplExprF env rhs cont2 + Nothing -> rebuild env (argInfoExpr fun rev_args) cont } ----------------------------------- tryInlining :: SimplEnv -> Logger -> OutId -> SimplCont -> SimplM (Maybe OutExpr) @@ -4030,7 +4036,7 @@ mkDupableStrictBind env arg_bndr join_rhs res_ty | otherwise = do { join_bndr <- newJoinId [arg_bndr] res_ty ; let arg_info = ArgInfo { ai_fun = join_bndr - , ai_rewrite = TryNothing, ai_args = [] + , ai_rules = [], ai_args = [] , ai_encl = False, ai_dmds = repeat topDmd , ai_discs = repeat 0 } ; return ( addJoinFloats (emptyFloats env) $ ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -284,7 +284,7 @@ instance Outputable SimplCont where = (text "ApplyToTy" <+> pprParendType ty) $$ ppr cont ppr (ApplyToVal { sc_arg = arg, sc_dup = dup, sc_cont = cont, sc_hole_ty = hole_ty, sc_env = env }) = (hang (text "ApplyToVal" <+> ppr dup <+> text "hole-ty:" <+> pprParendType hole_ty) - 2 (ppr (seIdSubst env) $$ pprParendExpr arg)) + 2 (pprParendExpr arg)) $$ ppr cont ppr (StrictBind { sc_bndr = b, sc_cont = cont }) = (text "StrictBind" <+> ppr b) $$ ppr cont View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b86769ca5f000aa4b7d9f79f6134defb3ef47dc5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b86769ca5f000aa4b7d9f79f6134defb3ef47dc5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/4dede05a/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 18:13:25 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 12 Mar 2025 14:13:25 -0400 Subject: [Git][ghc/ghc][wip/T25647] 93 commits: We can't UNPACK multi-constructor GADTs Message-ID: <67d1cec580ac4_2792128eba98447e9@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 1a388aa3 by Simon Peyton Jones at 2025-03-12T18:13:19+00:00 WIP towards #25267 - - - - - 18c38e00 by Simon Peyton Jones at 2025-03-12T18:13:19+00:00 Wibbles - - - - - 7cff62c4 by Simon Peyton Jones at 2025-03-12T18:13:19+00:00 Default tyvars in data/newtype insnstances This is what fixes #25647 - - - - - a259fffa by Simon Peyton Jones at 2025-03-12T18:13:19+00:00 wibbles Including fix for #25725 - - - - - a0f9b55d by Simon Peyton Jones at 2025-03-12T18:13:19+00:00 Wibble - - - - - 6aa36f4d by Patrick at 2025-03-12T18:13:19+00:00 add more tests - - - - - e11c10d2 by Patrick at 2025-03-12T18:13:19+00:00 Fix up T25611d with explicit kind annotation - - - - - f7cba233 by Patrick at 2025-03-12T18:13:19+00:00 fix up T25647_fail - - - - - 87c78c2c by Patrick at 2025-03-12T18:13:19+00:00 cleanup whitespace - - - - - a370480b by Patrick at 2025-03-12T18:13:19+00:00 fix up T23512a - - - - - 5d80f02e by Patrick at 2025-03-12T18:13:19+00:00 add more examples to T25647b - - - - - 6cc88c6d by Patrick at 2025-03-12T18:13:19+00:00 add Dix6 to T25647_fail - - - - - 0fc151c1 by Patrick at 2025-03-12T18:13:19+00:00 add Dix7 for T25647a - - - - - 7ce260f7 by Patrick at 2025-03-12T18:13:19+00:00 change DefaultingStrategy of tcTyFamInstEqnGuts as well - - - - - 8f74eaa5 by Patrick at 2025-03-12T18:13:19+00:00 align wildcard with named typevar on wether it is skolem - - - - - 71ca02f9 by Patrick at 2025-03-12T18:13:19+00:00 fix T17536c - - - - - cd3b902e by Patrick at 2025-03-12T18:13:19+00:00 Fix T9357 - - - - - 91d84010 by Patrick at 2025-03-12T18:13:19+00:00 remove wildcard usage - - - - - bc5abed3 by Patrick at 2025-03-12T18:13:19+00:00 Revert "align wildcard with named typevar on wether it is skolem" This reverts commit d1f61858328cc190de9b34c9a24e8d6b28ee5fa9. - - - - - b9008121 by Patrick at 2025-03-12T18:13:19+00:00 add WildCardTv to forbid wildcard from defaulting - - - - - c685430c by Patrick at 2025-03-12T18:13:19+00:00 Fix wildcard related tests - - - - - 2e31b0c6 by Patrick at 2025-03-12T18:13:19+00:00 add wildcards testcase for T25647a - - - - - e4b7538e by Patrick at 2025-03-12T18:13:19+00:00 Fix T25647a - - - - - b967ea8c by Patrick at 2025-03-12T18:13:19+00:00 Revert "Fix wildcard related tests" This reverts commit 8756ab87f4e3d74968d3937f84f811f78a861852. - - - - - 6d2a5b26 by Patrick at 2025-03-12T18:13:19+00:00 limit WildCardTv to only HM_FamPat - - - - - 7b89f733 by Patrick at 2025-03-12T18:13:19+00:00 fix - - - - - 00fe5f3a by Patrick at 2025-03-12T18:13:19+00:00 Revert "remove wildcard usage" This reverts commit ccc9152f23177ab7a542852ffedf626edcdcef95. - - - - - 85491f9f by Patrick at 2025-03-12T18:13:19+00:00 rename WildCardTv to NoDefTauTv - - - - - b5eb1433 by Patrick at 2025-03-12T18:13:19+00:00 update note - - - - - d21ed79f by Patrick at 2025-03-12T18:13:19+00:00 rename isWildCardMetaTyVar to isNoDefTauMetaTyVar and fix defaultTyVarTcS - - - - - 5d747c7e by Patrick at 2025-03-12T18:13:19+00:00 fix comment - - - - - 687360ca by Patrick at 2025-03-12T18:13:19+00:00 format - - - - - 0330db9d by Patrick at 2025-03-12T18:13:19+00:00 remove NonStandardDefaultingStrategy and update Note [NoDefTauTv] - - - - - a969a09e by Patrick at 2025-03-12T18:13:19+00:00 add DixC10 to T25647a - - - - - d699ddd7 by Patrick at 2025-03-12T18:13:19+00:00 use TyVarTv for wildcard in HM_FamPat - - - - - 1a080142 by Patrick at 2025-03-12T18:13:19+00:00 Revert "use TyVarTv for wildcard in HM_FamPat" This reverts commit 638d6763d0b972f3c9a0e2c4218d8c7ce34dc800. - - - - - 3818f0fe by Patrick at 2025-03-12T18:13:19+00:00 Add FamArgType to in AssocInstInfo to guide the create of tv for wildcard - - - - - 005a18d6 by Patrick at 2025-03-12T18:13:19+00:00 Fix mode args passing down - - - - - 2f0f03c2 by Patrick at 2025-03-12T18:13:19+00:00 Fix under application for data fam - - - - - b72bb167 by Patrick at 2025-03-12T18:13:19+00:00 use HM_Sig for (a :: _) in type family - - - - - d1add315 by Patrick at 2025-03-12T18:13:19+00:00 add and use HM_FamSig for (a :: _) in type family - - - - - 0cb0d60b by Patrick at 2025-03-12T18:13:19+00:00 use TyVarTv instead of SkolemTv for freeArg `_`, since we also do not default TyVarTv in defaultTyVar and defaultTyVarTcS - - - - - 0e0a3220 by Patrick at 2025-03-12T18:13:19+00:00 Revert "add and use HM_FamSig for (a :: _) in type family" and use ClassArg for _ in (a :: _) in type family This reverts commit 9ab780da39c2afbce2411c2b96fef4108d6b8b70. - - - - - e71a52cb by Patrick at 2025-03-12T18:13:19+00:00 fix - - - - - 2ca7ff8b by Patrick at 2025-03-12T18:13:19+00:00 remove unused updateHoleMode function from TcTyMode - - - - - dadd2e01 by Patrick at 2025-03-12T18:13:19+00:00 flip the classVar to TyVarTv to observe any breakage - - - - - 64a2098e by Patrick at 2025-03-12T18:13:19+00:00 fix - - - - - ea1f3b87 by Patrick at 2025-03-12T18:13:19+00:00 disable DixC10 from T25647a - - - - - ef110541 by Patrick at 2025-03-12T18:13:19+00:00 update ExplicitForAllFams4b - - - - - 43a2c5ee by Patrick at 2025-03-12T18:13:19+00:00 cleanup NoDefTauTv - - - - - d304aa90 by Patrick at 2025-03-12T18:13:19+00:00 move [FamArgFlavour] to tyCon - - - - - 5700dda5 by Patrick at 2025-03-12T18:13:19+00:00 add note - - - - - c97aba56 by Patrick at 2025-03-12T18:13:19+00:00 refactor documentation for FamArgFlavour and clean up comments - - - - - 8567b3b9 by Patrick at 2025-03-12T18:13:19+00:00 enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging - - - - - bc42743d by Patrick at 2025-03-12T18:13:19+00:00 Ensure wildcard behave correctly - - - - - 3082f8e3 by Patrick at 2025-03-12T18:13:19+00:00 Revert "update ExplicitForAllFams4b" This reverts commit 90a2858278668bc6ad66ef43a5651808d8f24a0f. - - - - - 657e2cb8 by Patrick at 2025-03-12T18:13:19+00:00 Add detailed notes on wildcard handling in type families and refine related documentation - - - - - 43b8a26c by Patrick at 2025-03-12T18:13:19+00:00 Refine documentation on wildcard handling in type families and clarify design choices for FamArgFlavour - - - - - 97c0fc9c by Patrick at 2025-03-12T18:13:19+00:00 Fix typos in documentation regarding wildcards in type families and clarify references - - - - - 9dd00d82 by Patrick at 2025-03-12T18:13:19+00:00 Clarify wildcard handling in type families documentation and improve explanations for FamArgFlavour - - - - - 6109b368 by Patrick at 2025-03-12T18:13:19+00:00 Enhance documentation on FamArgFlavour handling in type families and clarify implementation details in TyCon and HsType modules - - - - - 3846ea1e by Patrick at 2025-03-12T18:13:19+00:00 format - - - - - 2c0049d3 by Patrick at 2025-03-12T18:13:19+00:00 Refactor documentation on wildcards in type families and clarify implementation details in TyCon, Rename, and HsType modules - - - - - 0c40cdc7 by Patrick at 2025-03-12T18:13:19+00:00 Rename variable `famArgFlvs` to `fam_arg_flvs` for consistency in type inference functions - - - - - e5790c0a by Patrick at 2025-03-12T18:13:19+00:00 Improve documentation on wildcard interpretation in type families, clarifying the relationship with class arguments and enhancing the explanation of FamArgFlavour categories. - - - - - 1047047e by Patrick at 2025-03-12T18:13:19+00:00 Add comment to clarify implementation details for wildcards in family instances - - - - - e1669f68 by Patrick at 2025-03-12T18:13:19+00:00 Refactor HsOuterTyVarBndrs to include implicit variable bindings and update related functions for consistency - - - - - a7b21545 by Patrick at 2025-03-12T18:13:19+00:00 Enhance HsOuterTyVarBndrs to support implicit variable bindings and update related functions for consistency - - - - - ea505683 by Patrick at 2025-03-12T18:13:19+00:00 Add new test case T25647d - - - - - 3820368b by Patrick at 2025-03-12T18:13:19+00:00 Remove unused implicit variable bindings from HsOuterExplicit in addHsOuterSigTyVarBinds function - - - - - 23efde26 by Patrick at 2025-03-12T18:13:19+00:00 Add forall quantifiers to MultMul type family for clarity - - - - - 74a54653 by Patrick at 2025-03-12T18:13:19+00:00 Refactor bindHsOuterTyVarBndrs' - - - - - 84207ab1 by Patrick at 2025-03-12T18:13:19+00:00 Add empty implicit variable bindings to HsOuterExplicit in mkEmptySigType - - - - - 844484cd by Patrick at 2025-03-12T18:13:19+00:00 Add empty implicit variable bindings to HsOuterExplicit in synifyDataCon - - - - - 5afa406f by Patrick at 2025-03-12T18:13:19+00:00 Add missing implicit variable bindings to HsOuterExplicit in ExactPrint instance - - - - - 6c2835e8 by Patrick at 2025-03-12T18:13:19+00:00 Add implicit variable bindings to HsOuterExplicit in various instances - - - - - 2b037a4d by Patrick at 2025-03-12T18:13:19+00:00 Add forall quantifier to D Int newtype instance - - - - - 330151a1 by Patrick at 2025-03-12T18:13:19+00:00 zonk_quant outer binders for families - - - - - 1f4d5454 by Patrick at 2025-03-12T18:13:19+00:00 revert to old behaviour - - - - - 39077466 by Patrick at 2025-03-12T18:13:19+00:00 add note and comment - - - - - 170a5d89 by Patrick at 2025-03-12T18:13:19+00:00 refactor - - - - - 9a749c3e by Patrick at 2025-03-12T18:13:19+00:00 fix test T25647d - - - - - 07316009 by Patrick at 2025-03-12T18:13:19+00:00 handle [Naughty quantification candidates] - - - - - 0f2dae68 by Patrick at 2025-03-12T18:13:19+00:00 handle explicit implicit binders seperately - - - - - 687ab1ef by Patrick at 2025-03-12T18:13:19+00:00 handle explicit implicit binders seperately fix - - - - - 475c3026 by Patrick at 2025-03-12T18:13:19+00:00 fix lint - - - - - af9ae387 by Patrick at 2025-03-12T18:13:19+00:00 some renaming - - - - - 566edcef by Patrick at 2025-03-12T18:13:19+00:00 update tests to reflect changes in error messages - - - - - 50 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Core/DataCon.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Types/LclEnv.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Id/Make.hs - compiler/Language/Haskell/Syntax/Decls.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - rts/HeapStackCheck.cmm - rts/PrimOps.cmm - + testsuite/tests/indexed-types/should_compile/T11450a.hs - testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/SimpleFail2a.hs - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.hs - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T14230a.hs - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T14246.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/rename/should_fail/T23512a.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/typecheck/should_compile/T25647_fail.hs - + testsuite/tests/typecheck/should_compile/T25647_fail.stderr - + testsuite/tests/typecheck/should_compile/T25647a.hs - + testsuite/tests/typecheck/should_compile/T25647b.hs - + testsuite/tests/typecheck/should_compile/T25647c.hs - + testsuite/tests/typecheck/should_compile/T25647d.hs - + testsuite/tests/typecheck/should_compile/T25647d_fail.hs - + testsuite/tests/typecheck/should_compile/T25647d_fail.stderr - + testsuite/tests/typecheck/should_compile/T25725.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T18640b.stderr - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a3b1fedd205356f9e8006148c1c62b0f49927a38...566edcef30a738576b1f71cbceca405a0d681681 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a3b1fedd205356f9e8006148c1c62b0f49927a38...566edcef30a738576b1f71cbceca405a0d681681 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/91b8a865/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 20:52:10 2025 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Wed, 12 Mar 2025 16:52:10 -0400 Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] undo ticks changes for hpc Message-ID: <67d1f3fa33fb2_2c25fe90d7b07552@gitlab.mail> Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: a1a228ce by Apoorv Ingle at 2025-03-12T15:50:12-05:00 undo ticks changes for hpc - - - - - 2 changed files: - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Tc/Gen/App.hs Changes: ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -586,8 +586,7 @@ addTickHsExpr (HsProc x pat cmdtop) = addTickHsExpr (XExpr (WrapExpr w e)) = liftM (XExpr . WrapExpr w) $ (addTickHsExpr e) -- Explicitly no tick on inside -addTickHsExpr (XExpr (ExpandedThingTc o e)) = - liftM (XExpr . ExpandedThingTc o) $ addTickHsExpr e +addTickHsExpr (XExpr (ExpandedThingTc o e)) = addTickHsExpanded o e addTickHsExpr e@(XExpr (ConLikeTc {})) = return e -- We used to do a freeVar on a pat-syn builder, but actually @@ -606,10 +605,25 @@ addTickHsExpr (HsDo srcloc cxt (L l stmts)) = do { (stmts', _) <- addTickLStmts' forQual stmts (return ()) ; return (HsDo srcloc cxt (L l stmts')) } where - forQual = case cxt of + forQual = case cxt of ListComp -> Just $ BinBox QualBinBox _ -> Nothing +addTickHsExpanded :: HsThingRn -> HsExpr GhcTc -> TM (HsExpr GhcTc) +addTickHsExpanded o@(OrigStmt (L pos LastStmt{}) _) e + -- LastStmt always gets a tick for breakpoint and hpc coverage + = do d <- getDensity + case d of + TickForCoverage -> liftM (XExpr . ExpandedThingTc o) $ tick_it e + TickForBreakPoints -> liftM (XExpr . ExpandedThingTc o) $ tick_it e + _ -> liftM (XExpr . ExpandedThingTc o) $ addTickHsExpr e + where + tick_it e = unLoc <$> allocTickBox (ExpBox False) False False (locA pos) + (addTickHsExpr e) +addTickHsExpanded o e + = liftM (XExpr . ExpandedThingTc o) $ addTickHsExpr e + + addTickTupArg :: HsTupArg GhcTc -> TM (HsTupArg GhcTc) addTickTupArg (Present x e) = do { e' <- addTickLHsExpr e ; return (Present x e') } ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -876,7 +876,7 @@ looks_like_type_arg _ = False addArgCtxt :: AppCtxt -> LHsExpr GhcRn -> TcM a -> TcM a --- There are 3 cases: +-- There are 2 cases: -- 1. In the normal case, we add an informative context -- "In the third argument of f, namely blah" -- 2. If we are deep inside generated code (`isGeneratedCode` is `True`) @@ -885,9 +885,6 @@ addArgCtxt :: AppCtxt -> LHsExpr GhcRn -- "In the expression: arg" -- Unless the arg is also a generated thing, in which case do nothing. -- See Note [Rebindable syntax and XXExprGhcRn] in GHC.Hs.Expr --- 3. We are in an expanded `do`-block statement --- Do nothing as we have already added the error --- context in GHC.Tc.Do.tcXExpr -- See Note [Expanding HsDo with XXExprGhcRn] in GHC.Tc.Gen.Do addArgCtxt ctxt (L arg_loc arg) thing_inside = do { in_generated_code <- inGeneratedCode View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1a228ce32b7f8f37ec4dba6fee899d3e78ec715 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1a228ce32b7f8f37ec4dba6fee899d3e78ec715 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/0e88eed7/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 23:44:08 2025 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Wed, 12 Mar 2025 19:44:08 -0400 Subject: [Git][ghc/ghc][wip/haddocks-for-ghc-warnings] Improve haddock-visible documentation for GHC.Driver.Flags Message-ID: <67d21c48552a7_31c2843267d4878aa@gitlab.mail> Bodigrim pushed to branch wip/haddocks-for-ghc-warnings at Glasgow Haskell Compiler / GHC Commits: 60bafd21 by Andrew Lelechenko at 2025-03-12T23:43:55+00:00 Improve haddock-visible documentation for GHC.Driver.Flags - - - - - 1 changed file: - compiler/GHC/Driver/Flags.hs Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -360,7 +360,7 @@ validHoleFitsImpliedGFlags , (Opt_ShowTypeAppVarsOfHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits) , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowProvOfHoleFits) ] --- General flags that are switched on/off when other general flags are switched +-- | General flags that are switched on/off when other general flags are switched -- on impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)] impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles) @@ -373,12 +373,12 @@ impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles) ,(Opt_InfoTableMap, turnOn, Opt_InfoTableMapWithFallback) ] ++ validHoleFitsImpliedGFlags --- General flags that are switched on/off when other general flags are switched +-- | General flags that are switched on/off when other general flags are switched -- off impliedOffGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)] impliedOffGFlags = [(Opt_Strictness, turnOff, Opt_WorkerWrapper)] --- Please keep what_glasgow_exts_does.rst up to date with this list +-- | Please keep @docs/users_guide/what_glasgow_exts_does.rst@ up to date with this list. glasgowExtsFlags :: [LangExt.Extension] glasgowExtsFlags = [ LangExt.ConstrainedClassMethods @@ -426,7 +426,7 @@ data DumpFlag -- enabled if you run -ddump-cmm-verbose-by-proc -- Each flag corresponds to exact stage of Cmm pipeline. | Opt_D_dump_cmm_verbose - -- same as -ddump-cmm-verbose-by-proc but writes each stage + -- ^ same as -ddump-cmm-verbose-by-proc but writes each stage -- to a separate file (if used with -ddump-to-file) | Opt_D_dump_cmm_cfg | Opt_D_dump_cmm_cbe @@ -500,9 +500,9 @@ data DumpFlag | Opt_D_dump_rn_stats | Opt_D_dump_opt_cmm | Opt_D_dump_simpl_stats - | Opt_D_dump_cs_trace -- Constraint solver in type checker + | Opt_D_dump_cs_trace -- ^ Constraint solver in type checker | Opt_D_dump_tc_trace - | Opt_D_dump_ec_trace -- Pattern match exhaustiveness checker + | Opt_D_dump_ec_trace -- ^ Pattern match exhaustiveness checker | Opt_D_dump_if_trace | Opt_D_dump_splices | Opt_D_th_dec_file @@ -591,9 +591,13 @@ data GeneralFlag | Opt_InfoTableMapWithFallback | Opt_InfoTableMapWithStack - | Opt_WarnIsError -- -Werror; makes warnings fatal - | Opt_ShowWarnGroups -- Show the group a warning belongs to - | Opt_HideSourcePaths -- Hide module source/object paths + | Opt_WarnIsError + -- ^ @-Werror@; makes all warnings fatal. + -- See 'wopt_set_fatal' for making individual warnings fatal as in @-Werror=foo at . + | Opt_ShowWarnGroups + -- ^ Show the group a warning belongs to. + | Opt_HideSourcePaths + -- ^ @-fhide-source-paths@; hide module source/object paths. | Opt_PrintExplicitForalls | Opt_PrintExplicitKinds @@ -641,15 +645,15 @@ data GeneralFlag | Opt_IgnoreAsserts | Opt_DoEtaReduction | Opt_CaseMerge - | Opt_CaseFolding -- Constant folding through case-expressions + | Opt_CaseFolding -- ^ Constant folding through case-expressions | Opt_UnboxStrictFields | Opt_UnboxSmallStrictFields | Opt_DictsCheap - | Opt_EnableRewriteRules -- Apply rewrite rules during simplification - | Opt_EnableThSpliceWarnings -- Enable warnings for TH splices - | Opt_RegsGraph -- do graph coloring register allocation - | Opt_RegsIterative -- do iterative coalescing graph coloring register allocation - | Opt_PedanticBottoms -- Be picky about how we treat bottom + | Opt_EnableRewriteRules -- ^ Apply rewrite rules during simplification + | Opt_EnableThSpliceWarnings -- ^ Enable warnings for TH splices + | Opt_RegsGraph -- ^ Do graph coloring register allocation + | Opt_RegsIterative -- ^ Do iterative coalescing graph coloring register allocation + | Opt_PedanticBottoms -- ^ Be picky about how we treat bottom | Opt_LlvmFillUndefWithGarbage -- Testing for undef bugs (hidden flag) | Opt_IrrefutableTuples | Opt_CmmSink @@ -658,13 +662,13 @@ data GeneralFlag | Opt_CmmControlFlow | Opt_AsmShortcutting | Opt_OmitYields - | Opt_FunToThunk -- deprecated - | Opt_DictsStrict -- be strict in argument dictionaries + | Opt_FunToThunk -- deprecated + | Opt_DictsStrict -- ^ Be strict in argument dictionaries | Opt_DmdTxDictSel -- ^ deprecated, no effect and behaviour is now default. -- Allowed switching of a special demand transformer for dictionary selectors - | Opt_Loopification -- See Note [Self-recursive tail calls] - | Opt_CfgBlocklayout -- ^ Use the cfg based block layout algorithm. - | Opt_WeightlessBlocklayout -- ^ Layout based on last instruction per block. + | Opt_Loopification -- See Note [Self-recursive tail calls] + | Opt_CfgBlocklayout -- ^ Use the cfg based block layout algorithm. + | Opt_WeightlessBlocklayout -- ^ Layout based on last instruction per block. | Opt_CprAnal | Opt_WorkerWrapper | Opt_WorkerWrapperUnlift -- ^ Do W/W split for unlifting even if we won't unbox anything. @@ -681,7 +685,7 @@ data GeneralFlag -- Inference flags | Opt_DoTagInferenceChecks - -- PreInlining is on by default. The option is there just to see how + -- | PreInlining is on by default. The option is there just to see how -- bad things get if you turn it off! | Opt_SimplPreInlining @@ -690,15 +694,15 @@ data GeneralFlag | Opt_OmitInterfacePragmas | Opt_ExposeAllUnfoldings | Opt_ExposeOverloadedUnfoldings - | Opt_KeepAutoRules -- ^Keep auto-generated rules even if they seem to have become useless - | Opt_WriteInterface -- forces .hi files to be written even with -fno-code + | Opt_KeepAutoRules -- ^ Keep auto-generated rules even if they seem to have become useless + | Opt_WriteInterface -- ^ Forces .hi files to be written even with -fno-code | Opt_WriteSelfRecompInfo | Opt_WriteSelfRecompFlags -- ^ Include detailed flag information for self-recompilation debugging - | Opt_WriteHie -- generate .hie files + | Opt_WriteHie -- ^ Generate .hie files -- JavaScript opts - | Opt_DisableJsMinifier -- ^ render JavaScript pretty-printed instead of minified (compacted) - | Opt_DisableJsCsources -- ^ don't link C sources (compiled to JS) with Haskell code (compiled to JS) + | Opt_DisableJsMinifier -- ^ Render JavaScript pretty-printed instead of minified (compacted) + | Opt_DisableJsCsources -- ^ Don't link C sources (compiled to JS) with Haskell code (compiled to JS) -- profiling opts | Opt_AutoSccsOnIndividualCafs @@ -781,11 +785,11 @@ data GeneralFlag | Opt_LinkRts -- output style opts - | Opt_ErrorSpans -- Include full span info in error messages, + | Opt_ErrorSpans -- ^ Include full span info in error messages, -- instead of just the start position. | Opt_DeferDiagnostics | Opt_DiagnosticsAsJSON -- ^ Dump diagnostics as JSON - | Opt_DiagnosticsShowCaret -- Show snippets of offending code + | Opt_DiagnosticsShowCaret -- ^ Show snippets of offending code | Opt_PprCaseAsLet | Opt_PprShowTicks | Opt_ShowHoleConstraints @@ -808,29 +812,29 @@ data GeneralFlag | Opt_ShowLoadedModules | Opt_HexWordLiterals -- See Note [Print Hexadecimal Literals] - -- Suppress a coercions inner structure, replacing it with '...' + -- | Suppress a coercions inner structure, replacing it with '...' | Opt_SuppressCoercions - -- Suppress the type of a coercion as well + -- | Suppress the type of a coercion as well | Opt_SuppressCoercionTypes | Opt_SuppressVarKinds - -- Suppress module id prefixes on variables. + -- | Suppress module id prefixes on variables. | Opt_SuppressModulePrefixes - -- Suppress type applications. + -- | Suppress type applications. | Opt_SuppressTypeApplications - -- Suppress info such as arity and unfoldings on identifiers. + -- | Suppress info such as arity and unfoldings on identifiers. | Opt_SuppressIdInfo - -- Suppress separate type signatures in core, but leave types on + -- | Suppress separate type signatures in core, but leave types on -- lambda bound vars | Opt_SuppressUnfoldings - -- Suppress the details of even stable unfoldings + -- | Suppress the details of even stable unfoldings | Opt_SuppressTypeSignatures - -- Suppress unique ids on variables. + -- | Suppress unique ids on variables. -- Except for uniques, as some simplifier phases introduce new -- variables that have otherwise identical names. | Opt_SuppressUniques | Opt_SuppressStgExts | Opt_SuppressStgReps - | Opt_SuppressTicks -- Replaces Opt_PprShowTicks + | Opt_SuppressTicks -- ^ Replaces Opt_PprShowTicks | Opt_SuppressTimestamps -- ^ Suppress timestamps in dumps | Opt_SuppressCoreSizes -- ^ Suppress per binding Core size stats in dumps @@ -1030,54 +1034,54 @@ data WarningFlag = | Opt_WarnDerivingTypeable | Opt_WarnDeferredTypeErrors | Opt_WarnDeferredOutOfScopeVariables - | Opt_WarnNonCanonicalMonadInstances -- since 8.0 - | Opt_WarnNonCanonicalMonadFailInstances -- since 8.0, removed 8.8 - | Opt_WarnNonCanonicalMonoidInstances -- since 8.0 - | Opt_WarnMissingPatternSynonymSignatures -- since 8.0 - | Opt_WarnUnrecognisedWarningFlags -- since 8.0 - | Opt_WarnSimplifiableClassConstraints -- Since 8.2 - | Opt_WarnCPPUndef -- Since 8.2 - | Opt_WarnUnbangedStrictPatterns -- Since 8.2 - | Opt_WarnMissingHomeModules -- Since 8.2 - | Opt_WarnPartialFields -- Since 8.4 + | Opt_WarnNonCanonicalMonadInstances -- ^ @since 8.0 + | Opt_WarnNonCanonicalMonadFailInstances -- ^ @since 8.0, has no effect since 8.8 + | Opt_WarnNonCanonicalMonoidInstances -- ^ @since 8.0 + | Opt_WarnMissingPatternSynonymSignatures -- ^ @since 8.0 + | Opt_WarnUnrecognisedWarningFlags -- ^ @since 8.0 + | Opt_WarnSimplifiableClassConstraints -- ^ @since 8.2 + | Opt_WarnCPPUndef -- ^ @since 8.2 + | Opt_WarnUnbangedStrictPatterns -- ^ @since 8.2 + | Opt_WarnMissingHomeModules -- ^ @since 8.2 + | Opt_WarnPartialFields -- ^ @since 8.4 | Opt_WarnMissingExportList | Opt_WarnInaccessibleCode - | Opt_WarnStarIsType -- Since 8.6 - | Opt_WarnStarBinder -- Since 8.6 - | Opt_WarnImplicitKindVars -- Since 8.6 + | Opt_WarnStarIsType -- ^ @since 8.6 + | Opt_WarnStarBinder -- ^ @since 8.6 + | Opt_WarnImplicitKindVars -- ^ @since 8.6 | Opt_WarnSpaceAfterBang - | Opt_WarnMissingDerivingStrategies -- Since 8.8 - | Opt_WarnPrepositiveQualifiedModule -- Since 8.10 - | Opt_WarnUnusedPackages -- Since 8.10 - | Opt_WarnInferredSafeImports -- Since 8.10 - | Opt_WarnMissingSafeHaskellMode -- Since 8.10 - | Opt_WarnCompatUnqualifiedImports -- Since 8.10 + | Opt_WarnMissingDerivingStrategies -- ^ @since 8.8 + | Opt_WarnPrepositiveQualifiedModule -- ^ @since 8.10 + | Opt_WarnUnusedPackages -- ^ @since 8.10 + | Opt_WarnInferredSafeImports -- ^ @since 8.10 + | Opt_WarnMissingSafeHaskellMode -- ^ @since 8.10 + | Opt_WarnCompatUnqualifiedImports -- ^ @since 8.10 | Opt_WarnDerivingDefaults - | Opt_WarnInvalidHaddock -- Since 9.0 - | Opt_WarnOperatorWhitespaceExtConflict -- Since 9.2 - | Opt_WarnOperatorWhitespace -- Since 9.2 - | Opt_WarnAmbiguousFields -- Since 9.2 - | Opt_WarnImplicitLift -- Since 9.2 - | Opt_WarnMissingKindSignatures -- Since 9.2 - | Opt_WarnMissingPolyKindSignatures -- Since 9.8 - | Opt_WarnMissingExportedPatternSynonymSignatures -- since 9.2 - | Opt_WarnRedundantStrictnessFlags -- Since 9.4 - | Opt_WarnForallIdentifier -- Since 9.4 - | Opt_WarnUnicodeBidirectionalFormatCharacters -- Since 9.0.2 - | Opt_WarnGADTMonoLocalBinds -- Since 9.4 - | Opt_WarnTypeEqualityOutOfScope -- Since 9.4 - | Opt_WarnTypeEqualityRequiresOperators -- Since 9.4 - | Opt_WarnLoopySuperclassSolve -- Since 9.6, has no effect since 9.10 - | Opt_WarnTermVariableCapture -- Since 9.8 - | Opt_WarnMissingRoleAnnotations -- Since 9.8 - | Opt_WarnImplicitRhsQuantification -- Since 9.8 - | Opt_WarnIncompleteExportWarnings -- Since 9.8 - | Opt_WarnIncompleteRecordSelectors -- Since 9.10 - | Opt_WarnBadlyStagedTypes -- Since 9.10 - | Opt_WarnInconsistentFlags -- Since 9.8 - | Opt_WarnDataKindsTC -- Since 9.10 - | Opt_WarnDefaultedExceptionContext -- Since 9.10 - | Opt_WarnViewPatternSignatures -- Since 9.12 + | Opt_WarnInvalidHaddock -- ^ @since 9.0 + | Opt_WarnOperatorWhitespaceExtConflict -- ^ @since 9.2 + | Opt_WarnOperatorWhitespace -- ^ @since 9.2 + | Opt_WarnAmbiguousFields -- ^ @since 9.2 + | Opt_WarnImplicitLift -- ^ @since 9.2 + | Opt_WarnMissingKindSignatures -- ^ @since 9.2 + | Opt_WarnMissingPolyKindSignatures -- ^ @since 9.8 + | Opt_WarnMissingExportedPatternSynonymSignatures -- ^ @since 9.2 + | Opt_WarnRedundantStrictnessFlags -- ^ @since 9.4 + | Opt_WarnForallIdentifier -- ^ @since 9.4 + | Opt_WarnUnicodeBidirectionalFormatCharacters -- ^ @since 9.0.2 + | Opt_WarnGADTMonoLocalBinds -- ^ @since 9.4 + | Opt_WarnTypeEqualityOutOfScope -- ^ @since 9.4 + | Opt_WarnTypeEqualityRequiresOperators -- ^ @since 9.4 + | Opt_WarnLoopySuperclassSolve -- ^ @since 9.6, has no effect since 9.10 + | Opt_WarnTermVariableCapture -- ^ @since 9.8 + | Opt_WarnMissingRoleAnnotations -- ^ @since 9.8 + | Opt_WarnImplicitRhsQuantification -- ^ @since 9.8 + | Opt_WarnIncompleteExportWarnings -- ^ @since 9.8 + | Opt_WarnIncompleteRecordSelectors -- ^ @since 9.10 + | Opt_WarnBadlyStagedTypes -- ^ @since 9.10 + | Opt_WarnInconsistentFlags -- ^ @since 9.8 + | Opt_WarnDataKindsTC -- ^ @since 9.10 + | Opt_WarnDefaultedExceptionContext -- ^ @since 9.10 + | Opt_WarnViewPatternSignatures -- ^ @since 9.12 deriving (Eq, Ord, Show, Enum, Bounded) -- | Return the names of a WarningFlag @@ -1253,7 +1257,7 @@ warningGroupIncludesExtendedWarnings W_everything = True -- | Warning groups. -- --- As all warnings are in the Weverything set, it is ignored when +-- As all warnings are in the 'W_everything' set, it is ignored when -- displaying to the user which group a warning is in. warningGroups :: [WarningGroup] warningGroups = [minBound..maxBound] @@ -1268,7 +1272,7 @@ warningGroups = [minBound..maxBound] -- Separating this from 'warningGroups' allows for multiple -- hierarchies with no inherent relation to be defined. -- --- The special-case Weverything group is not included. +-- The special-case 'W_everything' group is not included. warningHierarchies :: [[WarningGroup]] warningHierarchies = hierarchies ++ map (:[]) rest where @@ -1338,7 +1342,7 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnViewPatternSignatures ] --- | Things you get with -W +-- | Things you get with @-W at . minusWOpts :: [WarningFlag] minusWOpts = standardWarnings ++ @@ -1354,7 +1358,7 @@ minusWOpts Opt_WarnUnbangedStrictPatterns ] --- | Things you get with -Wall +-- | Things you get with @-Wall at . minusWallOpts :: [WarningFlag] minusWallOpts = minusWOpts ++ @@ -1375,11 +1379,11 @@ minusWallOpts Opt_WarnDerivingTypeable ] --- | Things you get with -Weverything, i.e. *all* known warnings flags +-- | Things you get with @-Weverything@, i.e. *all* known warnings flags. minusWeverythingOpts :: [WarningFlag] minusWeverythingOpts = [ toEnum 0 .. ] --- | Things you get with -Wcompat. +-- | Things you get with @-Wcompat at . -- -- This is intended to group together warnings that will be enabled by default -- at some point in the future, so that library authors eager to make their @@ -1389,7 +1393,7 @@ minusWcompatOpts = [ Opt_WarnImplicitRhsQuantification ] --- | Things you get with -Wunused-binds +-- | Things you get with @-Wunused-binds at . unusedBindsFlags :: [WarningFlag] unusedBindsFlags = [ Opt_WarnUnusedTopBinds , Opt_WarnUnusedLocalBinds View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60bafd219638de2dec49c1342d50672542af8d62 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60bafd219638de2dec49c1342d50672542af8d62 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/f09624d7/attachment-0001.html> From gitlab at gitlab.haskell.org Wed Mar 12 23:51:50 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Mar 2025 19:51:50 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] Work in progress [skip ci] Message-ID: <67d21e16307b4_31c28432732891830@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: 9f2f832c by Simon Peyton Jones at 2025-03-12T23:51:28+00:00 Work in progress [skip ci] - - - - - 2 changed files: - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Env.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Core.Opt.Simplify.Env ( seArityOpts, seCaseCase, seCaseFolding, seCaseMerge, seCastSwizzle, seDoEtaReduction, seEtaExpand, seFloatEnable, seInline, seNames, seOptCoercionOpts, sePhase, sePlatform, sePreInline, - seRuleOpts, seRules, seUnfoldingOpts, + seRuleOpts, seRules, seUnfoldingOpts, seHasEmptySubst, mkSimplEnv, extendIdSubst, extendCvIdSubst, extendTvSubst, extendCvSubst, zapSubstEnv, setSubstEnv, bumpCaseDepth, @@ -253,6 +253,10 @@ seRules env = sm_rules (seMode env) seUnfoldingOpts :: SimplEnv -> UnfoldingOpts seUnfoldingOpts env = sm_uf_opts (seMode env) +seHasEmptySubst :: SimplEnv -> Bool +seHasEmptySubst (SimplEnv { seIdSubst = id_env, seTvSubst = tv_env, seCvSubst = cv_env }) + = isEmptyVarEnv id_env && isEmptyVarEnv tv_env && isEmptyVarEnv cv_env + -- See Note [The environments of the Simplify pass] data SimplMode = SimplMode -- See comments in GHC.Core.Opt.Simplify.Monad { sm_phase :: !CompilerPhase ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -1520,15 +1520,22 @@ simplTick env tickish expr cont ************************************************************************ -} +type SimplEnvIS = SimplEnv +-- Invariant: the substition is empty + rebuild :: SimplEnv -> OutExpr -> SimplCont -> SimplM (SimplFloats, OutExpr) --- At this point the substitution in the SimplEnv should be irrelevant; --- only the in-scope set matters -rebuild env expr cont - = case cont of +-- At this point the substitution in the SimplEnv is empty. +-- Only the in-scope set matters, plus the flags +rebuild env expr cont = rebuild_go (zapSubstEnv env) expr cont + +rebuild_go :: SimplEnvIS -> OutExpr -> SimplCont -> SimplM (SimplFloats, OutExpr) +rebuild_go env expr cont + = assertPpr (seHasEmptySubst env) (ppr (getFullSubst env) $$ ppr expr) $ + case cont of Stop {} -> return (emptyFloats env, expr) - TickIt t cont -> rebuild env (mkTick t expr) cont + TickIt t cont -> rebuild_go env (mkTick t expr) cont CastIt { sc_co = co, sc_opt = opt, sc_cont = cont } - -> rebuild env (mkCast expr co') cont + -> rebuild_go env (mkCast expr co') cont -- NB: mkCast implements the (Coercion co |> g) optimisation where co' = optOutCoercion env co opt @@ -1544,13 +1551,13 @@ rebuild env expr cont -> completeBindX (se `setInScopeFromE` env) from_what b expr body cont ApplyToTy { sc_arg_ty = ty, sc_cont = cont} - -> rebuild env (App expr (Type ty)) cont + -> rebuild_go env (App expr (Type ty)) cont ApplyToVal { sc_arg = arg, sc_env = se, sc_dup = dup_flag , sc_cont = cont, sc_hole_ty = fun_ty } -- See Note [Avoid redundant simplification] -> do { (_, _, arg') <- simplLazyArg env dup_flag fun_ty Nothing se arg - ; rebuild env (App expr arg') cont } + ; rebuild_go env (App expr arg') cont } completeBindX :: SimplEnv -> FromWhat @@ -1748,7 +1755,8 @@ simplCast env body co0 cont0 -- See Note [Representation polymorphism invariants] in GHC.Core -- test: typecheck/should_run/EtaExpandLevPoly -simplLazyArg :: SimplEnv -> DupFlag +simplLazyArg :: SimplEnv -- ^ Used only for its InScopeSet + -> DupFlag -> OutType -- ^ Type of the function applied to this arg -> Maybe ArgInfo -- ^ Just <=> This arg `ai` occurs in an app -- `f a1 ... an` where we have ArgInfo on @@ -1829,7 +1837,10 @@ simpl_lam env bndr body (ApplyToVal { sc_arg = arg, sc_env = arg_se -- But fun_ty is an OutType, so is fully substituted ; if | Just env' <- let res = preInlineUnconditionally env NotTopLevel bndr arg arg_se - in pprTrace "simpl_lam" (ppr arg $$ ppr (isJust res)) res + in pprTrace "simpl_lam" + (vcat [ ppr bndr, ppr arg, ppr (seIdSubst arg_se) + , ppr (isJust res) ]) $ + res , not (needsCaseBindingL arg_levity arg) , not ( isSimplified dup && not (exprIsTrivial arg) && @@ -2323,7 +2334,8 @@ simplOutId env fun cont then tryRules zapped_env rules_for_me fun cont1 else return Nothing ; case mb_match of { - Just (rhs, cont2) -> simplExprF zapped_env rhs cont2 ; + Just (rhs, cont2) -> pprTrace "tryRules1" (ppr fun) $ + simplExprF zapped_env rhs cont2 ; Nothing -> do { logger <- getLogger @@ -2343,11 +2355,18 @@ simplOutId env fun cont --------------------------------------------------------- -- Dealing with a call site -rebuildCall :: SimplEnv -> ArgInfo -> SimplCont - -> SimplM (SimplFloats, OutExpr) +rebuildCall, rebuildCall_go :: SimplEnv -> ArgInfo -> SimplCont + -> SimplM (SimplFloats, OutExpr) +-- At this point the substitution in the SimplEnv is irrelevant; +-- it is usually empty, and regardless should be ignored. +-- Only the in-scope set matters, plus the seMode flags + +reubildCall env arg_info cont + = assertPpr (seHasEmptySubst env) (ppr (getFullSubst env) $$ ppr expr) $ + rebuildCall_go env arg_info cont ---------- Bottoming applications -------------- -rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_dmds = [] }) cont +rebuildCall_go env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_dmds = [] }) cont -- When we run out of strictness args, it means -- that the call is definitely bottom; see GHC.Core.Opt.Simplify.Utils.mkArgInfo -- Then we want to discard the entire strict continuation. E.g. @@ -2413,16 +2432,16 @@ rebuildCall env info@(ArgInfo { ai_fun = fun, ai_args = rev_args -} ---------- Simplify type applications and casts -------------- -rebuildCall env info (CastIt { sc_co = co, sc_opt = opt, sc_cont = cont }) +rebuildCall_go env info (CastIt { sc_co = co, sc_opt = opt, sc_cont = cont }) = rebuildCall env (addCastTo info co') cont where co' = optOutCoercion env co opt -rebuildCall env info (ApplyToTy { sc_arg_ty = arg_ty, sc_hole_ty = hole_ty, sc_cont = cont }) +rebuildCall-go env info (ApplyToTy { sc_arg_ty = arg_ty, sc_hole_ty = hole_ty, sc_cont = cont }) = rebuildCall env (addTyArgTo info arg_ty hole_ty) cont ---------- Simplify value arguments -------------------- -rebuildCall env fun_info +rebuildCall_go env fun_info (ApplyToVal { sc_arg = arg, sc_env = arg_se , sc_dup = dup_flag, sc_hole_ty = fun_ty , sc_cont = cont }) @@ -2451,14 +2470,15 @@ rebuildCall env fun_info ; rebuildCall env (addValArgTo fun_info arg' fun_ty) cont } ---------- No further useful info, revert to generic rebuild ------------ -rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) cont +rebuildCall_go env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) cont | null rules = rebuild env (argInfoExpr fun rev_args) cont | otherwise -- Try rules again = do { let full_cont = pushSimplifiedRevArgs env rev_args cont ; mb_match <- tryRules env rules fun full_cont ; case mb_match of - Just (rhs, cont2) -> simplExprF env rhs cont2 + Just (rhs, cont2) -> pprTrace "tryRules2" (ppr fun $$ ppr (seIdSubst env)) $ + simplExprF env rhs cont2 Nothing -> rebuild env (argInfoExpr fun rev_args) cont } ----------------------------------- @@ -2701,18 +2721,15 @@ tryRules env rules fn cont trySeqRules :: SimplEnv -> OutExpr -> InExpr -- Scrutinee and RHS -> SimplCont - -> SimplM (Maybe (SimplEnv, CoreExpr, SimplCont)) + -> SimplM (Maybe (CoreExpr, SimplCont)) -- See Note [User-defined RULES for seq] -- `in_env` applies to `rhs :: InExpr` but not to `scrut :: OutExpr` trySeqRules in_env scrut rhs cont = do { rule_base <- getSimplRules ; let seq_rules = getRules rule_base seqId - ; mb_match <- tryRules out_env seq_rules seqId rule_cont - ; return $ case mb_match of - Just (rhs,cont') -> Just (out_env, rhs, cont') - Nothing -> Nothing } + ; tryRules out_env seq_rules seqId rule_cont } where - out_env = zapSubstEnv in_env + out_env = zapSubstEnv in_env no_cast_scrut = drop_casts scrut -- All these are OutTypes @@ -3210,8 +3227,8 @@ rebuildCase env scrut case_bndr alts@[Alt _ bndrs rhs] cont | is_plain_seq = do { mb_rule <- trySeqRules env scrut rhs cont ; case mb_rule of - Just (env',rule_rhs, cont') -> simplExprF env' rule_rhs cont' - Nothing -> reallyRebuildCase env scrut case_bndr alts cont } + Just (rule_rhs, cont') -> simplExprF (zapSubstEnv env) rule_rhs cont' + Nothing -> reallyRebuildCase env scrut case_bndr alts cont } -------------------------------------------------- -- 3. Primop-related case-rules @@ -3262,7 +3279,7 @@ reallyRebuildCase env scrut case_bndr alts cont -- Note [Case-of-case and full laziness] = do { case_expr <- simplAlts env scrut case_bndr alts (mkBoringStop (contHoleType cont)) - ; rebuild env case_expr cont } + ; rebuild (zapSubstEnv env) case_expr cont } | otherwise = do { (floats, env', cont') <- mkDupableCaseCont env alts cont View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f2f832cd99d3a3f3cc809c417ec3c072b8beb03 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f2f832cd99d3a3f3cc809c417ec3c072b8beb03 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/84f86994/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 00:31:45 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 12 Mar 2025 20:31:45 -0400 Subject: [Git][ghc/ghc][wip/T25647] improve zonking logic for tcFamInstLHSBinders Message-ID: <67d2277169b89_31c284884cbc969d1@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 3d92409e by Patrick at 2025-03-13T08:31:35+08:00 improve zonking logic for tcFamInstLHSBinders - - - - - 3 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Zonk/TcType.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -249,47 +249,43 @@ tcTyClGroup (TyClGroup { group_tyclds = tyclds th_bndrs' `plusNameEnv` th_bndrs) } --- tcFamInstLHSBinders :: FamEqn TyVar Name -> TcM [TyVar] tcFamInstLHSBinders :: TcLevel -> SkolemInfo -> HsOuterFamEqnTyVarBndrs GhcTc -> HsOuterFamEqnTyVarBndrs GhcRn -> [TcTyVar] -> Type -> WantedConstraints -> IOEnv (Env TcGblEnv TcLclEnv) ([TyCoVar], [TcTyVar]) tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted = do - -- This code (and the stuff immediately above) is very similar - -- to that in tcTyFamInstEqnGuts. Maybe we should abstract the - -- common code; but for the moment I concluded that it's - -- clearer to duplicate it. Still, if you fix a bug here, - -- check there too! -- See Note [Type variables in type families instance decl] ; let outer_exp_tvs = scopedSort $ explicitOuterTyVars outer_bndrs ; let outer_imp_tvs = implicitOuterTyVars outer_bndrs ; checkFamTelescope tclvl hs_outer_bndrs outer_exp_tvs - ; outer_imp_wc_tvs <- liftZonkM $ zonkTcTyVarsToTcTyVarsMaybe $ outer_imp_tvs ++ wcs + ; wc_itvs <- liftZonkM $ zonkInvariants wcs + ; outer_imp_itvs <- liftZonkM $ zonkInvariants outer_imp_tvs -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; (dvs, cqdvs) <- candidateQTyVarsWithBinders outer_imp_wc_tvs outer_exp_tvs lhs_ty - ; qtvs <- quantifyTyVarsWithBinders cqdvs skol_info dvs - -- Have to make a same defaulting choice for reuslt kind here + ; dvs <- candidateQTyVarsWithBinders (outer_exp_tvs ++ outer_imp_tvs ++ wcs) lhs_ty + ; (qtvs, outer_imp_qtvs) <- quantifyTyVarsWithBinders wc_itvs outer_imp_itvs skol_info dvs + -- Have to make a same defaulting choice for result kind here -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - - ; let final_tvs = scopedSort (qtvs ++ outer_exp_tvs) - + ; let final_tvs = scopedSort (qtvs ++ outer_exp_tvs ++ outer_imp_qtvs) + -- This scopedSort is important: the qtvs may be /interleaved/ with + -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ; traceTc "tcFamInstLHSBinders" $ vcat [ - -- ppr fam_tc - text "lhs_ty:" <+> ppr lhs_ty - , text "final_tvs:" <+> pprTyVars final_tvs + text "outer_bndrs:" <+> ppr outer_bndrs , text "outer_imp_tvs:" <+> pprTyVars outer_imp_tvs , text "outer_exp_tvs:" <+> pprTyVars outer_exp_tvs , text "wcs:" <+> pprTyVars wcs - , text "outer_imp_wc_tvs:" <+> pprTyVars outer_imp_wc_tvs - , text "outer_bndrs:" <+> ppr outer_bndrs - , text "qtvs:" <+> pprTyVars qtvs - , text "cqdvs:" <+> pprTyVars cqdvs - , text "dvs:" <+> ppr dvs + + -- after zonking + , text "wc_itvs:" <+> pprTyVars wc_itvs + , text "outer_imp_itvs:" <+> pprTyVars outer_imp_itvs + , text "dvs:" <+> ppr dvs + + -- after quantification + , text "qtvs(include wildcards):" <+> pprTyVars qtvs + , text "outer_imp_qtvs:" <+> pprTyVars outer_imp_qtvs + , text "final_tvs:" <+> pprTyVars final_tvs ] - -- This scopedSort is important: the qtvs may be /interleaved/ with - -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ; reportUnsolvedEqualities skol_info final_tvs tclvl wanted return (final_tvs, qtvs) ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1392,23 +1392,18 @@ partitionCandidates dvs@(DV { dv_kvs = kvs, dv_tvs = tvs }) pred (extracted_tvs, rest_tvs) = partitionDVarSet pred tvs extracted = dVarSetToVarSet extracted_kvs `unionVarSet` dVarSetToVarSet extracted_tvs -candidateQTyVarsWithBinders :: [TyVar] -> [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar]) +candidateQTyVarsWithBinders :: [TyVar] -> Type -> TcM CandidatesQTvs -- (candidateQTyVarsWithBinders tvs ty) returns the candidateQTyVars -- of (forall tvs. ty), but do not treat 'tvs' as bound for the purpose -- of Note [Naughty quantification candidates]. Why? -- Because we are going to scoped-sort the quantified variables -- in among the tvs --- also return the bound variables that need to be quantified --- since they can be come from implicit binders and wildcards --- See Note [Type variables in type families instance decl] -candidateQTyVarsWithBinders imp_bound_tvs exp_bound_tvs ty +candidateQTyVarsWithBinders bound_tvs ty = do { kvs <- candidateQTyVarsOfKinds (map tyVarKind bound_tvs) ; cur_lvl <- getTcLevel ; all_tvs <- collect_cand_qtvs ty False cur_lvl emptyVarSet kvs ty - ; return (all_tvs `delCandidates` bound_tvs, boundedCandidates all_tvs imp_bound_tvs) } - where bound_tvs = imp_bound_tvs ++ exp_bound_tvs - + ; return (all_tvs `delCandidates` bound_tvs)} -- | Gathers free variables to use as quantification candidates (in -- 'quantifyTyVarsWithBinders). This might output the same var @@ -1758,14 +1753,15 @@ quantifyTyVars :: SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] -- Already zonked -> TcM [TcTyVar] -quantifyTyVars = quantifyTyVarsWithBinders [] +quantifyTyVars ski tvs = fst <$> quantifyTyVarsWithBinders [] [] ski tvs quantifyTyVarsWithBinders :: [TcTyVar] + -> [TcTyVar] -> SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] -- Already zonked - -> TcM [TcTyVar] + -> TcM ([TcTyVar], [TcTyVar]) -- See Note [quantifyTyVars] -- Can be given a mixture of TcTyVars and TyVars, in the case of -- associated type declarations. Also accepts covars, but *never* returns any. @@ -1773,31 +1769,41 @@ quantifyTyVarsWithBinders :: -- invariants on CandidateQTvs, we do not have to filter out variables -- free in the environment here. Just quantify unconditionally, subject -- to the restrictions in Note [quantifyTyVars]. -quantifyTyVarsWithBinders cvs skol_info dvs + +-- for wildcards, do not default, just skolemise add to the list of quantified +-- for outer_imp_qtvs, do not default and skolemise, and return separately +quantifyTyVarsWithBinders wc_itvs outer_imp_itvs skol_info dvs -- short-circuit common case - | isEmptyCandidates dvs && null cvs + | isEmptyCandidates dvs && null wc_itvs && null outer_imp_itvs = do { traceTc "quantifyTyVars has nothing to quantify" empty - ; return [] } + ; return ([], []) } | otherwise = do { traceTc "quantifyTyVars {" ( vcat [ text "dvs =" <+> ppr dvs, - text "cvs =" <+> ppr cvs + text "wc_qtvs =" <+> ppr wc_itvs, + text "outer_imp_qtvs =" <+> ppr outer_imp_itvs ]) ; undefaulted <- defaultTyVars dvs - ; final_qtvs <- liftZonkM $ mapMaybeM zonk_quant (undefaulted++cvs) + ; (final_qtvs, out_imp_qtvs) <- liftZonkM $ do + qtvs <- mapMaybeM zonk_quant undefaulted + wc_qtv <- mapMaybeM zonk_quant wc_itvs + out_imp_qtvs <- mapMaybeM zonk_quant outer_imp_itvs + return (qtvs ++ wc_qtv, out_imp_qtvs) ; traceTc "quantifyTyVars }" (vcat [ text "undefaulted:" <+> pprTyVars undefaulted - , text "final_qtvs:" <+> pprTyVars final_qtvs ]) + , text "final_qtvs:" <+> pprTyVars final_qtvs + , text "out_imp_qtvs:" <+> pprTyVars out_imp_qtvs + ]) -- We should never quantify over coercion variables; check this ; let co_vars = filter isCoVar final_qtvs ; massertPpr (null co_vars) (ppr co_vars) - ; return final_qtvs } + ; return (final_qtvs, out_imp_qtvs) } where -- zonk_quant returns a tyvar if it should be quantified over; -- otherwise, it returns Nothing. The latter case happens for ===================================== compiler/GHC/Tc/Zonk/TcType.hs ===================================== @@ -20,7 +20,7 @@ module GHC.Tc.Zonk.TcType , zonkTcTyVarToTcTyVar, zonkTcTyVarsToTcTyVars , zonkInvisTVBinder , zonkCo - , zonkTcTyVarsToTcTyVarsMaybe + , zonkInvariants -- ** Zonking 'TyCon's , zonkTcTyCon @@ -270,8 +270,13 @@ zonkTcTyVar tv zonkTcTyVarsToTcTyVars :: HasDebugCallStack => [TcTyVar] -> ZonkM [TcTyVar] zonkTcTyVarsToTcTyVars = mapM zonkTcTyVarToTcTyVar -zonkTcTyVarsToTcTyVarsMaybe :: HasDebugCallStack => [TcTyVar] -> ZonkM [TcTyVar] -zonkTcTyVarsToTcTyVarsMaybe = mapMaybeM (fmap getTyVar_maybe . zonkTcTyVar) +-- let x = zonked and y = unzonked +-- take intersection of x and y +zonkInvariants :: HasDebugCallStack => [TcTyVar] -> ZonkM [TcTyVar] +zonkInvariants y = do + x <- mapMaybeM (fmap getTyVar_maybe . zonkTcTyVar) y + return $ dVarSetElems $ mkDVarSet y `intersectDVarSet` mkDVarSet x + zonkTcTyVarToTcTyVar :: HasDebugCallStack => TcTyVar -> ZonkM TcTyVar zonkTcTyVarToTcTyVar tv View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3d92409e96b7cb1521492d00aaf6b1d6384a9a58 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3d92409e96b7cb1521492d00aaf6b1d6384a9a58 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/4de03ac4/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 00:48:14 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 12 Mar 2025 20:48:14 -0400 Subject: [Git][ghc/ghc][wip/T25647] clean up trace statements and remove unused function Message-ID: <67d22b4e409e_31c284c12b1898968@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 90ccf36d by Patrick at 2025-03-13T08:48:04+08:00 clean up trace statements and remove unused function - - - - - 3 changed files: - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/Solver.hs ===================================== @@ -175,7 +175,6 @@ pushLevelAndSolveEqualities skol_info_anon tcbs thing_inside ; report_unsolved_equalities skol_info_anon (binderVars tcbs) tclvl wanted ; return res } - pushLevelAndSolveEqualitiesX :: String -> TcM a -> TcM (TcLevel, WantedConstraints, a) -- Push the level, gather equality constraints, and then solve them. ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -507,8 +507,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_ext = lwarn fst $ splitForAllForAllTyBinders dfun_ty visible_skol_tvs = drop n_inferred skol_tvs - ; traceTc "tcLocalInstDecl 1" (ppr dfun_ty $$ ppr (invisibleBndrCount dfun_ty) $$ ppr skol_tvs - $$ ppr (classTyVars clas)) + ; traceTc "tcLocalInstDecl 1" (ppr dfun_ty $$ ppr (invisibleBndrCount dfun_ty) $$ ppr skol_tvs) -- Next, process any associated types. ; (datafam_stuff, tyfam_insts) ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -827,7 +827,7 @@ cloneAnonMetaTyVar info tv kind = do { details <- newMetaDetails info ; name <- cloneMetaTyVarName (tyVarName tv) ; let tyvar = mkTcTyVar name kind details - ; traceTc "cloneAnonMetaTyVar" (ppr tyvar <+> dcolon <+> ppr (tyVarKind tyvar) <+> text "from" <+> ppr tv) + ; traceTc "cloneAnonMetaTyVar" (ppr tyvar <+> dcolon <+> ppr (tyVarKind tyvar)) ; return tyvar } -- Make a new CycleBreakerTv. See Note [Type equality cycles] @@ -1375,14 +1375,6 @@ delCandidates (DV { dv_kvs = kvs, dv_tvs = tvs, dv_cvs = cvs }) vars , dv_tvs = tvs `delDVarSetList` vars , dv_cvs = cvs `delVarSetList` vars } -boundedCandidates :: CandidatesQTvs -> [Var] -> [Var] -boundedCandidates (DV { dv_kvs = kvs, dv_tvs = tvs, dv_cvs = _cvs }) vars - = dVarSetElems $ - (kvs `intersectDVarSet` dvars) - `unionDVarSet` (tvs `intersectDVarSet` dvars) - where dvars = extendDVarSetList emptyDVarSet vars - - partitionCandidates :: CandidatesQTvs -> (TyVar -> Bool) -> (TyVarSet, CandidatesQTvs) -- The selected TyVars are returned as a non-deterministic TyVarSet partitionCandidates dvs@(DV { dv_kvs = kvs, dv_tvs = tvs }) pred View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/90ccf36daedba03fdac61d86f2e34a07fb2daf89 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/90ccf36daedba03fdac61d86f2e34a07fb2daf89 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/bb1c8c58/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 02:28:15 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Wed, 12 Mar 2025 22:28:15 -0400 Subject: [Git][ghc/ghc][wip/T25647] fix ppr Message-ID: <67d242bf2e8d6_31c28416c428c1088a7@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 7dfaeefb by Patrick at 2025-03-13T10:28:01+08:00 fix ppr - - - - - 1 changed file: - compiler/GHC/Tc/TyCl.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -271,7 +271,8 @@ tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ; traceTc "tcFamInstLHSBinders" $ vcat [ - text "outer_bndrs:" <+> ppr outer_bndrs + text "lhs_ty:" <+> ppr lhs_ty + , text "outer_bndrs:" <+> ppr outer_bndrs , text "outer_imp_tvs:" <+> pprTyVars outer_imp_tvs , text "outer_exp_tvs:" <+> pprTyVars outer_exp_tvs , text "wcs:" <+> pprTyVars wcs @@ -3503,7 +3504,7 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty -- so that any strange coercions inside lhs_ty -- have been solved before we attempt to unravel it - ; traceTc "tcTyFamInstEqnGuts }" (vcat [ ppr pats, ppr fam_tc, pprTyVars final_tvs ]) + ; traceTc "tcTyFamInstEqnGuts }" (vcat [ ppr fam_tc, pprTyVars final_tvs ]) -- Don't try to print 'pats' here, because lhs_ty involves -- a knot-tied type constructor, so we get a black hole View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7dfaeefb939c83470fcf33b0303d68af63deb678 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7dfaeefb939c83470fcf33b0303d68af63deb678 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/8c73ab81/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 03:46:38 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 12 Mar 2025 23:46:38 -0400 Subject: [Git][ghc/ghc][wip/bytecode-serialize-pre] 87 commits: LLVM: account for register type in funPrologue Message-ID: <67d2551e7ae0_36e86a31f6141896d@gitlab.mail> Cheng Shao pushed to branch wip/bytecode-serialize-pre at Glasgow Haskell Compiler / GHC Commits: 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 3a6ca229 by Cheng Shao at 2025-03-13T03:12:19+00:00 compiler: do not allocate strings in bytecode assembler - - - - - 9790fd5f by Cheng Shao at 2025-03-13T03:14:25+00:00 compiler: make bc_strs serializable - - - - - 1099c5dc by Cheng Shao at 2025-03-13T03:14:29+00:00 compiler: make bc_itbls serializable - - - - - 4777dcec by Cheng Shao at 2025-03-13T03:46:17+00:00 compiler: remove FFIInfo bookkeeping in BCO - - - - - 6ef40e50 by Cheng Shao at 2025-03-13T03:46:22+00:00 compiler: make FFIInfo serializable in BCO - - - - - 0bf578c6 by Cheng Shao at 2025-03-13T03:46:22+00:00 compiler: make SptEntry serializable - - - - - b203b23f by Cheng Shao at 2025-03-13T03:46:22+00:00 ghci: remove redundant NewBreakModule message - - - - - f860c4bb by Cheng Shao at 2025-03-13T03:46:22+00:00 WIP - - - - - 391 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - 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/Cmm/CallConv.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/Types.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/StaticPtr.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - m4/fp_settings.m4 - rts/HeapStackCheck.cmm - rts/Interpreter.c - rts/PrimOps.cmm - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - testsuite/tests/bytecode/T22376/all.T - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d71e1840c5daca60930085d704f7a0afdd8e9f9f...f860c4bb261659c6fb3d81b02b88083f6ab89acd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d71e1840c5daca60930085d704f7a0afdd8e9f9f...f860c4bb261659c6fb3d81b02b88083f6ab89acd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250312/f130c844/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 05:47:20 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 13 Mar 2025 01:47:20 -0400 Subject: [Git][ghc/ghc][master] interfaces: Ensure that forceModIface deeply forces a ModIface Message-ID: <67d2716866c0f_39841947a89c29558@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 29 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - libraries/ghc-boot/GHC/Serialized.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Core.hs ===================================== @@ -120,6 +120,8 @@ import Data.List.NonEmpty (nonEmpty) import qualified Data.List.NonEmpty as NE import Data.Word +import Control.DeepSeq + infixl 4 `mkApps`, `mkTyApps`, `mkVarApps`, `App`, `mkCoApps` -- Left associative, so that we can say (f `mkTyApps` xs `mkVarApps` ys) @@ -1185,6 +1187,10 @@ instance Binary IsOrphan where n <- get bh return $ NotOrphan n +instance NFData IsOrphan where + rnf IsOrphan = () + rnf (NotOrphan n) = rnf n + {- Note [Orphans] ~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Coercion/Axiom.hs ===================================== @@ -58,6 +58,7 @@ import GHC.Types.SrcLoc import qualified Data.Data as Data import Data.Array import Data.List ( mapAccumL ) +import Control.DeepSeq {- Note [Coercion axiom branches] @@ -559,6 +560,11 @@ instance Binary Role where 3 -> return Phantom _ -> panic ("get Role " ++ show tag) +instance NFData Role where + rnf Nominal = () + rnf Representational = () + rnf Phantom = () + {- ************************************************************************ * * ===================================== compiler/GHC/Core/DataCon.hs ===================================== @@ -112,6 +112,7 @@ import qualified Data.ByteString.Lazy as LBS import qualified Data.Data as Data import Data.Char import Data.List( find ) +import Control.DeepSeq {- Note [Data constructor representation] @@ -1078,6 +1079,16 @@ instance Binary SrcUnpackedness where 1 -> return SrcUnpack _ -> return NoSrcUnpack +instance NFData SrcStrictness where + rnf SrcLazy = () + rnf SrcStrict = () + rnf NoSrcStrict = () + +instance NFData SrcUnpackedness where + rnf SrcNoUnpack = () + rnf SrcUnpack = () + rnf NoSrcUnpack = () + -- | Compare strictness annotations eqHsBang :: HsImplBang -> HsImplBang -> Bool eqHsBang HsLazy HsLazy = True ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -994,6 +994,11 @@ instance Outputable FunSel where ppr SelArg = text "arg" ppr SelRes = text "res" +instance NFData FunSel where + rnf SelMult = () + rnf SelArg = () + rnf SelRes = () + instance Binary CoSel where put_ bh (SelTyCon n r) = do { putByte bh 0; put_ bh n; put_ bh r } put_ bh SelForAll = putByte bh 1 @@ -1010,9 +1015,9 @@ instance Binary CoSel where _ -> return (SelFun SelRes) } instance NFData CoSel where - rnf (SelTyCon n r) = n `seq` r `seq` () + rnf (SelTyCon n r) = rnf n `seq` rnf r `seq` () rnf SelForAll = () - rnf (SelFun fs) = fs `seq` () + rnf (SelFun fs) = rnf fs `seq` () -- | A semantically more meaningful type to represent what may or may not be a -- useful 'Coercion'. ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -181,6 +181,7 @@ import GHC.Settings.Constants import GHC.Utils.Misc import GHC.Types.Unique.Set import GHC.Unit.Module +import Control.DeepSeq import Language.Haskell.Syntax.Basic (FieldLabelString(..)) @@ -731,6 +732,11 @@ instance Binary TyConBndrVis where 0 -> return AnonTCB _ -> do { vis <- get bh; return (NamedTCB vis) } } +instance NFData TyConBndrVis where + rnf AnonTCB = () + rnf (NamedTCB vis) = rnf vis + + {- ********************************************************************* * * @@ -2916,6 +2922,10 @@ instance Binary Injectivity where _ -> do { xs <- get bh ; return (Injective xs) } } +instance NFData Injectivity where + rnf NotInjective = () + rnf (Injective xs) = rnf xs + -- | Returns whether or not this 'TyCon' is definite, or a hole -- that may be filled in at some later point. See Note [Skolem abstract data] tyConSkolem :: TyCon -> Bool ===================================== compiler/GHC/Data/Strict.hs ===================================== @@ -22,10 +22,15 @@ import GHC.Prelude hiding (Maybe(..), Either(..)) import Control.Applicative import Data.Semigroup import Data.Data +import Control.DeepSeq data Maybe a = Nothing | Just !a deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data) +instance NFData a => NFData (Maybe a) where + rnf Nothing = () + rnf (Just x) = rnf x + fromMaybe :: a -> Maybe a -> a fromMaybe d Nothing = d fromMaybe _ (Just x) = x ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -76,7 +76,10 @@ instance Binary Language where get bh = toEnum <$> get bh instance NFData Language where - rnf x = x `seq` () + rnf Haskell98 = () + rnf Haskell2010 = () + rnf GHC2021 = () + rnf GHC2024 = () data OnOff a = On a | Off a ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -111,7 +111,5 @@ instance Outputable ModIfaceSelfRecomp where ])] instance NFData ModIfaceSelfRecomp where - -- Note (MP): does not deeply force Usages but the old ModIface logic didn't either, so - -- I left it as a shallow force. rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = src_hash `seq` usages `seq` flag_hash `seq` opt_hash `seq` hpc_hash `seq` plugin_hash `seq` () \ No newline at end of file + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -94,7 +94,7 @@ import GHC.Utils.Binary.Typeable () -- instance Binary AnnPayload import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith, - seqList, zipWithEqual ) + zipWithEqual ) import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..)) @@ -539,6 +539,14 @@ instance Binary IfaceLFInfo where 4 -> pure IfLFUnlifted _ -> panic "Invalid byte" +instance NFData IfaceLFInfo where + rnf = \case + IfLFReEntrant arity -> rnf arity + IfLFThunk updatable mb_fun -> rnf updatable `seq` rnf mb_fun + IfLFCon con -> rnf con + IfLFUnknown fun_flag -> rnf fun_flag + IfLFUnlifted -> () + {- Note [Versioning of instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2767,6 +2775,10 @@ getUnfoldingCache bh = do return (UnfoldingCache { uf_is_value = hnf, uf_is_conlike = conlike , uf_is_work_free = wf, uf_expandable = exp }) +seqUnfoldingCache :: IfUnfoldingCache -> () +seqUnfoldingCache (UnfoldingCache hnf conlike wf exp) = + rnf hnf `seq` rnf conlike `seq` rnf wf `seq` rnf exp `seq` () + infixl 9 .<<|. (.<<|.) :: (Num a, Bits a) => a -> Bool -> a x .<<|. b = (if b then (`setBit` 0) else id) (x `shiftL` 1) @@ -2837,12 +2849,10 @@ instance Binary IfaceExpr where putByte bh 13 put_ bh a put_ bh b - put_ bh (IfaceLitRubbish TypeLike r) = do + put_ bh (IfaceLitRubbish torc r) = do putByte bh 14 put_ bh r - put_ bh (IfaceLitRubbish ConstraintLike r) = do - putByte bh 15 - put_ bh r + put_ bh torc get bh = do h <- getByte bh case h of @@ -2886,9 +2896,8 @@ instance Binary IfaceExpr where b <- get bh return (IfaceECase a b) 14 -> do r <- get bh - return (IfaceLitRubbish TypeLike r) - 15 -> do r <- get bh - return (IfaceLitRubbish ConstraintLike r) + torc <- get bh + return (IfaceLitRubbish torc r) _ -> panic ("get IfaceExpr " ++ show h) instance Binary IfaceTickish where @@ -3047,31 +3056,31 @@ instance NFData IfaceDecl where rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 IfaceData f1 f2 f3 f4 f5 f6 f7 f8 f9 -> - f1 `seq` seqList f2 `seq` f3 `seq` f4 `seq` f5 `seq` + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` rnf f9 IfaceSynonym f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 IfaceFamily f1 f2 f3 f4 f5 f6 -> - rnf f1 `seq` rnf f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 `seq` f6 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` () IfaceClass f1 f2 f3 f4 f5 -> - rnf f1 `seq` f2 `seq` seqList f3 `seq` rnf f4 `seq` rnf f5 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 IfaceAxiom nm tycon role ax -> rnf nm `seq` rnf tycon `seq` - role `seq` + rnf role `seq` rnf ax IfacePatSyn f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 -> - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` f6 `seq` - rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` f11 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 `seq` () instance NFData IfaceAxBranch where rnf (IfaceAxBranch f1 f2 f3 f4 f5 f6 f7) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` rnf f7 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 instance NFData IfaceClassBody where rnf = \case @@ -3089,7 +3098,7 @@ instance NFData IfaceAT where rnf (IfaceAT f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceClassOp where - rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` f3 `seq` () + rnf (IfaceClassOp f1 f2 f3) = rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` () instance NFData IfaceTyConParent where rnf = \case @@ -3104,19 +3113,22 @@ instance NFData IfaceConDecls where instance NFData IfaceConDecl where rnf (IfCon f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` f5 `seq` rnf f6 `seq` - rnf f7 `seq` rnf f8 `seq` f9 `seq` rnf f10 `seq` rnf f11 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` + rnf f7 `seq` rnf f8 `seq` rnf f9 `seq` rnf f10 `seq` rnf f11 instance NFData IfaceSrcBang where - rnf (IfSrcBang f1 f2) = f1 `seq` f2 `seq` () + rnf (IfSrcBang f1 f2) = rnf f1 `seq` rnf f2 `seq` () instance NFData IfaceBang where - rnf x = x `seq` () + rnf IfNoBang = () + rnf IfStrict = () + rnf IfUnpack = () + rnf (IfUnpackCo co) = rnf co instance NFData IfaceIdDetails where rnf = \case IfVanillaId -> () - IfWorkerLikeId dmds -> dmds `seqList` () + IfWorkerLikeId dmds -> rnf dmds `seq` () IfRecSelId (Left tycon) b c d -> rnf tycon `seq` rnf b `seq` rnf c `seq` rnf d IfRecSelId (Right decl) b c d -> rnf decl `seq` rnf b `seq` rnf c `seq` rnf d IfDFunId -> () @@ -3125,23 +3137,22 @@ instance NFData IfaceInfoItem where rnf = \case HsArity a -> rnf a HsDmdSig str -> seqDmdSig str - HsInline p -> p `seq` () -- TODO: seq further? + HsInline p -> rnf p `seq` () HsUnfold b unf -> rnf b `seq` rnf unf HsNoCafRefs -> () - HsCprSig cpr -> cpr `seq` () - HsLFInfo lf_info -> lf_info `seq` () -- TODO: seq further? - HsTagSig sig -> sig `seq` () + HsCprSig cpr -> seqCprSig cpr `seq` () + HsLFInfo lf_info -> rnf lf_info `seq` () + HsTagSig sig -> seqTagSig sig `seq` () instance NFData IfGuidance where rnf = \case IfNoGuidance -> () - IfWhen a b c -> a `seq` b `seq` c `seq` () + IfWhen a b c -> rnf a `seq` rnf b `seq` rnf c `seq` () instance NFData IfaceUnfolding where rnf = \case - IfCoreUnfold src cache guidance expr -> src `seq` cache `seq` rnf guidance `seq` rnf expr + IfCoreUnfold src cache guidance expr -> rnf src `seq` seqUnfoldingCache cache `seq` rnf guidance `seq` rnf expr IfDFunUnfold bndrs exprs -> rnf bndrs `seq` rnf exprs - -- See Note [UnfoldingCache] in GHC.Core for why it suffices to merely `seq` on cache instance NFData IfaceExpr where rnf = \case @@ -3149,16 +3160,16 @@ instance NFData IfaceExpr where IfaceExt nm -> rnf nm IfaceType ty -> rnf ty IfaceCo co -> rnf co - IfaceTuple sort exprs -> sort `seq` rnf exprs + IfaceTuple sort exprs -> rnf sort `seq` rnf exprs IfaceLam bndr expr -> rnf bndr `seq` rnf expr IfaceApp e1 e2 -> rnf e1 `seq` rnf e2 - IfaceCase e nm alts -> rnf e `seq` nm `seq` rnf alts + IfaceCase e nm alts -> rnf e `seq` rnf nm `seq` rnf alts IfaceECase e ty -> rnf e `seq` rnf ty IfaceLet bind e -> rnf bind `seq` rnf e IfaceCast e co -> rnf e `seq` rnf co - IfaceLit l -> l `seq` () -- FIXME - IfaceLitRubbish tc r -> tc `seq` rnf r `seq` () - IfaceFCall fc ty -> fc `seq` rnf ty + IfaceLit l -> rnf l `seq` () + IfaceLitRubbish tc r -> rnf tc `seq` rnf r `seq` () + IfaceFCall fc ty -> rnf fc `seq` rnf ty IfaceTick tick e -> rnf tick `seq` rnf e instance NFData IfaceAlt where @@ -3170,7 +3181,7 @@ instance (NFData b, NFData a) => NFData (IfaceBindingX a b) where IfaceRec binds -> rnf binds instance NFData IfaceTopBndrInfo where - rnf (IfGblTopBndr n) = n `seq` () + rnf (IfGblTopBndr n) = rnf n `seq` () rnf (IfLclTopBndr fs ty info dets) = rnf fs `seq` rnf ty `seq` rnf info `seq` rnf dets `seq` () instance NFData IfaceMaybeRhs where @@ -3192,22 +3203,22 @@ instance NFData IfaceFamTyConFlav where instance NFData IfaceTickish where rnf = \case IfaceHpcTick m i -> rnf m `seq` rnf i - IfaceSCC cc b1 b2 -> cc `seq` rnf b1 `seq` rnf b2 - IfaceSource src str -> src `seq` rnf str + IfaceSCC cc b1 b2 -> rnf cc `seq` rnf b1 `seq` rnf b2 + IfaceSource src str -> rnf src `seq` rnf str IfaceBreakpoint m i fvs -> rnf m `seq` rnf i `seq` rnf fvs instance NFData IfaceConAlt where rnf = \case IfaceDefaultAlt -> () IfaceDataAlt nm -> rnf nm - IfaceLitAlt lit -> lit `seq` () + IfaceLitAlt lit -> rnf lit `seq` () instance NFData IfaceCompleteMatch where rnf (IfaceCompleteMatch f1 mtc) = rnf f1 `seq` rnf mtc instance NFData IfaceRule where rnf (IfaceRule f1 f2 f3 f4 f5 f6 f7 f8) = - rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` f8 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq` () instance NFData IfaceDefault where rnf (IfaceDefault f1 f2 f3) = @@ -3215,11 +3226,11 @@ instance NFData IfaceDefault where instance NFData IfaceFamInst where rnf (IfaceFamInst f1 f2 f3 f4) = - rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` () + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` () instance NFData IfaceClsInst where rnf (IfaceClsInst f1 f2 f3 f4 f5 f6) = - f1 `seq` rnf f2 `seq` rnf f3 `seq` f4 `seq` f5 `seq` rnf f6 + rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 `seq` rnf f6 instance NFData IfaceWarnings where rnf = \case @@ -3227,12 +3238,12 @@ instance NFData IfaceWarnings where IfWarnSome vs ds -> rnf vs `seq` rnf ds instance NFData IfaceWarningTxt where - rnf = \case - IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 - IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 + rnf = \case + IfWarningTxt f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 + IfDeprecatedTxt f1 f2 -> rnf f1 `seq` rnf f2 instance NFData IfaceStringLiteral where - rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 + rnf (IfStringLiteral f1 f2) = rnf f1 `seq` rnf f2 instance NFData IfaceAnnotation where - rnf (IfaceAnnotation f1 f2) = f1 `seq` f2 `seq` () + rnf (IfaceAnnotation f1 f2) = rnf f1 `seq` rnf f2 `seq` () ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -2577,18 +2577,23 @@ instance Binary (DefMethSpec IfaceType) where 0 -> return VanillaDM _ -> do { t <- get bh; return (GenericDM t) } +instance NFData (DefMethSpec IfaceType) where + rnf = \case + VanillaDM -> () + GenericDM t -> rnf t + instance NFData IfaceType where rnf = \case IfaceFreeTyVar f1 -> f1 `seq` () IfaceTyVar f1 -> rnf f1 IfaceLitTy f1 -> rnf f1 IfaceAppTy f1 f2 -> rnf f1 `seq` rnf f2 - IfaceFunTy f1 f2 f3 f4 -> f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 - IfaceForAllTy f1 f2 -> f1 `seq` rnf f2 + IfaceFunTy f1 f2 f3 f4 -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 + IfaceForAllTy f1 f2 -> rnf f1 `seq` rnf f2 IfaceTyConApp f1 f2 -> rnf f1 `seq` rnf f2 IfaceCastTy f1 f2 -> rnf f1 `seq` rnf f2 IfaceCoercionTy f1 -> rnf f1 - IfaceTupleTy f1 f2 f3 -> f1 `seq` f2 `seq` rnf f3 + IfaceTupleTy f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 instance NFData IfaceTyLit where rnf = \case @@ -2599,21 +2604,25 @@ instance NFData IfaceTyLit where instance NFData IfaceCoercion where rnf = \case IfaceReflCo f1 -> rnf f1 - IfaceGReflCo f1 f2 f3 -> f1 `seq` rnf f2 `seq` rnf f3 - IfaceFunCo f1 f2 f3 f4 -> f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 - IfaceTyConAppCo f1 f2 f3 -> f1 `seq` rnf f2 `seq` rnf f3 + IfaceGReflCo f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 + IfaceFunCo f1 f2 f3 f4 -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 + IfaceTyConAppCo f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 IfaceAppCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceForAllCo f1 f2 f3 f4 f5 -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 IfaceCoVarCo f1 -> rnf f1 IfaceAxiomCo f1 f2 -> rnf f1 `seq` rnf f2 - IfaceUnivCo f1 f2 f3 f4 deps -> rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf deps + IfaceUnivCo f1 f2 f3 f4 deps -> rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf deps IfaceSymCo f1 -> rnf f1 IfaceTransCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceSelCo f1 f2 -> rnf f1 `seq` rnf f2 - IfaceLRCo f1 f2 -> f1 `seq` rnf f2 + IfaceLRCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceInstCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceKindCo f1 -> rnf f1 IfaceSubCo f1 -> rnf f1 + -- These are not deeply forced because they are not used in ModIface, + -- these constructors are for pretty-printing. + -- See Note [Free TyVars and CoVars in IfaceType] + -- See Note [Holes in IfaceCoercion] IfaceFreeCoVar f1 -> f1 `seq` () IfaceHoleCo f1 -> f1 `seq` () @@ -2624,15 +2633,17 @@ instance NFData IfaceAxiomRule where IfaceAR_B n i -> rnf n `seq` rnf i instance NFData IfaceMCoercion where - rnf x = seq x () + rnf IfaceMRefl = () + rnf (IfaceMCo c) = rnf c instance NFData IfaceOneShot where - rnf x = seq x () + rnf IfaceOneShot = () + rnf IfaceNoOneShot = () instance NFData IfaceTyConSort where rnf = \case IfaceNormalTyCon -> () - IfaceTupleTyCon arity sort -> rnf arity `seq` sort `seq` () + IfaceTupleTyCon arity sort -> rnf arity `seq` rnf sort `seq` () IfaceSumTyCon arity -> rnf arity IfaceEqualityTyCon -> () @@ -2640,7 +2651,7 @@ instance NFData IfLclName where rnf (IfLclName lfs) = rnf lfs instance NFData IfaceTyConInfo where - rnf (IfaceTyConInfo f s) = f `seq` rnf s + rnf (IfaceTyConInfo f s) = rnf f `seq` rnf s instance NFData IfaceTyCon where rnf (IfaceTyCon nm info) = rnf nm `seq` rnf info @@ -2653,4 +2664,4 @@ instance NFData IfaceBndr where instance NFData IfaceAppArgs where rnf = \case IA_Nil -> () - IA_Arg f1 f2 f3 -> rnf f1 `seq` f2 `seq` rnf f3 + IA_Arg f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -148,6 +148,7 @@ import qualified GHC.Boot.TH.Ppr as TH #if defined(HAVE_INTERNAL_INTERPRETER) import Unsafe.Coerce ( unsafeCoerce ) import GHC.Desugar ( AnnotationWrapper(..) ) +import Control.DeepSeq #endif import Control.Monad @@ -1039,11 +1040,7 @@ convertAnnotationWrapper fhv = do -- annotation are exposed at this point. This is also why we are -- doing all this stuff inside the context of runMeta: it has the -- facilities to deal with user error in a meta-level expression - seqSerialized serialized `seq` serialized - --- | Force the contents of the Serialized value so weknow it doesn't contain any bottoms -seqSerialized :: Serialized -> () -seqSerialized (Serialized the_type bytes) = the_type `seq` bytes `seqList` () + rnf serialized `seq` serialized #endif ===================================== compiler/GHC/Types/Annotations.hs ===================================== @@ -31,7 +31,7 @@ import Control.Monad import Data.Maybe import Data.Typeable import Data.Word ( Word8 ) - +import Control.DeepSeq -- | Represents an annotation after it has been sufficiently desugared from -- it's initial form of 'GHC.Hs.Decls.AnnDecl' @@ -71,6 +71,10 @@ instance Binary name => Binary (AnnTarget name) where 0 -> liftM NamedTarget $ get bh _ -> liftM ModuleTarget $ get bh +instance NFData name => NFData (AnnTarget name) where + rnf (NamedTarget n) = rnf n + rnf (ModuleTarget m) = rnf m + instance Outputable Annotation where ppr ann = ppr (ann_target ann) ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -167,6 +167,11 @@ instance Binary LeftOrRight where 0 -> return CLeft _ -> return CRight } +instance NFData LeftOrRight where + rnf CLeft = () + rnf CRight = () + + {- ************************************************************************ @@ -529,6 +534,10 @@ instance Binary FunctionOrData where 1 -> return IsData _ -> panic "Binary FunctionOrData" +instance NFData FunctionOrData where + rnf IsFunction = () + rnf IsData = () + {- ************************************************************************ * * @@ -612,6 +621,11 @@ instance Binary CbvMark where 1 -> return MarkedCbv _ -> panic "Invalid binary format" +instance NFData CbvMark where + rnf MarkedCbv = () + rnf NotMarkedCbv = () + + isMarkedCbv :: CbvMark -> Bool isMarkedCbv MarkedCbv = True isMarkedCbv NotMarkedCbv = False @@ -871,6 +885,9 @@ data OverlapMode -- See Note [Rules for instance lookup] in GHC.Core.InstEnv instance Outputable OverlapFlag where ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag) +instance NFData OverlapFlag where + rnf (OverlapFlag mode safe) = rnf mode `seq` rnf safe + instance Outputable OverlapMode where ppr (NoOverlap _) = empty ppr (Overlappable _) = text "[overlappable]" @@ -879,6 +896,14 @@ instance Outputable OverlapMode where ppr (Incoherent _) = text "[incoherent]" ppr (NonCanonical _) = text "[noncanonical]" +instance NFData OverlapMode where + rnf (NoOverlap s) = rnf s + rnf (Overlappable s) = rnf s + rnf (Overlapping s) = rnf s + rnf (Overlaps s) = rnf s + rnf (Incoherent s) = rnf s + rnf (NonCanonical s) = rnf s + instance Binary OverlapMode where put_ bh (NoOverlap s) = putByte bh 0 >> put_ bh s put_ bh (Overlaps s) = putByte bh 1 >> put_ bh s @@ -1032,6 +1057,11 @@ instance Binary TupleSort where 1 -> return UnboxedTuple _ -> return ConstraintTuple +instance NFData TupleSort where + rnf BoxedTuple = () + rnf UnboxedTuple = () + rnf ConstraintTuple = () + tupleSortBoxity :: TupleSort -> Boxity tupleSortBoxity BoxedTuple = Boxed @@ -1860,6 +1890,14 @@ instance Binary Activation where ab <- get bh return (ActiveAfter src ab) +instance NFData Activation where + rnf = \case + AlwaysActive -> () + NeverActive -> () + ActiveBefore src aa -> rnf src `seq` rnf aa + ActiveAfter src ab -> rnf src `seq` rnf ab + FinalActive -> () + instance Outputable RuleMatchInfo where ppr ConLike = text "CONLIKE" ppr FunLike = text "FUNLIKE" @@ -1872,6 +1910,11 @@ instance Binary RuleMatchInfo where if h == 1 then return ConLike else return FunLike +instance NFData RuleMatchInfo where + rnf = \case + ConLike -> () + FunLike -> () + instance Outputable InlineSpec where ppr (Inline src) = text "INLINE" <+> pprWithSourceText src empty ppr (NoInline src) = text "NOINLINE" <+> pprWithSourceText src empty @@ -1906,6 +1949,14 @@ instance Binary InlineSpec where s <- get bh return (Opaque s) +instance NFData InlineSpec where + rnf = \case + Inline s -> rnf s + NoInline s -> rnf s + Inlinable s -> rnf s + Opaque s -> rnf s + NoUserInlinePrag -> () + instance Outputable InlinePragma where ppr = pprInline @@ -1925,6 +1976,9 @@ instance Binary InlinePragma where d <- get bh return (InlinePragma s a b c d) +instance NFData InlinePragma where + rnf (InlinePragma s a b c d) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c `seq` rnf d + -- | Outputs string for pragma name for any of INLINE/INLINABLE/NOINLINE. This -- differs from the Outputable instance for the InlineSpec type where the pragma -- name string as well as the accompanying SourceText (if any) is printed. @@ -2017,6 +2071,13 @@ instance Binary UnfoldingSource where 2 -> return StableSystemSrc _ -> return VanillaSrc +instance NFData UnfoldingSource where + rnf = \case + CompulsorySrc -> () + StableUserSrc -> () + StableSystemSrc -> () + VanillaSrc -> () + instance Outputable UnfoldingSource where ppr CompulsorySrc = text "Compulsory" ppr StableUserSrc = text "StableUser" @@ -2161,6 +2222,19 @@ data TypeOrConstraint = TypeLike | ConstraintLike deriving( Eq, Ord, Data ) +instance Binary TypeOrConstraint where + put_ bh = \case + TypeLike -> putByte bh 0 + ConstraintLike -> putByte bh 1 + get bh = getByte bh >>= \case + 0 -> pure TypeLike + 1 -> pure ConstraintLike + _ -> panic "TypeOrConstraint.get: invalid value" + +instance NFData TypeOrConstraint where + rnf = \case + TypeLike -> () + ConstraintLike -> () {- ********************************************************************* * * @@ -2209,18 +2283,6 @@ instance Outputable (TyConFlavour tc) where go BuiltInTypeFlavour = "built-in type" go PromotedDataConFlavour = "promoted data constructor" -instance NFData tc => NFData (TyConFlavour tc) where - rnf ClassFlavour = () - rnf (TupleFlavour !_) = () - rnf SumFlavour = () - rnf DataTypeFlavour = () - rnf NewtypeFlavour = () - rnf AbstractTypeFlavour = () - rnf (OpenFamilyFlavour !_ mb_tc) = rnf mb_tc - rnf ClosedTypeFamilyFlavour = () - rnf TypeSynonymFlavour = () - rnf BuiltInTypeFlavour = () - rnf PromotedDataConFlavour = () -- | Get the enclosing class TyCon (if there is one) for the given TyConFlavour tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc ===================================== compiler/GHC/Types/CostCentre.hs ===================================== @@ -36,6 +36,7 @@ import GHC.Utils.Outputable import GHC.Types.SrcLoc import GHC.Data.FastString import GHC.Types.CostCentre.State +import Control.DeepSeq import Data.Data @@ -395,6 +396,21 @@ instance Binary CostCentre where -- CostCentre in the original module, it is not used by importing -- modules. +instance NFData CostCentre where + rnf (NormalCC aa ab ac ad) = rnf aa `seq` rnf ab `seq` rnf ac `seq` rnf ad + rnf (AllCafsCC ae ad) = rnf ae `seq` rnf ad + +instance NFData CCFlavour where + rnf CafCC = () + rnf (IndexedCC flav i) = rnf flav `seq` rnf i + +instance NFData IndexedCCFlavour where + rnf ExprCC = () + rnf DeclCC = () + rnf HpcCC = () + rnf LateCC = () + rnf CallerCC = () + getAllCAFsCC :: Module -> (CostCentre, CostCentreStack) getAllCAFsCC this_mod = let ===================================== compiler/GHC/Types/CostCentre/State.hs ===================================== @@ -15,6 +15,7 @@ import GHC.Data.FastString.Env import Data.Data import GHC.Utils.Binary +import Control.DeepSeq -- | Per-module state for tracking cost centre indices. -- @@ -29,6 +30,9 @@ newCostCentreState = CostCentreState emptyFsEnv newtype CostCentreIndex = CostCentreIndex { unCostCentreIndex :: Int } deriving (Eq, Ord, Data, Binary) +instance NFData CostCentreIndex where + rnf (CostCentreIndex i) = rnf i + -- | Get a new index for a given cost centre name. getCCIndex :: FastString -> CostCentreState ===================================== compiler/GHC/Types/ForeignCall.hs ===================================== @@ -30,6 +30,8 @@ import GHC.Types.SourceText ( SourceText, pprWithSourceText ) import Data.Char import Data.Data +import Control.DeepSeq (NFData(..)) + {- ************************************************************************ * * @@ -344,3 +346,31 @@ instance Binary Header where get bh = do s <- get bh h <- get bh return (Header s h) + +instance NFData ForeignCall where + rnf (CCall c) = rnf c + +instance NFData Safety where + rnf PlaySafe = () + rnf PlayInterruptible = () + rnf PlayRisky = () + +instance NFData CCallSpec where + rnf (CCallSpec t c s) = rnf t `seq` rnf c `seq` rnf s + +instance NFData CCallTarget where + rnf (StaticTarget s a b c) = rnf s `seq` rnf a `seq` rnf b `seq` rnf c + rnf DynamicTarget = () + +instance NFData CCallConv where + rnf CCallConv = () + rnf StdCallConv = () + rnf PrimCallConv = () + rnf CApiConv = () + rnf JavaScriptCallConv = () + +instance NFData CType where + rnf (CType s mh fs) = rnf s `seq` rnf mh `seq` rnf fs + +instance NFData Header where + rnf (Header s h) = rnf s `seq` rnf h ===================================== compiler/GHC/Types/GREInfo.hs ===================================== @@ -126,12 +126,6 @@ data GREInfo deriving Data -instance NFData GREInfo where - rnf Vanilla = () - rnf UnboundGRE = () - rnf (IAmTyCon tc) = rnf tc - rnf (IAmConLike info) = rnf info - rnf (IAmRecField info) = rnf info plusGREInfo :: GREInfo -> GREInfo -> GREInfo plusGREInfo Vanilla Vanilla = Vanilla ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -84,6 +84,7 @@ import Data.Char import Data.Data ( Data ) import GHC.Exts( isTrue#, dataToTag#, (<#) ) import Numeric ( fromRat ) +import Control.DeepSeq {- ************************************************************************ @@ -204,6 +205,20 @@ instance Binary LitNumType where h <- getByte bh return (toEnum (fromIntegral h)) +instance NFData LitNumType where + rnf (LitNumBigNat) = () + rnf (LitNumInt) = () + rnf (LitNumInt8) = () + rnf (LitNumInt16) = () + rnf (LitNumInt32) = () + rnf (LitNumInt64) = () + rnf (LitNumWord) = () + rnf (LitNumWord8) = () + rnf (LitNumWord16) = () + rnf (LitNumWord32) = () + rnf (LitNumWord64) = () + + {- Note [BigNum literals] ~~~~~~~~~~~~~~~~~~~~~~ @@ -288,6 +303,16 @@ instance Binary Literal where return (LitNumber nt i) _ -> pprPanic "Binary:Literal" (int (fromIntegral h)) +instance NFData Literal where + rnf (LitChar c) = rnf c + rnf (LitNumber nt i) = rnf nt `seq` rnf i + rnf (LitString s) = rnf s + rnf LitNullAddr = () + rnf (LitFloat r) = rnf r + rnf (LitDouble r) = rnf r + rnf (LitLabel l1 k2) = rnf l1 `seq` rnf k2 + rnf (LitRubbish {}) = () -- LitRubbish is not contained within interface files. + -- See Note [Rubbish literals]. instance Outputable Literal where ppr = pprLiteral id ===================================== compiler/GHC/Types/SourceFile.hs ===================================== @@ -13,6 +13,7 @@ where import GHC.Prelude import GHC.Utils.Binary import GHC.Unit.Types +import Control.DeepSeq {- Note [HscSource types] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -53,6 +54,10 @@ data HsBootOrSig | Hsig -- ^ .hsig file deriving (Eq, Ord, Show) +instance NFData HsBootOrSig where + rnf HsBoot = () + rnf Hsig = () + data HscSource -- | .hs file = HsSrcFile @@ -73,6 +78,10 @@ hscSourceToIsBoot :: HscSource -> IsBootInterface hscSourceToIsBoot HsBootFile = IsBoot hscSourceToIsBoot _ = NotBoot +instance NFData HscSource where + rnf HsSrcFile = () + rnf (HsBootOrSig h) = rnf h + instance Binary HscSource where put_ bh HsSrcFile = putByte bh 0 put_ bh HsBootFile = putByte bh 1 ===================================== compiler/GHC/Types/SrcLoc.hs ===================================== @@ -223,7 +223,8 @@ data RealSrcLoc -- We use 'BufPos' in in GHC.Parser.PostProcess.Haddock to associate Haddock -- comments with parts of the AST using location information (#17544). newtype BufPos = BufPos { bufPos :: Int } - deriving (Eq, Ord, Show, Data) + deriving (Eq, Ord, Show, Data, NFData) + -- | Source Location data SrcLoc @@ -373,11 +374,13 @@ data RealSrcSpan } deriving Eq --- | StringBuffer Source Span data BufSpan = BufSpan { bufSpanStart, bufSpanEnd :: {-# UNPACK #-} !BufPos } deriving (Eq, Ord, Show, Data) +instance NFData BufSpan where + rnf (BufSpan a1 a2) = rnf a1 `seq` rnf a2 + instance Semigroup BufSpan where BufSpan start1 end1 <> BufSpan start2 end2 = BufSpan (min start1 start2) (max end1 end2) @@ -439,8 +442,19 @@ instance ToJson RealSrcSpan where end = JSObject [ ("line", JSInt srcSpanELine), ("column", JSInt srcSpanECol) ] +instance NFData RealSrcSpan where + rnf (RealSrcSpan' file line col endLine endCol) = rnf file `seq` rnf line `seq` rnf col `seq` rnf endLine `seq` rnf endCol + instance NFData SrcSpan where - rnf x = x `seq` () + rnf (RealSrcSpan a1 a2) = rnf a1 `seq` rnf a2 + rnf (UnhelpfulSpan a1) = rnf a1 + +instance NFData UnhelpfulSpanReason where + rnf (UnhelpfulNoLocationInfo) = () + rnf (UnhelpfulWiredIn) = () + rnf (UnhelpfulInteractive) = () + rnf (UnhelpfulGenerated) = () + rnf (UnhelpfulOther a1) = rnf a1 getBufSpan :: SrcSpan -> Strict.Maybe BufSpan getBufSpan (RealSrcSpan _ mbspan) = mbspan ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -132,6 +132,7 @@ import GHC.Utils.Panic import GHC.Hs.Specificity () import Language.Haskell.Syntax.Specificity +import Control.DeepSeq import Data.Data @@ -499,6 +500,12 @@ instance Binary FunTyFlag where 2 -> return FTF_C_T _ -> return FTF_C_C +instance NFData FunTyFlag where + rnf FTF_T_T = () + rnf FTF_T_C = () + rnf FTF_C_T = () + rnf FTF_C_C = () + mkFunTyFlag :: TypeOrConstraint -> TypeOrConstraint -> FunTyFlag mkFunTyFlag TypeLike torc = visArg torc mkFunTyFlag ConstraintLike torc = invisArg torc @@ -734,6 +741,9 @@ instance (Binary tv, Binary vis) => Binary (VarBndr tv vis) where get bh = do { tv <- get bh; vis <- get bh; return (Bndr tv vis) } +instance (NFData tv, NFData vis) => NFData (VarBndr tv vis) where + rnf (Bndr tv vis) = rnf tv `seq` rnf vis + instance NamedThing tv => NamedThing (VarBndr tv flag) where getName (Bndr tv _) = getName tv ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -39,6 +39,7 @@ import Data.List (sortBy, sort, partition) import Data.Set (Set) import qualified Data.Set as Set import Data.Bifunctor +import Control.DeepSeq -- | Dependency information about ALL modules and packages below this one -- in the import hierarchy. This is the serialisable version of `ImportAvails`. @@ -104,6 +105,18 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +instance NFData Dependencies where + rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) + = rnf dmods + `seq` rnf dpkgs + `seq` rnf ppkgs + `seq` rnf hsigms + `seq` rnf tps + `seq` rnf bmods + `seq` rnf orphs + `seq` rnf finsts + `seq` () + -- | Extract information from the rename and typecheck phases to produce -- a dependencies information for the module being compiled. @@ -326,6 +339,13 @@ data Usage -- And of course, for modules that aren't imported directly we don't -- depend on their export lists +instance NFData Usage where + rnf (UsagePackageModule mod hash safe) = rnf mod `seq` rnf hash `seq` rnf safe `seq` () + rnf (UsageHomeModule mod uid hash entities exports safe) = rnf mod `seq` rnf uid `seq` rnf hash `seq` rnf entities `seq` rnf exports `seq` rnf safe `seq` () + rnf (UsageFile file hash label) = rnf file `seq` rnf hash `seq` rnf label `seq` () + rnf (UsageMergedRequirement mod hash) = rnf mod `seq` rnf hash `seq` () + rnf (UsageHomeModuleInterface mod uid hash) = rnf mod `seq` rnf uid `seq` rnf hash `seq` () + instance Binary Usage where put_ bh usg at UsagePackageModule{} = do putByte bh 0 ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -655,57 +655,50 @@ mkIfaceHashCache pairs emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint) emptyIfaceHashCache _occ = Nothing --- Take care, this instance only forces to the degree necessary to --- avoid major space leaks. +-- ModIface is completely forced since it will live in memory for a long time. +-- If forcing it uses a lot of memory, then store less things in ModIface. instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface - { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_ - , mi_exports_, mi_fixities_, mi_warns_, mi_anns_ - , mi_decls_, mi_defaults_, mi_extra_decls_, mi_foreign_, mi_top_env_, mi_insts_ - , mi_fam_insts_, mi_rules_, mi_trust_, mi_trust_pkg_ - , mi_complete_matches_, mi_docs_, mi_final_exts_ - , mi_ext_fields_ }) - = rnf mi_module_ - `seq` rnf mi_sig_of_ - `seq` mi_hsc_src_ - `seq` mi_hi_bytes_ - `seq` mi_deps_ - `seq` mi_exports_ - `seq` mi_fixities_ - `seq` rnf mi_warns_ - `seq` rnf mi_anns_ - `seq` rnf mi_decls_ - `seq` rnf mi_defaults_ - `seq` rnf mi_extra_decls_ - `seq` rnf mi_foreign_ - `seq` rnf mi_top_env_ - `seq` rnf mi_insts_ - `seq` rnf mi_fam_insts_ - `seq` rnf mi_rules_ - `seq` mi_trust_ - `seq` rnf mi_trust_pkg_ - `seq` rnf mi_complete_matches_ - `seq` rnf mi_docs_ - `seq` mi_final_exts_ - `seq` mi_ext_fields_ - `seq` () - -instance NFData (ModIfaceBackend) where - rnf (ModIfaceBackend{ mi_mod_hash - , mi_orphan, mi_finsts, mi_exp_hash - , mi_orphan_hash, mi_decl_warn_fn, mi_export_warn_fn, mi_fix_fn - , mi_hash_fn}) - = rnf mi_mod_hash - `seq` rnf mi_orphan - `seq` rnf mi_finsts - `seq` rnf mi_exp_hash - `seq` rnf mi_orphan_hash - `seq` rnf mi_decl_warn_fn - `seq` rnf mi_export_warn_fn - `seq` rnf mi_fix_fn - `seq` rnf mi_hash_fn + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + `seq` rnf a15 + `seq` rnf a16 + `seq` rnf a17 + `seq` rnf a18 + `seq` rnf a19 + `seq` rnf a20 + `seq` rnf a21 + `seq` rnf a22 + -- IfaceBinHandle + `seq` (a23 :: IfaceBinHandle phase) + `seq` rnf a24 + +instance NFData ModIfaceBackend where + rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + `seq` rnf a6 + `seq` rnf a7 + `seq` rnf a8 + `seq` rnf a9 + `seq` rnf a10 forceModIface :: ModIface -> IO () ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -517,6 +517,9 @@ newtype UnitId = UnitId } deriving (Data) +instance NFData UnitId where + rnf (UnitId fs) = rnf fs `seq` () + instance Binary UnitId where put_ bh (UnitId fs) = put_ bh fs get bh = do fs <- get bh; return (UnitId fs) @@ -704,6 +707,9 @@ data GenWithIsBoot mod = GWIB -- IsBootInterface: this is assumed to perform filtering of non-boot modules, -- e.g. in GHC.Driver.Env.hptModulesBelow +instance NFData mod => NFData (GenWithIsBoot mod) where + rnf (GWIB mod isBoot) = rnf mod `seq` rnf isBoot `seq` () + type ModuleNameWithIsBoot = GenWithIsBoot ModuleName type ModuleWithIsBoot = GenWithIsBoot Module ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,11 +2,11 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where -import Data.Data +import Data.Data (Data) import Data.Eq import Data.Ord import Data.Bool -import Data.Int (Int) +import Prelude import GHC.Data.FastString (FastString) import Control.DeepSeq @@ -134,5 +134,13 @@ data FixityDirection | InfixN deriving (Eq, Data) +instance NFData FixityDirection where + rnf InfixL = () + rnf InfixR = () + rnf InfixN = () + data Fixity = Fixity Int FixityDirection deriving (Eq, Data) + +instance NFData Fixity where + rnf (Fixity i d) = rnf i `seq` rnf d `seq` () ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -79,6 +79,7 @@ import Data.Bool import Data.Char import Prelude (Integer) import Data.Ord (Ord) +import Control.DeepSeq {- ************************************************************************ @@ -98,6 +99,10 @@ isPromoted :: PromotionFlag -> Bool isPromoted IsPromoted = True isPromoted NotPromoted = False +instance NFData PromotionFlag where + rnf NotPromoted = () + rnf IsPromoted = () + {- ************************************************************************ * * ===================================== compiler/Language/Haskell/Syntax/Type.hs-boot ===================================== @@ -4,6 +4,8 @@ import Data.Bool import Data.Eq import Data.Ord +import Control.DeepSeq + {- ************************************************************************ * * @@ -19,5 +21,6 @@ data PromotionFlag instance Eq PromotionFlag instance Ord PromotionFlag +instance NFData PromotionFlag isPromoted :: PromotionFlag -> Bool ===================================== libraries/ghc-boot/GHC/Serialized.hs ===================================== @@ -22,11 +22,15 @@ import Prelude -- See note [Why do we import Prelude here?] import Data.Bits import Data.Word ( Word8 ) import Data.Data +import Control.DeepSeq -- | Represents a serialized value of a particular type. Attempts can be made to deserialize it at certain types data Serialized = Serialized TypeRep [Word8] +instance NFData Serialized where + rnf (Serialized tr ws) = rnf tr `seq` rnf ws + -- | Put a Typeable value that we are able to actually turn into bytes into a 'Serialized' value ready for deserialization later toSerialized :: forall a. Typeable a => (a -> [Word8]) -> a -> Serialized toSerialized serialize what = Serialized (typeOf what) (serialize what) ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -52,7 +52,6 @@ import Data.Map (Map) import qualified Data.Map as Map import qualified Data.Set as Set import GHC -import qualified GHC.Data.Strict as Strict import GHC.Data.BooleanFormula (BooleanFormula) import GHC.Driver.Session (Language) import qualified GHC.LanguageExtensions as LangExt @@ -61,7 +60,7 @@ import GHC.Types.Fixity (Fixity (..)) import GHC.Types.Name (stableNameCmp) import GHC.Types.Name.Occurrence import GHC.Types.Name.Reader (RdrName (..)) -import GHC.Types.SrcLoc (BufPos (..), BufSpan (..), srcSpanToRealSrcSpan) +import GHC.Types.SrcLoc (srcSpanToRealSrcSpan) import GHC.Types.Var (Specificity) import GHC.Utils.Outputable @@ -987,15 +986,6 @@ instance NFData RdrName where rnf (Orig m on) = m `deepseq` on `deepseq` () rnf (Exact n) = rnf n -instance NFData FixityDirection where - rnf InfixL = () - rnf InfixR = () - rnf InfixN = () - -instance NFData Fixity where - rnf (Fixity n dir) = - n `deepseq` dir `deepseq` () - instance NFData (EpAnn NameAnn) where rnf (EpAnn en ann cs) = en `deepseq` ann `deepseq` cs `deepseq` () @@ -1065,15 +1055,6 @@ instance NFData EpaCommentTok where rnf (EpaLineComment s) = rnf s rnf (EpaBlockComment s) = rnf s -instance NFData a => NFData (Strict.Maybe a) where - rnf Strict.Nothing = () - rnf (Strict.Just x) = rnf x - -instance NFData BufSpan where - rnf (BufSpan p1 p2) = p1 `deepseq` p2 `deepseq` () - -instance NFData BufPos where - rnf (BufPos n) = rnf n instance NFData DeltaPos where rnf (SameLine n) = rnf n View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/915a6781cb0c8c7a0c832dcf2a8a769431aa8da0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/915a6781cb0c8c7a0c832dcf2a8a769431aa8da0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/20f17f9f/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 05:47:46 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 13 Mar 2025 01:47:46 -0400 Subject: [Git][ghc/ghc][master] Add interface-stability test for ghc-prim Message-ID: <67d27182b584b_3984194288303234e@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 5 changed files: - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - utils/dump-decls/Main.hs Changes: ===================================== testsuite/tests/interface-stability/README.mkd ===================================== @@ -6,10 +6,19 @@ utility to dump all exported declarations of all exposed modules for the following packages: * `base` + * `ghc-experimental` + * `template-haskell` + * `ghc-prim` These are compared against the expected exports in the test's corresponding `.stdout` file. +Stability expectations vary between these packages: Changes to the +interface of `base` normally need a [CLC proposal](https://github.com/haskell/core-libraries-committee). +The interfaces for the other packages listed are tracked primarily to +prevent _accidental_ changes to them when making changes in +`ghc-internal`, from which they re-export many things. + ## Updating expected output ===================================== testsuite/tests/interface-stability/all.T ===================================== @@ -10,3 +10,4 @@ def check_package(pkg_name): check_package('base') check_package('ghc-experimental') check_package('template-haskell') +check_package('ghc-prim') ===================================== testsuite/tests/interface-stability/ghc-prim-exports.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 ===================================== The diff for this file was not included because it is too large. ===================================== utils/dump-decls/Main.hs ===================================== @@ -71,8 +71,7 @@ ignoredModules = ] where unstableModules = - [ "GHC.Prim" - , "GHC.Conc.POSIX" + [ "GHC.Conc.POSIX" , "GHC.Conc.IO" ] platformDependentModules = View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24d373a69c17d11da42c7fdc93efd4c17bd3f2c7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24d373a69c17d11da42c7fdc93efd4c17bd3f2c7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/b119706e/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 07:42:35 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 13 Mar 2025 03:42:35 -0400 Subject: [Git][ghc/ghc][wip/iface-tests] 25 commits: users guide: Fix typo Message-ID: <67d28c6b15d4_3c909b1770dc675c4@gitlab.mail> Matthew Pickering pushed to branch wip/iface-tests at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 0c22e1c7 by Matthew Pickering at 2025-03-13T07:42:15+00:00 testsuite: Add a performance test for interface file checking This commit adds two tests. * `IfaceRecomp`: Tests the performance of the full recompilation check * `IfaceRecompSrcChanged`: Tests the performance of the recompilation check when the hash of the source file has changed. The IfaceRecompTest.hs file is designed to be "large"-ish in some senses, but the interface file is still not particually large. Some parts of the interface should not be used by the recompilation check: * Core definitions from interface files (`-fwrite-if-simplified-core`) * Haddock docs (`-haddock`) * Extra debugging information about specific flags (`-fwrite-if-self-recomp-flags`) I intend to improve the performance of this test and expand it if necessary in the near future. Fixes #25840 - - - - - 147 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/using-concurrent.rst - libraries/ghc-boot/GHC/Serialized.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - rts/HeapStackCheck.cmm - rts/PrimOps.cmm - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/driver/junit.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/perf/compiler/IfaceRecomp.hs - + testsuite/tests/perf/compiler/IfaceRecomp.stdout - + testsuite/tests/perf/compiler/IfaceRecompSrcChanged.stdout - + testsuite/tests/perf/compiler/IfaceRecompTest.hs - testsuite/tests/perf/compiler/Makefile - testsuite/tests/perf/compiler/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/dump-decls/Main.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5d38d49c9d482eee89459981926bd341703eeaf0...0c22e1c76f0482758f22f9facf1e8c0a04ce9d38 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5d38d49c9d482eee89459981926bd341703eeaf0...0c22e1c76f0482758f22f9facf1e8c0a04ce9d38 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/674e24d1/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 07:51:15 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 13 Mar 2025 03:51:15 -0400 Subject: [Git][ghc/ghc][wip/compress-iface] 7 commits: Add flag to control whether self-recompilation information is written to interface Message-ID: <67d28e733565f_3c909b51aaa467757@gitlab.mail> Matthew Pickering pushed to branch wip/compress-iface at Glasgow Haskell Compiler / GHC Commits: aa1ded09 by Matthew Pickering at 2025-03-05T09:26:00+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - cf497243 by Matthew Pickering at 2025-03-05T09:26:20+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 70b5f1da by Matthew Pickering at 2025-03-05T09:26:20+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 7b6d2bad by Matthew Pickering at 2025-03-05T09:26:20+00:00 WIP: Compress interface files - - - - - e8c53993 by Matthew Pickering at 2025-03-05T09:26:20+00:00 Fix - - - - - 609d0e3d by Matthew Pickering at 2025-03-05T09:26:20+00:00 fix - - - - - 3d8858fb by Matthew Pickering at 2025-03-06T09:53:55+00:00 Load GHCi/UI.hs into multi-repl - - - - - 43 changed files: - compiler/GHC.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/StgToCmm/InfoTableProv.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - + compiler/GHC/Unit/Module/ModIface/SelfRecomp.hs - compiler/GHC/Utils/Binary.hs - + compiler/GHC/Utils/Compress.hs - compiler/ghc.cabal.in - docs/users_guide/phases.rst - ghc/ghc-bin.cabal.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Rules/ToolArgs.hs - hadrian/src/Settings.hs - hadrian/src/Settings/Flavours/GhcInGhci.hs - hadrian/src/Settings/Flavours/Release.hs - m4/fp_find_libzstd.m4 - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/41bd0c91d0fb6345fa780e95d55255f157f9fc05...3d8858fbbc6db6d3e0322a405628654749b475d4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/41bd0c91d0fb6345fa780e95d55255f157f9fc05...3d8858fbbc6db6d3e0322a405628654749b475d4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/7e5ddb74/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 13 07:51:26 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 13 Mar 2025 03:51:26 -0400 Subject: [Git][ghc/ghc][wip/compress-iface] 47 commits: perf: Speed up the bytecode assembler Message-ID: <67d28e7e62899_3c909b51cc786798f@gitlab.mail> Matthew Pickering pushed to branch wip/compress-iface at Glasgow Haskell Compiler / GHC Commits: 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 559b8baf by Matthew Pickering at 2025-03-13T07:43:42+00:00 WIP: Compress interface files - - - - - 267 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm/InfoTableProv.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - + compiler/GHC/Utils/Compress.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/wasm.rst - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Flavours/Release.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Serialized.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - m4/fp_find_libzstd.m4 - rts/HeapStackCheck.cmm - rts/PrimOps.cmm - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/dump-decls/Main.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/jsffi/dyld.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d8858fbbc6db6d3e0322a405628654749b475d4...559b8baf3aed72778f4d4280ab627b97805b29cd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d8858fbbc6db6d3e0322a405628654749b475d4...559b8baf3aed72778f4d4280ab627b97805b29cd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/735eb4c1/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 08:05:53 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 13 Mar 2025 04:05:53 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/refactor-iface Message-ID: <67d291e1b7dc5_3c909b51ebf4734c4@gitlab.mail> Matthew Pickering pushed new branch wip/refactor-iface at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/refactor-iface You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/0af1155f/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 13 08:07:12 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 13 Mar 2025 04:07:12 -0400 Subject: [Git][ghc/ghc][wip/refactor-iface] fix Message-ID: <67d29230368b5_3c909b5228807361d@gitlab.mail> Matthew Pickering pushed to branch wip/refactor-iface at Glasgow Haskell Compiler / GHC Commits: 38a314ed by Matthew Pickering at 2025-03-13T08:07:04+00:00 fix - - - - - 1 changed file: - compiler/GHC.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -100,29 +100,37 @@ module GHC ( findGlobalAnns, mkNamePprCtxForModule, ModIface, - ModIface_( - mi_module, - mi_sig_of, - mi_hsc_src, - mi_hi_bytes, - mi_deps, - mi_exports, - mi_fixities, - mi_warns, - mi_anns, - mi_insts, - mi_fam_insts, - mi_rules, - mi_decls, - mi_top_env, - mi_simplified_core, - mi_trust, - mi_trust_pkg, - mi_complete_matches, - mi_docs, - mi_abi_hashes, - mi_ext_fields - ), + ModIface_( mi_mod_info + , mi_module + , mi_sig_of + , mi_hsc_src + , mi_iface_hash + , mi_deps + , mi_public + , mi_exports + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_defaults + , mi_simplified_core + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_abi_hashes + , mi_ext_fields + , mi_hi_bytes + , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn + ), pattern ModIface, SafeHaskellMode(..), View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/38a314ed9ca22b7af0d3c5c76c93984fa76d71d6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/38a314ed9ca22b7af0d3c5c76c93984fa76d71d6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/b8f7c99f/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 09:03:30 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 13 Mar 2025 05:03:30 -0400 Subject: [Git][ghc/ghc][wip/T24359] Add -Wrule-lhs-equalities warning Message-ID: <67d29f6275f22_3ee337c5c9c94988@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: e5300cce by Simon Peyton Jones at 2025-03-13T10:03:17+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 12 changed files: - compiler/GHC/Core/Rules.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Types/Error/Codes.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/using-warnings.rst - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -1001,17 +1001,17 @@ In short, it is Very Deeply Suspicious for a rule to quantify over a coercion variable. And SpecConstr no longer does so: see Note [SpecConstr and casts] in SpecConstr. -It is, however, OK for a cast to appear in a template. For example - newtype N a = MkN (a,a) -- Axiom ax:N a :: (a,a) ~R N a - f :: N a -> bah - RULE forall b x:b y:b. f @b ((x,y) |> (axN @b)) = ... - -When matching we can just move these casts to the other side: - match (tmpl |> co) tgt --> match tmpl (tgt |> sym co) -See matchTemplateCast. - Wrinkles: +(CT0) It is, however, OK for a cast to appear in a template provided the cast mentions + none of the template variables. For example + newtype N a = MkN (a,a) -- Axiom ax:N a :: (a,a) ~R N a + f :: N a -> bah + RULE forall b x:b y:b. f @b ((x,y) |> (axN @b)) = ... + When matching we can just move these casts to the other side: + match (tmpl |> co) tgt --> match tmpl (tgt |> sym co) + See matchTemplateCast. + (CT1) We need to be careful about scoping, and to match left-to-right, so that we know the substitution [a :-> b] before we meet (co :: (a,a) ~R N a), and so we can apply that substitition @@ -1496,11 +1496,12 @@ matchTemplateCast renv subst e1 co1 e2 mco filterFV (`elemVarSet` rv_tmpls renv) $ -- Check that the coercion does not tyCoFVsOfCo substed_co -- mention any of the template variables = -- This is the good path - -- See Note [Casts in the template] + -- See Note [Casts in the template] wrinkle (CT0) match renv subst e1 e2 (checkReflexiveMCo (mkTransMCoL mco (mkSymCo substed_co))) | otherwise = -- This is the Deeply Suspicious Path + -- See Note [Casts in the template] do { let co2 = case mco of MRefl -> mkRepReflCo (exprType e2) MCo co2 -> co2 ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1080,6 +1080,10 @@ data WarningFlag = | Opt_WarnViewPatternSignatures -- Since 9.12 | Opt_WarnUselessSpecialisations -- Since 9.14 | Opt_WarnDeprecatedPragmas -- Since 9.14 + | Opt_WarnRuleLhsEqualities + -- Since 9.14, scheduled to be removed in 9.18 + -- + -- See Note [Quantifying over equalities in RULES] in GHC.Tc.Gen.Sig deriving (Eq, Ord, Show, Enum, Bounded) -- | Return the names of a WarningFlag @@ -1198,6 +1202,7 @@ warnFlagNames wflag = case wflag of Opt_WarnViewPatternSignatures -> "view-pattern-signatures" :| [] Opt_WarnUselessSpecialisations -> "useless-specialisations" :| ["useless-specializations"] Opt_WarnDeprecatedPragmas -> "deprecated-pragmas" :| [] + Opt_WarnRuleLhsEqualities -> "rule-lhs-equalities" :| [] -- ----------------------------------------------------------------------------- -- Standard sets of warning options @@ -1341,7 +1346,8 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnTypeEqualityOutOfScope, Opt_WarnViewPatternSignatures, Opt_WarnUselessSpecialisations, - Opt_WarnDeprecatedPragmas + Opt_WarnDeprecatedPragmas, + Opt_WarnRuleLhsEqualities ] -- | Things you get with -W ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2360,6 +2360,7 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnViewPatternSignatures -> warnSpec x Opt_WarnUselessSpecialisations -> warnSpec x Opt_WarnDeprecatedPragmas -> warnSpec x + Opt_WarnRuleLhsEqualities -> warnSpec x warningGroupsDeps :: [(Deprecation, FlagSpec WarningGroup)] warningGroupsDeps = map mk warningGroups ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1426,6 +1426,16 @@ instance Diagnostic TcRnMessage where err = case errReason of UnboundVariable uv nis -> pprScopeError uv nis IllegalExpression -> text "Illegal expression:" <+> ppr bad_e + TcRnRuleLhsEqualities ruleName _lhs cts -> mkSimpleDecorated $ + text "Discarding RULE" <+> doubleQuotes (ftext ruleName) <> dot + $$ + hang + (sep [ text "The LHS of this rule gave rise to equality constraints" + , text "that GHC was unable to quantify over:" ] + ) + 4 (pprWithArising $ NE.toList cts) + $$ + text "NB: this warning will become an error starting from GHC 9.18" TcRnDuplicateRoleAnnot list -> mkSimpleDecorated $ hang (text "Duplicate role annotations for" <+> quotes (ppr $ roleAnnotDeclName first_decl) <> colon) @@ -2424,6 +2434,8 @@ instance Diagnostic TcRnMessage where -> ErrorWithoutFlag TcRnIllegalRuleLhs{} -> ErrorWithoutFlag + TcRnRuleLhsEqualities{} + -> WarningWithFlag Opt_WarnRuleLhsEqualities TcRnDuplicateRoleAnnot{} -> ErrorWithoutFlag TcRnDuplicateKindSig{} @@ -3097,6 +3109,8 @@ instance Diagnostic TcRnMessage where -> [suggestExtension LangExt.StandaloneKindSignatures] TcRnIllegalRuleLhs{} -> noHints + TcRnRuleLhsEqualities{} + -> noHints TcRnDuplicateRoleAnnot{} -> noHints TcRnDuplicateKindSig{} ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -3302,9 +3302,21 @@ data TcRnMessage where -} TcRnIllegalRuleLhs :: RuleLhsErrReason - -> FastString -- Rule name - -> LHsExpr GhcRn -- Full expression - -> HsExpr GhcRn -- Bad expression + -> FastString -- ^ Rule name + -> LHsExpr GhcRn -- ^ Full expression + -> HsExpr GhcRn -- ^ Bad expression + -> TcRnMessage + + {-| TcRnRuleLhsEqualities is a warning, controlled by '-Wrule-lhs-equalities', + that is triggered by a RULE whose LHS contains equality constraints + (of a certain form, such as @F a ~ b@ for a type family @F@). + + Test case: typecheck/should_compile/RuleEqs + -} + TcRnRuleLhsEqualities + :: FastString -- ^ rule name + -> LHsExpr GhcRn -- ^ LHS expression + -> NE.NonEmpty Ct -- ^ LHS equality constraints -> TcRnMessage {-| TcRnDuplicateRoleAnnot is an error triggered by two or more role ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -61,6 +61,7 @@ import GHC.Core.Type import GHC.Core.Multiplicity import GHC.Core.Predicate import GHC.Core.TyCo.Rep( mkNakedFunTy ) +import GHC.Core.TyCon( isTypeFamilyTyCon ) import GHC.Types.Var import GHC.Types.Var.Set @@ -81,9 +82,10 @@ import GHC.Utils.Panic import GHC.Data.Bag import GHC.Data.Maybe( orElse, whenIsJust ) -import Data.Maybe( mapMaybe ) -import qualified Data.List.NonEmpty as NE import Control.Monad( unless ) +import Data.Foldable ( toList ) +import qualified Data.List.NonEmpty as NE +import Data.Maybe( mapMaybe ) {- ------------------------------------------------------------- Note [Overview of type signatures] @@ -1278,23 +1280,35 @@ tcRule (HsRule { rd_ext = ext vcat [ ppr id <+> dcolon <+> ppr (idType id) | id <- tpl_ids ] ]) - -- SimplfyRule Plan, step 5 + -- /Temporarily/ deal with the fact that we previously accepted + -- rules that quantify over certain equality constraints. + -- + -- See Note [Quantifying over equalities in RULES]. + ; case allPreviouslyQuantifiableEqualities residual_lhs_wanted of { + Just cts | not (insolubleWC rhs_wanted) + -> do { addDiagnostic $ TcRnRuleLhsEqualities name lhs cts + ; return Nothing } ; + _ -> + + do { -- SimplifyRule Plan, step 5 -- Simplify the LHS and RHS constraints: -- For the LHS constraints we must solve the remaining constraints -- (a) so that we report insoluble ones -- (b) so that we bind any soluble ones - ; (lhs_implic, lhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs + (lhs_implic, lhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs residual_lhs_wanted ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted + ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ Just $ HsRule { rd_ext = ext - , rd_name = rname - , rd_act = act - , rd_bndrs = bndrs { rb_ext = qtkvs ++ tpl_ids } - , rd_lhs = mkHsDictLet lhs_binds lhs' - , rd_rhs = mkHsDictLet rhs_binds rhs' } } + ; return $ Just $ + HsRule { rd_ext = ext + , rd_name = rname + , rd_act = act + , rd_bndrs = bndrs { rb_ext = qtkvs ++ tpl_ids } + , rd_lhs = mkHsDictLet lhs_binds lhs' + , rd_rhs = mkHsDictLet rhs_binds rhs' } } } } {- ******************************************************************************** * * @@ -1453,7 +1467,6 @@ RHS constraints. Actually much of this is done by the on-the-fly constraint solving, so the same order must be observed in tcRule. - Note [RULE quantification over equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ At the moment a RULE never quantifies over an equality; see `rule_quant_ct` @@ -1467,6 +1480,14 @@ in `getRuleQuantCts`. Why not? (b) because if such things end up in 'givens' we get a bogus "inaccessible code" error + * Matching on coercions is Deeply Suspicious. We don't want to generate a + RULE like + forall a (co :: F a ~ Int). + foo (x |> Sym co) = ...co... + because matching on that template, to bind `co`, would require us to + match on the /structure/ of a coercion, which we must never do. + See GHC.Core.Rules Note [Casts in the template] + * Equality constraints are unboxed, and that leads to complications For example equality constraints from the LHS will emit coercion hole Wanteds. These don't have a name, so we can't quantify over them directly. @@ -1595,3 +1616,93 @@ getRuleQuantCts wc = case classifyPredType (ctPred ct) of EqPred {} -> False -- Note [RULE quantification over equalities] _ -> tyCoVarsOfCt ct `disjointVarSet` skol_tvs + +{- Note [Quantifying over equalities in RULES] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Up until version 9.12 (inclusive), GHC would happily quantify over certain Wanted +equalities in the LHS of a RULE. This was incorrect behaviour that led to a RULE +that would never fire, so GHC 9.14 and above no longer allow such RULES. +However, instead of throwing an error, GHC will /temporarily/ emit a warning +and drop the rule instead, in order to ease migration for library maintainers +(NB: this warning is not emitted when the RHS constraints are insoluble; in that +case we simply report those constraints as errors instead). +This warning is scheduled to be turned into an error, and the warning flag +removed (becoming a normal typechecker error), starting from version 9.18. + +The function 'allPreviouslyQuantifiableEqualities' computes the equality +constraints that previous (<= 9.12) versions of GHC accepted quantifying over. + + + Example (test case 'RuleEqs', extracted from the 'mono-traversable' library): + + type family Element mono + type instance Element [a] = a + + class MonoFoldable mono where + otoList :: mono -> [Element mono] + instance MonoFoldable [a] where + otoList = id + + ointercalate :: (MonoFoldable mono, Monoid (Element mono)) + => Element mono -> mono -> Element mono + {-# RULES "ointercalate list" forall x. ointercalate x = Data.List.intercalate x . otoList #-} + + Now, because Data.List.intercalate has the type signature + + forall a. [a] -> [[a]] -> [a] + + typechecking the LHS of this rule would give rise to the Wanted equality + + [W] Element mono ~ [a] + + Due to the type family, GHC 9.12 and below accepted to quantify over this + equality, which would lead to a rule LHS template of the form: + + forall (@mono) (@a) + ($dMonoFoldable :: MonoFoldable mono) + ($dMonoid :: Monoid (Element mono)) + (co :: [a] ~ Element mono) + (x :: [a]). + ointercalate @mono $dMonoFoldable $dMonoid + (x `cast` (Sub co)) + + Matching against this template would match on the structure of a coercion, + which goes against Note [Casts in the template] in GHC.Core.Rules. + In practice, this meant that this RULE would never fire. +-} + +-- | Computes all equality constraints that GHC doesn't accept, but previously +-- did accept (until GHC 9.12 (included)), when deciding what to quantify over +-- in the LHS of a RULE. +-- +-- See Note [Quantifying over equalities in RULES]. +allPreviouslyQuantifiableEqualities :: WantedConstraints -> Maybe (NE.NonEmpty Ct) +allPreviouslyQuantifiableEqualities wc = go emptyVarSet wc + where + go :: TyVarSet -> WantedConstraints -> Maybe (NE.NonEmpty Ct) + go skol_tvs (WC { wc_simple = simples, wc_impl = implics }) + = do { cts1 <- mapM (go_simple skol_tvs) simples + ; cts2 <- concatMapM (go_implic skol_tvs) implics + ; NE.nonEmpty $ toList cts1 ++ toList cts2 } + + go_simple :: TyVarSet -> Ct -> Maybe Ct + go_simple skol_tvs ct + | not (tyCoVarsOfCt ct `disjointVarSet` skol_tvs) + = Nothing + | EqPred _ t1 t2 <- classifyPredType (ctPred ct), ok_eq t1 t2 + = Just ct + | otherwise + = Nothing + + go_implic :: TyVarSet -> Implication -> Maybe [Ct] + go_implic skol_tvs (Implic { ic_skols = skols, ic_wanted = wc }) + = fmap toList $ go (skol_tvs `extendVarSetList` skols) wc + + ok_eq t1 t2 + | t1 `tcEqType` t2 = False + | otherwise = is_fun_app t1 || is_fun_app t2 + + is_fun_app ty -- ty is of form (F tys) where F is a type function + = case tyConAppTyCon_maybe ty of + Just tc -> isTypeFamilyTyCon tc + Nothing -> False ===================================== compiler/GHC/Types/Error/Codes.hs ===================================== @@ -610,6 +610,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "TcRnUnusedVariableInRuleDecl" = 65669 GhcDiagnosticCode "TcRnUnexpectedStandaloneKindSig" = 45906 GhcDiagnosticCode "TcRnIllegalRuleLhs" = 63294 + GhcDiagnosticCode "TcRnRuleLhsEqualities" = 53522 GhcDiagnosticCode "TcRnDuplicateRoleAnnot" = 97170 GhcDiagnosticCode "TcRnDuplicateKindSig" = 43371 GhcDiagnosticCode "TcRnIllegalDerivStrategy" = 87139 ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -25,9 +25,17 @@ Language This deprecation is controlled by the newly introduced ``-Wdeprecated-pragmas`` flag in ``-Wdefault``. -* A new flag, `-Wuseless-specialisations`, controls warnings emitted when GHC +* A new flag, ``-Wuseless-specialisations``, controls warnings emitted when GHC determines that a SPECIALISE pragma would have no effect. +* A new flag, ``-Wrule-lhs-equalities``, controls warnings emitted for RULES + whose left-hand side attempts to quantify over equality constraints that + previous GHC versions accepted quantifying over. GHC will now drop such RULES, + emitting a warning message controlled by this flag. + + This warning is intended to give visibility to the fact that the RULES that + previous GHC versions generated in such circumstances could never fire. + * ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified by `GHC Proposal 516: add warning for incomplete record selectors <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0516-incomplete-record-selectors.rst>`_. Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library. ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -436,6 +436,24 @@ of ``-W(no-)*``. uses multiple comma-separated type signatures (deprecated and scheduled to be removed in GHC 9.18). +.. ghc-flag:: -Wrule-lhs-equalities + :shortdesc: warn about rules whose LHS contains equality constraints + :type: dynamic + :reverse: -Wno-rule-lhs-equalities + :category: + + :since: 9.14 + + :default: on + + When GHC encounters a RULE whose left-hand side gives rise to equality + constraints that previous GHC versions (``<= 9.12``) accepted quantifying + over, GHC will instead drop the rule and emit a warning message, with the + warning message being controlled by this flag. + + This warning is intended to give visibility to the fact that the RULES that + previous GHC versions generated in such circumstances could never fire. + .. ghc-flag:: -Wmissed-specialisations :shortdesc: warn when specialisation of an imported, overloaded function fails. ===================================== testsuite/tests/typecheck/should_compile/RuleEqs.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} + +module RuleEqs where + +import qualified Data.List + +type family Element mono +type instance Element [a] = a + +class MonoFoldable mono where + otoList :: mono -> [Element mono] + +instance MonoFoldable [a] where + otoList = id + +ointercalate :: (MonoFoldable mono, Monoid (Element mono)) + => Element mono + -> mono + -> Element mono +ointercalate x = mconcat . Data.List.intersperse x . otoList +{-# INLINE [0] ointercalate #-} +{-# RULES "ointercalate list" forall x. ointercalate x = Data.List.intercalate x . otoList #-} ===================================== testsuite/tests/typecheck/should_compile/RuleEqs.stderr ===================================== @@ -0,0 +1,7 @@ +RuleEqs.hs:24:11: warning: [GHC-53522] [-Wrule-lhs-equalities (in -Wdefault)] + Discarding RULE "ointercalate list". + The LHS of this rule gave rise to equality constraints + that GHC was unable to quantify over: + [a0] ~ Element mono0 + NB: this warning will become an error starting from GHC 9.18 + ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -739,6 +739,7 @@ test('ExplicitSpecificityA1', normal, compile, ['']) test('ExplicitSpecificityA2', normal, compile, ['']) test('ExplicitSpecificity4', normal, compile, ['']) test('TcSpecPragmas', normal, compile, ['']) +test('RuleEqs', normal, compile, ['']) test('T17775-viewpats-a', normal, compile, ['']) test('T17775-viewpats-b', normal, compile_fail, ['']) test('T17775-viewpats-c', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e5300cce07183d11d961396be48925570e9b6d2f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e5300cce07183d11d961396be48925570e9b6d2f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/33e29772/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 09:51:08 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 13 Mar 2025 05:51:08 -0400 Subject: [Git][ghc/ghc][wip/T24359] Comments Message-ID: <67d2aa8cd10da_3f66863c19b4164b6@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: b8323c5e by Simon Peyton Jones at 2025-03-13T09:50:30+00:00 Comments Finished Sig.hs, but some questions in Binds.hs - - - - - 2 changed files: - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Sig.hs Changes: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -789,20 +789,23 @@ The restrictions are: 4. Unlifted binds may not be recursive. Checked in second clause of ds_val_bind. -Note [Desugaring SPECIALISE pragmas] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Note [Desugaring new-form SPECIALISE pragmas] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +"New-form" SPECIALISE pragmas generate a SpecPragE record in the typechecker, +which is desugared in this module by `dsSpec`. For the context see +Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig + Suppose we have f :: forall p q. (Ord p, Eq q) => p -> q -> q, and a pragma {-# SPECIALISE forall x. f @[a] @[Int] x [3,4] #-} -In `dsSpec` on `SpecPragE`, the SPECIALISE pragma has an expression `the_call` -that desugars to something like - - forall @a (d:Ord a) (x:[a]). - let d2:Ord [a] = $dfOrdList d - d3:Eq [Int] = $dfEqList $dfEqInt - in f @[a] @[Int] d2 d3 x [3,4] +In `dsSpec` the `SpecPragE` will look something like this: + SpecPragE { spe_fn_id = f + , spe_bndrs = @a (d:Ord a) (x:[a]) + , spe_call = let d2:Ord [a] = $dfOrdList d + d3:Eq [Int] = $dfEqList $dfEqInt + in f @[a] @[Int] d2 d3 x [3,4] } We want to get RULE forall a (d2:Ord a) (d3:Eq [Int]) (x:[a]). @@ -814,28 +817,37 @@ We want to get in <f-rhs> @[a] @[Int] d2 d3 x [3,4] Notice that -(SP1) If the expression had a type signature, such as + +(SP1) If the expression in the SPECIALISE pragma had a type signature, such as SPECIALISE f :: Eq b => Int -> b -> b then the desugared expression may have type abstractions and applications "in the way", like this: (/\b. (\d:Eq b). let d1 = $dfOrdInt in f @Int @b d1 d) @b (d2:Eq b) + The lambdas come from the type signature, which is then re-instantiated, + hence the applications of those lambdas. + We use the simple optimiser to simplify this to let { d = d2; d1 = $dfOrdInt } in f @Int @b (d2:Eq b) - Do no inlining in this "simple optimiser" phase: use `simpleOptExprNoInline`. - E.g. we don't want to turn + + Important: do no inlining in this "simple optimiser" phase: + use `simpleOptExprNoInline`. E.g. we don't want to turn let { d1=d; d2=d } in f d1 d2 --> f d d because the latter is harder to match. (SP2) the function `prepareSpecLHS` takes the simplified LHS `core_call` and splits those dictionary bindings into two: - * Bindings like + (SP2a) Bindings like d3:Eq [Int] = $dfEqList $dfEqInt depend only on constants and move to the specialised fuction body. That is crucial -- it makes those specialised methods available in the specialised body. This are the `spec_const_binds`. - * Bindings like + (SP2b) Bindings like + d1 = d + Suprisingly, we want to dis + + (SP2c) Bindings like d2:Ord [a] = $dfOrdList d depend on a locally-quantifed evidence variable `d`. Surprisingly, /we want to drop these bindings entirely!/ @@ -848,6 +860,11 @@ Notice that particular, we can't reliably get a (d:Ord a) dictionary from the supplied (d2:Eq [a]) argument. + Note: because of Note [Fully solving constraints for specialisation] in + GHC.Tc.Gen.Sig, there won't /be/ any such bindings -- they aren't + fully solved. But it earlier iterations there were, and it does no + harm to handle them. + Finally, inside those dictionary bindings we should find the call of the function itself f @[a] @[Int] d2 d3 x [3,4] ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -765,12 +765,15 @@ This is done in three parts. each original Wanted is either fully solved or left untouched. See Note [Fully solving constraints for specialisation]. - (3) Compute the constraints to quantify over, using `getRuleQuantCts`. + (3) Compute the constraints to quantify over, using `getRuleQuantCts` on + the unsolved constraints returned by (2). - (4) Emit the residual (non-quantified) constraints, and wrap the + (4) Emit the residual (non-solved, non-quantified) constraints, and wrap the expression in a let binding for those constraints. - (5) Store all the information in a 'SpecPragE' record, to be consumed + (5) Wrap the call in the combined evidence bindings from steps (2) and (4) + + (6) Store all the information in a 'SpecPragE' record, to be consumed by the desugarer. B. Zonker: `GHC.Tc.Zonk.Type.zonkLTcSpecPrags` @@ -786,7 +789,7 @@ This is done in three parts. (1) Simplify the expression. This is important because a type signature in the expression will have led to type/dictionary abstractions/applications. - Now it should look like + After simplification it should look like let <dict-binds> in f d1 d2 d3 (2) `prepareSpecLHS` identifies the `spec_const_binds`, discards the other @@ -799,23 +802,11 @@ This is done in three parts. Note [Fully solving constraints for specialisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ As far as specialisation is concerned, it is actively harmful to simplify -constraints without fully solving them. Two key examples: - -f :: ∀ a t. (Eq a, ∀x. Eq x => Eq (t x)). t a -> Char -{-# SPECIALISE f @Int #-} - - Typechecking 'f' will result in [W] Eq Int, [W] ∀x. Eq x => Eq (t x). - We absolutely MUST leave the quantified constraint alone, because we want to - quantify over it. If we were to try to simplify it, we would emit an - implication and would thereafter never be able to quantify over the original - quantified constraint. +constraints without /fully/ solving them. Two key examples: - However, we still need to simplify quantified constraints that can be fully - solved from instances, otherwise we would never be able to specialise them - away. Example: {-# SPECIALISE f @a @[] #-}. - -g :: ∀ a. Eq a => a -> Bool -{-# SPECIALISE g @[e] #-} +* Type-class instances + g :: ∀ a. Eq a => a -> Bool + {-# SPECIALISE g @[e] #-} Typechecking 'g' will result in [W] Eq [e]. Were we to simplify this to [W] Eq e, we would have difficulty generating a RULE for the specialisation: @@ -832,10 +823,25 @@ g :: ∀ a. Eq a => a -> Bool can't do anything useful from the knowledge that a dictionary for 'Eq [e]' is constructed from a dictionary for 'Eq e' using the 'Eq' instance for lists. - Note however that it is less important to tackle this problem in the typechecker, - as the desugarer would still be able to generate the correct RULE if we did - simplify 'Eq [e]' to 'Eq e'. See the second bullet point in (SP2) in - Note [Desugaring SPECIALISE pragmas] in GHC.HsToCore.Binds. + We could in principle tackle this problem in the desugarer, by discarding the + evidence for (d :: Eq [e]), and quantifiying over it instead: see the second + bullet point in (SP2) in Note [Desugaring SPECIALISE pragmas] in GHC.HsToCore.Binds. + + BUT that doesn't work for quantified constraints, as we see next. + +* Quantified constraints + f :: ∀ a t. (Eq a, ∀x. Eq x => Eq (t x)). t a -> Char + {-# SPECIALISE f @Int #-} + + Typechecking 'f' will result in [W] Eq Int, [W] ∀x. Eq x => Eq (t x). + We absolutely MUST leave the quantified constraint alone, because we want to + quantify over it. If we were to try to simplify it, we would emit an + implication and would thereafter never be able to quantify over the original + quantified constraint. + + However, we still need to simplify quantified constraints that can be + /fully solved/ from instances, otherwise we would never be able to + specialise them away. Example: {-# SPECIALISE f @a @[] #-}. The conclusion is this: @@ -1030,15 +1036,22 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) solveWanteds spec_e_wanted ; spec_e_wanted <- liftZonkM $ zonkWC spec_e_wanted - -- (3) Compute which constraints to quantify over. + -- (3) Compute which constraints to quantify over, by looking + -- at the unsolved constraints from (2) ; (quant_cands, residual_wc) <- getRuleQuantCts spec_e_wanted - -- (4) Emit the residual constraints (that we are not quantifying over) + -- (4) Emit the residual constraints (i.e. ones that we have + -- not solved in (2) nor quantified in (3) + -- NB: use the same `ev_binds_var` as (2), so the bindings + -- for (2) and (4) are combined ; let tv_bndrs = filter isTyVar rule_bndrs' qevs = map ctEvId (bagToList quant_cands) ; emitResidualConstraints rhs_tclvl skol_info_anon ev_binds_var emptyVarSet tv_bndrs qevs residual_wc + + -- (5) Wrap the call in the combined evidence bindings + -- from steps (2) and (4) ; let lhs_call = mkLHsWrap (WpLet (TcEvBinds ev_binds_var)) tc_spec_e ; ev_binds <- getTcEvBindsMap ev_binds_var @@ -1057,7 +1070,7 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl) , text "ev_binds:" <+> ppr ev_binds ] - -- (5) Store the results in a SpecPragE record, which will be + -- (6) Store the results in a SpecPragE record, which will be -- zonked and then consumed by the desugarer. ; return [SpecPragE { spe_fn_nm = nm View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b8323c5e05bab4712038bdabe8e1eb68ed35f6bf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b8323c5e05bab4712038bdabe8e1eb68ed35f6bf You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/69ae107d/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 11:39:00 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 13 Mar 2025 07:39:00 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/recomp-tests Message-ID: <67d2c3d485a64_186724f196025865@gitlab.mail> Matthew Pickering pushed new branch wip/recomp-tests at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/recomp-tests You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/d7edb288/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 13 12:36:44 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 13 Mar 2025 08:36:44 -0400 Subject: [Git][ghc/ghc][wip/refactor-iface] iface: Store logical parts of ModIface together Message-ID: <67d2d15bb77f9_2b4aa660aa873299@gitlab.mail> Matthew Pickering pushed to branch wip/refactor-iface at Glasgow Haskell Compiler / GHC Commits: 99dca0b9 by Matthew Pickering at 2025-03-13T12:30:27+00:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 - - - - - 17 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - ghc/Main.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -100,29 +100,37 @@ module GHC ( findGlobalAnns, mkNamePprCtxForModule, ModIface, - ModIface_( - mi_module, - mi_sig_of, - mi_hsc_src, - mi_hi_bytes, - mi_deps, - mi_exports, - mi_fixities, - mi_warns, - mi_anns, - mi_insts, - mi_fam_insts, - mi_rules, - mi_decls, - mi_extra_decls, - mi_top_env, - mi_trust, - mi_trust_pkg, - mi_complete_matches, - mi_docs, - mi_final_exts, - mi_ext_fields - ), + ModIface_( mi_mod_info + , mi_module + , mi_sig_of + , mi_hsc_src + , mi_iface_hash + , mi_deps + , mi_public + , mi_exports + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_defaults + , mi_simplified_core + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_abi_hashes + , mi_ext_fields + , mi_hi_bytes + , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn + ), pattern ModIface, SafeHaskellMode(..), ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -844,7 +844,7 @@ hscRecompStatus case recomp_if_result of OutOfDateItem reason mb_checked_iface -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ fmap (mi_iface_hash . mi_final_exts) mb_checked_iface + return $ HscRecompNeeded $ fmap mi_iface_hash mb_checked_iface UpToDateItem checked_iface -> do let lcl_dflags = ms_hspp_opts mod_summary if | not (backendGeneratesCode (backend lcl_dflags)) -> do @@ -862,7 +862,7 @@ hscRecompStatus , xopt LangExt.TemplateHaskell lcl_dflags -> do msg $ needsRecompileBecause THWithJS - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface | otherwise -> do -- Do need linkable @@ -918,7 +918,7 @@ hscRecompStatus return $ HscUpToDate checked_iface $ linkable OutOfDateItem reason _ -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface -- | Check that the .o files produced by compilation are already up-to-date -- or not. @@ -968,10 +968,8 @@ loadByteCode iface mod_sum = do let this_mod = ms_mod mod_sum if_date = fromJust $ ms_iface_date mod_sum - case mi_extra_decls iface of - Just extra_decls -> do - let fi = WholeCoreBindings extra_decls this_mod (ms_location mod_sum) - (mi_foreign iface) + case iface_core_bindings iface (ms_location mod_sum) of + Just fi -> do return (UpToDateItem (Linkable if_date this_mod (NE.singleton (CoreBindings fi)))) _ -> return $ outOfDateItemBecause MissingBytecode Nothing @@ -1019,15 +1017,15 @@ compile_for_interpreter hsc_env use = -- | Assemble 'WholeCoreBindings' if the interface contains Core bindings. iface_core_bindings :: ModIface -> ModLocation -> Maybe WholeCoreBindings iface_core_bindings iface wcb_mod_location = - mi_extra_decls <&> \ wcb_bindings -> + mi_simplified_core <&> \(IfaceSimplifiedCore bindings foreign') -> WholeCoreBindings { - wcb_bindings, + wcb_bindings = bindings, wcb_module = mi_module, wcb_mod_location, - wcb_foreign = mi_foreign + wcb_foreign = foreign' } where - ModIface {mi_module, mi_extra_decls, mi_foreign} = iface + ModIface {mi_module, mi_simplified_core} = iface -- | Return an 'IO' that hydrates Core bindings and compiles them to bytecode if -- the interface contains any, using the supplied type env for typechecking. @@ -1376,7 +1374,7 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do -- dynamic interfaces. Hopefully both the dynamic and the non-dynamic -- interfaces stay in sync... -- - let change = old_iface /= Just (mi_iface_hash (mi_final_exts iface)) + let change = old_iface /= Just (mi_iface_hash iface) let dt = dynamicTooState dflags ===================================== compiler/GHC/HsToCore/Usage.hs ===================================== @@ -185,7 +185,7 @@ mkObjectUsage pit plugins fc hug th_links_needed th_pkgs_needed = do case miface of Nothing -> pprPanic "mkObjectUsage" (ppr m) Just iface -> - return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash (mi_final_exts iface)) + return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash iface) librarySpecToUsage :: LibrarySpec -> IO [Usage] librarySpecToUsage (Objects os) = traverse (fing Nothing) os @@ -278,10 +278,10 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names usg_entities = Map.toList ent_hashs, usg_safe = imp_safe } where - finsts_mod = mi_finsts (mi_final_exts iface) - hash_env = mi_hash_fn (mi_final_exts iface) - mod_hash = mi_mod_hash (mi_final_exts iface) - export_hash | depend_on_exports = Just (mi_exp_hash (mi_final_exts iface)) + finsts_mod = mi_finsts iface + hash_env = mi_hash_fn iface + mod_hash = mi_mod_hash iface + export_hash | depend_on_exports = Just (mi_exp_hash iface) | otherwise = Nothing by_is_safe (ImportedByUser imv) = imv_is_safe imv ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -41,34 +41,28 @@ data IfaceDynFlags = IfaceDynFlags , ifaceCallerCCFilters :: [CallerCcFilter] } -pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc -pprIfaceDynFlags (f, mflags) = - vcat $ - [ text "fingerprint:" <+> (ppr f) - ] - ++ case mflags of - Nothing -> [missingExtraFlagInfo] - Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> - [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) - , text "safe-mode:" <+> ppr a2 - , text "lang:" <+> ppr a3 - , text "exts:" <+> ppr a4 - , text "cpp-options:" - , nest 2 $ ppr a5 - , text "js-options:" - , nest 2 $ ppr a6 - , text "cmm-options:" - , nest 2 $ ppr a7 - , text "paths:" <+> hcat (map text a8) - , text "prof:" <+> ppr a9 - , text "ticky:" - , nest 2 $ vcat (map ppr a10) - , text "codegen:" - , nest 2 $ vcat (map ppr a11) - , text "fat-iface:" <+> ppr a12 - , text "debug-level:" <+> ppr a13 - , text "caller-cc-filters:" <+> ppr a14 - ] +pprIfaceDynFlags :: IfaceDynFlags -> SDoc +pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + vcat [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] missingExtraFlagInfo :: SDoc missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,7 +59,6 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields -import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -74,7 +73,6 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Logger -import GHC.Utils.Fingerprint( Fingerprint ) import GHC.Settings.Constants @@ -644,7 +642,7 @@ loadInterface doc_str mod from & set_mi_fam_insts (panic "No mi_fam_insts in PIT") & set_mi_rules (panic "No mi_rules in PIT") & set_mi_anns (panic "No mi_anns in PIT") - & set_mi_extra_decls (panic "No mi_extra_decls in PIT") + & set_mi_simplified_core (panic "No mi_simplified_core in PIT") bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1083,7 +1081,7 @@ load_dynamic_too :: Logger -> NameCache -> UnitState -> DynFlags load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do read_file logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case Succeeded (dynIface, _) - | mi_mod_hash (mi_final_exts iface) == mi_mod_hash (mi_final_exts dynIface) + | mi_mod_hash iface == mi_mod_hash dynIface -> return (Succeeded ()) | otherwise -> do return $ (Failed $ DynamicHashMismatchError wanted_mod loc) @@ -1174,11 +1172,10 @@ ghcPrimIface & set_mi_exports ghcPrimExports & set_mi_decls [] & set_mi_fixities ghcPrimFixities - & set_mi_final_exts ((mi_final_exts empty_iface) - { mi_fix_fn = mkIfaceFixCache ghcPrimFixities - , mi_decl_warn_fn = mkIfaceDeclWarnCache ghcPrimWarns - , mi_export_warn_fn = mkIfaceExportWarnCache ghcPrimWarns - }) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) + & set_mi_decl_warn_fn (mkIfaceDeclWarnCache ghcPrimWarns) + & set_mi_export_warn_fn (mkIfaceExportWarnCache ghcPrimWarns) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] in GHC.Builtin.Utils & set_mi_warns (toIfaceWarnings ghcPrimWarns) -- See Note [GHC.Prim Deprecations] in GHC.Builtin.Utils @@ -1263,21 +1260,14 @@ pprModIface unit_state iface = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") - <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) - <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) + <+> (if mi_orphan iface then text "[orphan module]" else Outputable.empty) + <+> (if mi_finsts iface then text "[family instance module]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) - , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) - , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat - [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) - , nest 2 (text "opt_hash:" <+> ppr opt_hash) - , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) - , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) - , vcat (map pprUsage usages) - ] - , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) + , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash iface)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash iface)) + , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash iface)) + , withSelfRecomp iface empty ppr + , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "where") , text "exports:" @@ -1288,10 +1278,14 @@ pprModIface unit_state iface , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] - , case mi_extra_decls iface of + , case mi_simplified_core iface of Nothing -> empty - Just eds -> text "extra decls:" - $$ nest 2 (vcat ([ppr bs | bs <- eds])) + Just (IfaceSimplifiedCore eds fs) -> + vcat [ text "extra decls:" + $$ nest 2 (vcat ([ppr bs | bs <- eds])) + , text "foreign stubs:" + $$ nest 2 (ppr fs) + ] , vcat (map ppr (mi_insts iface)) , vcat (map ppr (mi_fam_insts iface)) , vcat (map ppr (mi_rules iface)) @@ -1303,7 +1297,6 @@ pprModIface unit_state iface , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where - exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" @@ -1329,35 +1322,6 @@ pprExport avail@(AvailTC n _) = pp_export [] = Outputable.empty pp_export names = braces (hsep (map ppr names)) -pprUsage :: Usage -> SDoc -pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } - = pprUsageImport mod hash safe -pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name - , usg_mod_hash = hash, usg_safe = safe - , usg_exports = exports, usg_entities = entities } - = pprUsageImport (mkModule unit_id mod_name) hash safe $$ - nest 2 ( - maybe Outputable.empty (\v -> text "exports: " <> ppr v) exports $$ - vcat [ ppr n <+> ppr v | (n,v) <- entities ] - ) -pprUsage usage at UsageFile{} - = hsep [text "addDependentFile", - doubleQuotes (ftext (usg_file_path usage)), - ppr (usg_file_hash usage)] -pprUsage usage at UsageMergedRequirement{} - = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] -pprUsage usage at UsageHomeModuleInterface{} - = hsep [text "implementation", ppr (usg_mod_name usage) - , ppr (usg_unit_id usage) - , ppr (usg_iface_hash usage)] - -pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc -pprUsageImport mod hash safe - = hsep [ text "import", pp_safe, ppr mod - , ppr hash ] - where - pp_safe | safe = text "safe" - | otherwise = text " -/ " pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -88,13 +88,13 @@ import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModSummary import GHC.Unit.Module.Deps -import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign, emptyIfaceForeign) import Data.Function import Data.List ( sortBy ) import Data.Ord import Data.IORef - +import Data.Traversable {- ************************************************************************ @@ -143,11 +143,13 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos stubs foreign_files = updateDecl (mi_decls partial_iface) mb_stg_infos mb_cmm_infos -- See Note [Foreign stubs and TH bytecode linking] - foreign_ <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + mi_simplified_core <- for (mi_simplified_core partial_iface) $ \simpl_core -> do + fs <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + return $ (simpl_core { mi_sc_foreign = fs }) full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env $ set_mi_foreign foreign_ $ set_mi_decls decls partial_iface + addFingerprints hsc_env $ set_mi_simplified_core mi_simplified_core $ set_mi_decls decls partial_iface -- Debug printing let unit_state = hsc_units hsc_env @@ -289,7 +291,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode - -> Maybe ModIfaceSelfRecomp + -> Maybe IfaceSelfRecomp -> Maybe Docs -> ModDetails -> PartialModIface @@ -316,8 +318,8 @@ mkIface_ hsc_env entities = typeEnvElts type_env show_linear_types = xopt LangExt.LinearTypes (hsc_dflags hsc_env) - extra_decls = if gopt Opt_WriteIfSimplifiedCore dflags then Just [ toIfaceTopBind b | b <- core_prog ] - else Nothing + simplified_core = if gopt Opt_WriteIfSimplifiedCore dflags then Just (IfaceSimplifiedCore [ toIfaceTopBind b | b <- core_prog ] emptyIfaceForeign) + else Nothing decls = [ tyThingToIfaceDecl show_linear_types entity | entity <- entities, let name = getName entity, @@ -370,12 +372,12 @@ mkIface_ hsc_env & set_mi_anns annotations & set_mi_top_env rdrs & set_mi_decls decls - & set_mi_extra_decls extra_decls + & set_mi_simplified_core simplified_core & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) & set_mi_docs docs - & set_mi_final_exts () + & set_mi_abi_hashes () & set_mi_ext_fields emptyExtensibleFields & set_mi_hi_bytes PartialIfaceBinHandle ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -88,6 +88,7 @@ import Data.Ord import Data.Containers.ListUtils import Data.Bifunctor import GHC.Iface.Errors.Ppr +import Data.Functor {- ----------------------------------------------- @@ -325,8 +326,8 @@ check_old_iface hsc_env mod_summary maybe_iface maybe_dyn_iface <- liftIO $ loadIface (setDynamicNow dflags) (msDynHiFilePath mod_summary) case maybe_dyn_iface of Nothing -> return $ outOfDateItemBecause MissingDynHiFile Nothing - Just dyn_iface | mi_iface_hash (mi_final_exts dyn_iface) - /= mi_iface_hash (mi_final_exts normal_iface) + Just dyn_iface | mi_iface_hash dyn_iface + /= mi_iface_hash normal_iface -> return $ outOfDateItemBecause MismatchedDynHiFile Nothing Just {} -> return res _ -> return res @@ -382,7 +383,7 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface - -> ModIfaceSelfRecomp + -> IfaceSelfRecomp -> IfG (MaybeValidated ModIface) checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger @@ -435,7 +436,7 @@ checkVersions hsc_env mod_summary iface self_recomp -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins :: Plugins -> IfaceSelfRecomp -> IfG RecompileRequired checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp @@ -528,10 +529,10 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash :: HscEnv -> Module -> IfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + let FingerprintWithValue old_fp old_flags = mi_sr_flag_hash self_recomp (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally if old_fp == new_fp then up_to_date logger (text "Module flags unchanged") @@ -573,7 +574,7 @@ checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkOptimHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env let old_hash = mi_sr_opt_hash iface @@ -589,7 +590,7 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env let old_hash = mi_sr_hpc_hash self_recomp @@ -606,7 +607,7 @@ checkHpcHash hsc_env self_recomp = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures :: HscEnv -> ModSummary -> IfaceSelfRecomp -> IO RecompileRequired checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env @@ -748,7 +749,7 @@ checkModUsage _ UsagePackageModule{ logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChanged (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) -- We only track the ABI hash of package modules, rather than -- individual entity usages, so if the ABI hash changes we must -- recompile. This is safe but may entail more recompilation when @@ -758,7 +759,7 @@ checkModUsage _ UsageMergedRequirement{ usg_mod = mod, usg_mod_hash = old_mod_ha logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedRaw (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name , usg_unit_id = uid , usg_iface_hash = old_mod_hash } = do @@ -766,7 +767,7 @@ checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedIface mod_name - checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash (mi_final_exts iface)) + checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash iface) checkModUsage _ UsageHomeModule{ usg_mod_name = mod_name, @@ -779,9 +780,9 @@ checkModUsage _ UsageHomeModule{ logger <- getLogger needInterface mod $ \iface -> do let - new_mod_hash = mi_mod_hash (mi_final_exts iface) - new_decl_hash = mi_hash_fn (mi_final_exts iface) - new_export_hash = mi_exp_hash (mi_final_exts iface) + new_mod_hash = mi_mod_hash iface + new_decl_hash = mi_hash_fn iface + new_export_hash = mi_exp_hash iface reason = ModuleChanged (moduleName mod) @@ -986,7 +987,7 @@ we use is: -- | Compute the information needed for self-recompilation checking. This -- information can be computed before the backend phase. -mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO IfaceSelfRecomp mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env @@ -1000,10 +1001,10 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do let include_detailed_flags (flag_hash, flags) = if gopt Opt_WriteSelfRecompFlags dflags - then (flag_hash, Just flags) - else (flag_hash, Nothing) + then FingerprintWithValue flag_hash (Just flags) + else FingerprintWithValue flag_hash Nothing - return (ModIfaceSelfRecomp + return (IfaceSelfRecomp { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash @@ -1018,28 +1019,91 @@ addFingerprints :: HscEnv -> PartialModIface -> IO ModIface -addFingerprints hsc_env iface0 - = do - eps <- hscEPS hsc_env - let - decls = mi_decls iface0 - decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings $ mi_warns iface0) - export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ mi_warns iface0) - fix_fn = mkIfaceFixCache (mi_fixities iface0) +addFingerprints hsc_env iface0 = do + (abiHashes, caches, decls_w_hashes) <- addAbiHashes hsc_env (mi_mod_info iface0) (mi_public iface0) (mi_deps iface0) + -- The interface hash depends on: + -- - the ABI hash, plus + -- - the things which can affect whether a module is recompiled + -- - the module level annotations, + -- - deps (home and external packages, dependent files) + iface_hash <- computeFingerprint putNameLiterally + (mi_abi_mod_hash abiHashes, + mi_self_recomp_info iface0, + decls_w_hashes ) + + -- put the declarations in a canonical order, sorted by OccName + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ + [(getOccName d, e) | e@(_, d) <- decls_w_hashes] + + -- This key is safe because mi_extra_decls contains tidied things. + getOcc (IfGblTopBndr b) = getOccName b + getOcc (IfLclTopBndr fs _ _ details) = + case details of + IfRecSelId { ifRecSelFirstCon = first_con } + -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) + _ -> mkVarOccFS (ifLclNameFS fs) + + binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () + binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) + + sorted_extra_decls :: Maybe IfaceSimplifiedCore + sorted_extra_decls = mi_simplified_core iface0 <&> \simpl_core -> + IfaceSimplifiedCore (sortOn binding_key (mi_sc_extra_decls simpl_core)) (mi_sc_foreign simpl_core) + + let final_iface = completePartialModIface iface0 iface_hash + sorted_decls sorted_extra_decls abiHashes caches + -- + return final_iface + + + +-- The ABI hash should depend on everything in IfacePublic +-- This is however computed in a very convoluted way, so be careful your +-- addition ends up in the right place. In essence all this function does is +-- compute a hash of the arguments. +-- +-- Why the convoluted way? Hashing individual declarations allows us to do fine-grained +-- recompilation checking for home package modules, which record precisely what they use +-- from each module. +addAbiHashes :: HscEnv -> IfaceModInfo -> PartialIfacePublic -> Dependencies -> IO (IfaceAbiHashes, IfaceCache, [(Fingerprint, IfaceDecl)]) +addAbiHashes hsc_env info iface_public deps = do + eps <- hscEPS hsc_env + let + -- If you have arrived here by accident then congragulations, + -- you have discovered the ABI hash. Your reward is to update the ABI hash to + -- account for your change to the interface file. Omitting your field using a + -- wildcard may lead to some unfortunate consequences. + + -- MP: TODO: Existing bug where defaults, trust_pkg and complete are not taken into account + -- when computing the ABI hash. + IfacePublic exports fixities warns anns decls _defaults insts fam_insts rules trust _trust_pkg _complete _ _ = iface_public + -- And these fields of deps should be in IfacePublic, but in good time. + Dependencies _ _ _ sig_mods trusted_pkgs boot_mods orph_mods fis_mods = deps + decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings warns) + export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ warns) + fix_fn = mkIfaceFixCache fixities + + this_mod = mi_mod_info_module info + semantic_mod = mi_mod_info_semantic_module info + (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph insts + (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph rules + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph fam_insts + ann_fn = mkIfaceAnnCache anns -- The ABI of a declaration represents everything that is made -- visible about the declaration that a client can depend on. -- see IfaceDeclABI below. - declABI :: IfaceDecl -> IfaceDeclABI + declABI :: IfaceDecl -> IfaceDeclABI -- TODO: I'm not sure if this should be semantic_mod or this_mod. -- See also Note [Identity versus semantic module] - declABI decl = (this_mod, decl, extras) + declABI decl = (this_mod, decl, extras) where extras = declExtras fix_fn ann_fn non_orph_rules non_orph_insts non_orph_fis top_lvl_name_env decl -- This is used for looking up the Name of a default method -- from its OccName. See Note [default method Name] - top_lvl_name_env = + top_lvl_name_env = mkOccEnv [ (nameOccName nm, nm) | IfaceId { ifName = nm } <- decls ] @@ -1047,15 +1111,15 @@ addFingerprints hsc_env iface0 -- This is computed by finding the free external names of each -- declaration, including IfaceDeclExtras (things that a -- declaration implicitly depends on). - edges :: [ Node OccName IfaceDeclABI ] - edges = [ DigraphNode abi (getOccName decl) out + edges :: [ Node OccName IfaceDeclABI ] + edges = [ DigraphNode abi (getOccName decl) out | decl <- decls , let abi = declABI decl , let out = localOccs $ freeNamesDeclABI abi ] - name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) - localOccs = + name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) + localOccs = map (getParent . getOccName) -- NB: names always use semantic module, so -- filtering must be on the semantic module! @@ -1073,17 +1137,17 @@ addFingerprints hsc_env iface0 -- maps OccNames to their parents in the current module. -- e.g. a reference to a constructor must be turned into a reference -- to the TyCon for the purposes of calculating dependencies. - parent_map :: OccEnv OccName - parent_map = foldl' extend emptyOccEnv decls + parent_map :: OccEnv OccName + parent_map = foldl' extend emptyOccEnv decls where extend env d = extendOccEnvList env [ (b,n) | b <- ifaceDeclImplicitBndrs d ] where n = getOccName d -- Strongly-connected groups of declarations, in dependency order - groups :: [SCC IfaceDeclABI] - groups = stronglyConnCompFromEdgedVerticesOrd edges + groups :: [SCC IfaceDeclABI] + groups = stronglyConnCompFromEdgedVerticesOrd edges - global_hash_fn = mkHashFun hsc_env eps + global_hash_fn = mkHashFun hsc_env eps -- How to output Names when generating the data to fingerprint. -- Here we want to output the fingerprint for each top-level @@ -1091,9 +1155,9 @@ addFingerprints hsc_env iface0 -- module. In this way, the fingerprint for a declaration will -- change if the fingerprint for anything it refers to (transitively) -- changes. - mk_put_name :: OccEnv (OccName,Fingerprint) + mk_put_name :: OccEnv (OccName,Fingerprint) -> WriteBinHandle -> Name -> IO () - mk_put_name local_env bh name + mk_put_name local_env bh name | isWiredInName name = putNameLiterally bh name -- wired-in names don't have fingerprints | otherwise @@ -1120,21 +1184,21 @@ addFingerprints hsc_env iface0 -- take a strongly-connected group of declarations and compute -- its fingerprint. - fingerprint_group :: (OccEnv (OccName,Fingerprint), + fingerprint_group :: (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) -> SCC IfaceDeclABI -> IO (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) - fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) - = do let hash_fn = mk_put_name local_env - decl = abiDecl abi + fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) + = do let hash_fn = mk_put_name local_env + decl = abiDecl abi --pprTrace "fingerprinting" (ppr (ifName decl) ) $ do - hash <- computeFingerprint hash_fn abi - env' <- extend_hash_env local_env (hash,decl) - return (env', (hash,decl) : decls_w_hashes) + hash <- computeFingerprint hash_fn abi + env' <- extend_hash_env local_env (hash,decl) + return (env', (hash,decl) : decls_w_hashes) - fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) + fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) = do let stable_abis = sortBy cmp_abiNames abis stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env @@ -1150,33 +1214,27 @@ addFingerprints hsc_env iface0 return (local_env2, pairs ++ decls_w_hashes) -- Make a fingerprint from the ordinal position of a binding in its group. - mkRecFingerprint :: Word64 -> Fingerprint - mkRecFingerprint i = Fingerprint 0 i + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i - bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint - bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. -- - extend_hash_env :: OccEnv (OccName,Fingerprint) + extend_hash_env :: OccEnv (OccName,Fingerprint) -> (Fingerprint,IfaceDecl) -> IO (OccEnv (OccName,Fingerprint)) - extend_hash_env env0 (hash,d) = + extend_hash_env env0 (hash,d) = return (foldr (\(b,fp) env -> extendOccEnv env b (b,fp)) env0 (ifaceDeclFingerprints hash d)) -- - (local_env, decls_w_hashes) <- + (local_env, decls_w_hashes) <- foldM fingerprint_group (emptyOccEnv, []) groups - -- when calculating fingerprints, we always need to use canonical ordering - -- for lists of things. The mi_deps has various lists of modules and - -- suchlike, which are stored in canonical order: - let sorted_deps :: Dependencies - sorted_deps = mi_deps iface0 - -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way -- that changes in orphans get propagated all the way up the @@ -1202,10 +1260,11 @@ addFingerprints hsc_env iface0 -- External. It's true that Home1 will get rebuilt if the orphans -- of External, but we also need to make sure Home2 gets rebuilt -- as well. See #12733 for more details. - let orph_mods - = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] - $ dep_orphs sorted_deps - dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods + let orph_mods_no_self + = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] + $ orph_mods + dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods_no_self + -- Note [Do not update EPS with your own hi-boot] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1216,26 +1275,26 @@ addFingerprints hsc_env iface0 -- instances yourself, no need to consult hs-boot; if you do load the -- interface into EPS, you will see a duplicate orphan instance. - orphan_hash <- computeFingerprint (mk_put_name local_env) + orphan_hash <- computeFingerprint (mk_put_name local_env) (map ifDFun orph_insts, orph_rules, orph_fis) - -- Hash of the transitive things in dependencies - dep_hash <- computeFingerprint putNameLiterally - (dep_sig_mods (mi_deps iface0), - dep_boot_mods (mi_deps iface0), - -- Trusted packages are like orphans - dep_trusted_pkgs (mi_deps iface0), + -- Hash of the transitive things in dependencies + dep_hash <- computeFingerprint putNameLiterally + (sig_mods, + boot_mods, + -- Trusted packages are like orphans + trusted_pkgs, -- See Note [Export hash depends on non-orphan family instances] - dep_finsts (mi_deps iface0) ) + fis_mods ) - -- the export list hash doesn't depend on the fingerprints of - -- the Names it mentions, only the Names themselves, hence putNameLiterally. - export_hash <- computeFingerprint putNameLiterally - (mi_exports iface0, + -- the export list hash doesn't depend on the fingerprints of + -- the Names it mentions, only the Names themselves, hence putNameLiterally. + export_hash <- computeFingerprint putNameLiterally + (exports, orphan_hash, dep_hash, dep_orphan_hashes, - mi_trust iface0) + trust) -- Make sure change of Safe Haskell mode causes recomp. -- Note [Export hash depends on non-orphan family instances] @@ -1266,79 +1325,44 @@ addFingerprints hsc_env iface0 -- (also we didn't store it anywhere!) -- - -- put the declarations in a canonical order, sorted by OccName - let sorted_decls :: [(Fingerprint, IfaceDecl)] - sorted_decls = Map.elems $ Map.fromList $ - [(getOccName d, e) | e@(_, d) <- decls_w_hashes] - - -- This key is safe because mi_extra_decls contains tidied things. - getOcc (IfGblTopBndr b) = getOccName b - getOcc (IfLclTopBndr fs _ _ details) = - case details of - IfRecSelId { ifRecSelFirstCon = first_con } - -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) - _ -> mkVarOccFS (ifLclNameFS fs) - binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () - binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) - - sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - - -- the ABI hash depends on: - -- - decls - -- - export list - -- - orphans - -- - deprecations - -- - flag abi hash - -- - foreign stubs and files - mod_hash <- computeFingerprint putNameLiterally - (map fst sorted_decls, + -- the ABI hash depends on: + -- - decls + -- - export list + -- - orphans + -- - deprecations + -- - flag abi hash + mod_hash <- computeFingerprint putNameLiterally + (sort (map fst decls_w_hashes), export_hash, -- includes orphan_hash - mi_warns iface0, - mi_foreign iface0) - - - -- The interface hash depends on: - -- - the ABI hash, plus - -- - the things which can affect whether a module is recompiled - -- - the module level annotations, - -- - deps (home and external packages, dependent files) - iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_self_recomp_info iface0, - sorted_deps ) + ann_fn AnnModule, + warns) - let - final_iface_exts = ModIfaceBackend - { mi_mod_hash = mod_hash - , mi_iface_hash = iface_hash - , mi_orphan = not ( all ifRuleAuto orph_rules + -- Surely the ABI depends on "module" annotations? + -- Also named defaults + + + + let + final_iface_exts = IfaceAbiHashes + { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts && null orph_fis) - , mi_finsts = not (null (mi_fam_insts iface0)) - , mi_exp_hash = export_hash - , mi_orphan_hash = orphan_hash - , mi_decl_warn_fn = decl_warn_fn - , mi_export_warn_fn = export_warn_fn - , mi_fix_fn = fix_fn - , mi_hash_fn = lookupOccEnv local_env + , mi_abi_finsts = not (null fam_insts) + , mi_abi_exp_hash = export_hash + , mi_abi_orphan_hash = orphan_hash } - final_iface = completePartialModIface iface0 - sorted_decls sorted_extra_decls final_iface_exts - -- - return final_iface + caches = IfaceCache + { mi_cache_decl_warn_fn = decl_warn_fn + , mi_cache_export_warn_fn = export_warn_fn + , mi_cache_fix_fn = fix_fn + , mi_cache_hash_fn = lookupOccEnv local_env + } + return (final_iface_exts, caches, decls_w_hashes) where - this_mod = mi_module iface0 - semantic_mod = mi_semantic_module iface0 - (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) - (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) - (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - ann_fn = mkIfaceAnnCache (mi_anns iface0) - -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the @@ -1378,7 +1402,7 @@ getOrphanHashes hsc_env mods = do get_orph_hash mod = do iface <- initIfaceLoad hsc_env . withIfaceErr ctx $ loadInterface (text "getOrphanHashes") mod ImportBySystem - return (mi_orphan_hash (mi_final_exts iface)) + return (mi_orphan_hash iface) mapM get_orph_hash mods @@ -1531,7 +1555,7 @@ instance Binary IfaceIdExtras where put_ bh (IdExtras fix rules anns)= do { put_ bh fix; put_ bh rules; put_ bh anns } declExtras :: (OccName -> Maybe Fixity) - -> (OccName -> [AnnPayload]) + -> (AnnCacheKey -> [AnnPayload]) -> OccEnv [IfaceRule] -> OccEnv [IfaceClsInst] -> OccEnv [IfaceFamInst] @@ -1546,10 +1570,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl IfaceDataExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n) ++ map ifDFun (lookupOccEnvL inst_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) (map (id_extras . occName . ifConName) (visibleIfConDecls cons)) IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} -> - IfaceClassExtras (fix_fn n) insts (ann_fn n) meths defms + IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms where insts = (map ifDFun $ (concatMap at_extras ats) ++ lookupOccEnvL inst_env n) @@ -1562,17 +1586,16 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl , let dmOcc = mkDefaultMethodOcc (nameOccName bndr) , Just dmName <- [lookupOccEnv dm_env dmOcc] ] IfaceSynonym{} -> IfaceSynonymExtras (fix_fn n) - (ann_fn n) + (ann_fn (AnnOccName n)) IfaceFamily{} -> IfaceFamilyExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) _other -> IfaceOtherDeclExtras where n = getOccName decl - id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn occ) + id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl) - {- Note [default method Name] (see also #15970) ~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1685,20 +1708,25 @@ mkHashFun hsc_env eps name -- just one of the many horrible hacks in the backpack -- implementation. $ loadInterface (text "lookupVers2") mod ImportBySystem - return $ snd (mi_hash_fn (mi_final_exts iface) occ `orElse` + return $ snd (mi_hash_fn iface occ `orElse` pprPanic "lookupVers1" (ppr mod <+> ppr occ)) +data AnnCacheKey = AnnModule | AnnOccName OccName + -- | Creates cached lookup for the 'mi_anns' field of ModIface -- Hackily, we use "module" as the OccName for any module-level annotations -mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload] +mkIfaceAnnCache :: [IfaceAnnotation] -> AnnCacheKey -> [AnnPayload] mkIfaceAnnCache anns - = \n -> lookupOccEnv env n `orElse` [] + = \n -> case n of + AnnModule -> module_anns + AnnOccName occn -> lookupOccEnv env occn `orElse` [] where - pair (IfaceAnnotation target value) = - (case target of - NamedTarget occn -> occn - ModuleTarget _ -> mkVarOccFS (fsLit "module") - , [value]) + (module_anns, occ_anns) = partitionEithers $ map classify anns + classify (IfaceAnnotation target value) = + case target of + NamedTarget occn -> Right (occn, [value]) + ModuleTarget _ -> Left value + -- flipping (++), so the first argument is always short - env = mkOccEnv_C (flip (++)) (map pair anns) + env = mkOccEnv_C (flip (++)) occ_anns ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,5 +1,5 @@ module GHC.Iface.Recomp.Types ( - ModIfaceSelfRecomp(..), + IfaceSelfRecomp(..), IfaceDynFlags(..), pprIfaceDynFlags, missingExtraFlagInfo, @@ -9,7 +9,9 @@ import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable import GHC.Iface.Flags +import GHC.Types.SafeHaskell import GHC.Unit.Module.Deps +import GHC.Unit.Module import GHC.Utils.Binary @@ -59,8 +61,8 @@ proper way. -- itself. -- -- See Note [Self recompilation information in interface files] -data ModIfaceSelfRecomp = - ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint +data IfaceSelfRecomp = + IfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint -- ^ Hash of the .hs source, used for recompilation checking. , mi_sr_usages :: [Usage] -- ^ Usages; kept sorted so that it's easy to decide @@ -69,7 +71,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) + , mi_sr_flag_hash :: !(FingerprintWithValue IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -81,8 +83,8 @@ data ModIfaceSelfRecomp = } -instance Binary ModIfaceSelfRecomp where - put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do +instance Binary IfaceSelfRecomp where + put_ bh (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do put_ bh mi_sr_src_hash lazyPut bh mi_sr_usages put_ bh mi_sr_flag_hash @@ -97,19 +99,58 @@ instance Binary ModIfaceSelfRecomp where opt_hash <- get bh hpc_hash <- get bh plugin_hash <- get bh - return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + return $ IfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } -instance Outputable ModIfaceSelfRecomp where - ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) +instance Outputable IfaceSelfRecomp where + ppr (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash - , text "usages:" <+> ppr (length mi_sr_usages) - , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash + , text "flags:" <+> pprFingerprintWithValue missingExtraFlagInfo (fmap pprIfaceDynFlags mi_sr_flag_hash) , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash + , text "usages:" <+> ppr (map pprUsage mi_sr_usages) ])] -instance NFData ModIfaceSelfRecomp where - rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file +instance NFData IfaceSelfRecomp where + rnf (IfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () + +pprFingerprintWithValue :: SDoc -> FingerprintWithValue SDoc -> SDoc +pprFingerprintWithValue missingInfo (FingerprintWithValue fp mflags) + = vcat $ + [ text "fingerprint:" <+> (ppr fp) + ] + ++ case mflags of + Nothing -> [missingInfo] + Just doc -> [doc] + +pprUsage :: Usage -> SDoc +pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } + = pprUsageImport mod hash safe +pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name + , usg_mod_hash = hash, usg_safe = safe + , usg_exports = exports, usg_entities = entities } + = pprUsageImport (mkModule unit_id mod_name) hash safe $$ + nest 2 ( + maybe empty (\v -> text "exports: " <> ppr v) exports $$ + vcat [ ppr n <+> ppr v | (n,v) <- entities ] + ) +pprUsage usage at UsageFile{} + = hsep [text "addDependentFile", + doubleQuotes (ftext (usg_file_path usage)), + ppr (usg_file_hash usage)] +pprUsage usage at UsageMergedRequirement{} + = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] +pprUsage usage at UsageHomeModuleInterface{} + = hsep [text "implementation", ppr (usg_mod_name usage) + , ppr (usg_unit_id usage) + , ppr (usg_iface_hash usage)] + +pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc +pprUsageImport mod hash safe + = hsep [ text "import", pp_safe, ppr mod + , ppr hash ] + where + pp_safe | safe = text "safe" + | otherwise = text " -/ " \ No newline at end of file ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -183,7 +183,7 @@ lookupFixityRn_help name -- loadInterfaceForName will find B.hi even if B is a hidden module, -- and that's what we want. = do { iface <- loadInterfaceForName doc name - ; let mb_fix = mi_fix_fn (mi_final_exts iface) occ + ; let mb_fix = mi_fix_fn iface occ ; let msg = case mb_fix of Nothing -> text "looking up name" <+> ppr name ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -485,8 +485,8 @@ calculateAvails :: HomeUnit calculateAvails home_unit other_home_units iface mod_safe' want_boot imported_by = let imp_mod = mi_module iface imp_sem_mod= mi_semantic_module iface - orph_iface = mi_orphan (mi_final_exts iface) - has_finsts = mi_finsts (mi_final_exts iface) + orph_iface = mi_orphan iface + has_finsts = mi_finsts iface deps = mi_deps iface trust = getSafeMode $ mi_trust iface trust_pkg = mi_trust_pkg iface @@ -1397,7 +1397,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) _ -> failLookupWith err mk_depr_export_warning gre - = DeprecatedExport name <$> mi_export_warn_fn (mi_final_exts iface) name + = DeprecatedExport name <$> mi_export_warn_fn iface name where name = greName gre ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -539,9 +539,9 @@ warnIfDeclDeprecated gre@(GRE { gre_imp = iss }) lookupImpDeclDeprec :: ModIface -> GlobalRdrElt -> Maybe (WarningTxt GhcRn) lookupImpDeclDeprec iface gre -- Bleat if the thing, or its parent, is warn'd - = mi_decl_warn_fn (mi_final_exts iface) (greOccName gre) `mplus` + = mi_decl_warn_fn iface (greOccName gre) `mplus` case greParent gre of - ParentIs p -> mi_decl_warn_fn (mi_final_exts iface) (nameOccName p) + ParentIs p -> mi_decl_warn_fn iface (nameOccName p) NoParent -> Nothing warnIfExportDeprecated :: GlobalRdrElt -> RnM () @@ -562,7 +562,7 @@ warnIfExportDeprecated gre@(GRE { gre_imp = iss }) process_import_spec is = do let mod = is_mod $ is_decl is iface <- loadInterfaceForModule doc mod - let mb_warn_txt = mi_export_warn_fn (mi_final_exts iface) name + let mb_warn_txt = mi_export_warn_fn iface name return $ (moduleName mod, ) <$> mb_warn_txt ------------------------- ===================================== compiler/GHC/Tc/Instance/Family.hs ===================================== @@ -308,7 +308,7 @@ checkFamInstConsistency directlyImpMods ifc <- modIface mod deps <- dep_finsts . mi_deps <$> modIface mod pure $ - if mi_finsts (mi_final_exts ifc) + if mi_finsts ifc then mod:deps else deps ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -97,7 +97,7 @@ checkHsigDeclM sig_iface sig_thing real_thing = do -- implementation cases. checkBootDeclM Hsig sig_thing real_thing real_fixity <- lookupFixityRn name - let sig_fixity = case mi_fix_fn (mi_final_exts sig_iface) (occName name) of + let sig_fixity = case mi_fix_fn sig_iface (occName name) of Nothing -> defaultFixity Just f -> f when (real_fixity /= sig_fixity) $ @@ -850,7 +850,7 @@ mergeSignatures if outer_mod == mi_module iface -- Don't add ourselves! then tcg_merged tcg_env - else (mi_module iface, mi_mod_hash (mi_final_exts iface)) : tcg_merged tcg_env + else (mi_module iface, mi_mod_hash iface) : tcg_merged tcg_env } -- Note [Signature merging DFuns] ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -1,18 +1,20 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ExplicitNamespaces #-} -- | Dependencies and Usage of a module module GHC.Unit.Module.Deps - ( Dependencies - , mkDependencies - , noDependencies - , dep_direct_mods - , dep_direct_pkgs - , dep_sig_mods - , dep_trusted_pkgs - , dep_orphs - , dep_plugin_pkgs - , dep_finsts - , dep_boot_mods + ( Dependencies(dep_direct_mods + , dep_direct_pkgs + , dep_sig_mods + , dep_trusted_pkgs + , dep_orphs + , dep_plugin_pkgs + , dep_finsts + , dep_boot_mods + , Dependencies) , dep_orphs_update , dep_finsts_update + , mkDependencies + , noDependencies , pprDeps , Usage (..) , ImportAvails (..) @@ -52,38 +54,38 @@ import Control.DeepSeq -- -- See Note [Transitive Information in Dependencies] data Dependencies = Deps - { dep_direct_mods :: Set (UnitId, ModuleNameWithIsBoot) + { dep_direct_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All home-package modules which are directly imported by this one. -- This may include modules from other units when using multiple home units - , dep_direct_pkgs :: Set UnitId + , dep_direct_pkgs_ :: Set UnitId -- ^ All packages directly imported by this module -- I.e. packages to which this module's direct imports belong. -- Does not include other home units when using multiple home units. -- Modules from these units will go in `dep_direct_mods` - , dep_plugin_pkgs :: Set UnitId + , dep_plugin_pkgs_ :: Set UnitId -- ^ All units needed for plugins ------------------------------------ -- Transitive information below here - , dep_sig_mods :: ![ModuleName] + , dep_sig_mods_ :: ![ModuleName] -- ^ Transitive closure of hsig files in the home package - , dep_trusted_pkgs :: Set UnitId + , dep_trusted_pkgs_ :: Set UnitId -- Packages which we are required to trust -- when the module is imported as a safe import -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names - , dep_boot_mods :: Set (UnitId, ModuleNameWithIsBoot) + , dep_boot_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All modules which have boot files below this one, and whether we -- should use the boot file or not. -- This information is only used to populate the eps_is_boot field. -- See Note [Structure of dep_boot_mods] - , dep_orphs :: [Module] + , dep_orphs_ :: [Module] -- ^ Transitive closure of orphan modules (whether -- home or external pkg). -- @@ -93,7 +95,7 @@ data Dependencies = Deps -- which relies on dep_orphs having the complete list!) -- This does NOT include us, unlike 'imp_orphs'. - , dep_finsts :: [Module] + , dep_finsts_ :: [Module] -- ^ Transitive closure of depended upon modules which -- contain family instances (whether home or external). -- This is used by 'checkFamInstConsistency'. This @@ -105,6 +107,26 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +pattern Dependencies :: Set (UnitId, ModuleNameWithIsBoot) + -> Set UnitId + -> Set UnitId + -> [ModuleName] + -> Set UnitId + -> Set (UnitId, ModuleNameWithIsBoot) + -> [Module] + -> [Module] + -> Dependencies +pattern Dependencies {dep_direct_mods, dep_direct_pkgs, dep_plugin_pkgs, dep_sig_mods, dep_trusted_pkgs, dep_boot_mods, dep_orphs, dep_finsts} + <- Deps {dep_direct_mods_ = dep_direct_mods + , dep_direct_pkgs_ = dep_direct_pkgs + , dep_plugin_pkgs_ = dep_plugin_pkgs + , dep_sig_mods_ = dep_sig_mods + , dep_trusted_pkgs_ = dep_trusted_pkgs + , dep_boot_mods_ = dep_boot_mods + , dep_orphs_ = dep_orphs + , dep_finsts_ = dep_finsts} +{-# COMPLETE Dependencies #-} + instance NFData Dependencies where rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) = rnf dmods @@ -158,14 +180,14 @@ mkDependencies home_unit mod imports plugin_mods = sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports - in Deps { dep_direct_mods = direct_mods - , dep_direct_pkgs = direct_pkgs - , dep_plugin_pkgs = plugin_units - , dep_sig_mods = sort sig_mods - , dep_trusted_pkgs = trust_pkgs - , dep_boot_mods = source_mods - , dep_orphs = sortBy stableModuleCmp dep_orphs - , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) + in Deps { dep_direct_mods_ = direct_mods + , dep_direct_pkgs_ = direct_pkgs + , dep_plugin_pkgs_ = plugin_units + , dep_sig_mods_ = sort sig_mods + , dep_trusted_pkgs_ = trust_pkgs + , dep_boot_mods_ = source_mods + , dep_orphs_ = sortBy stableModuleCmp dep_orphs + , dep_finsts_ = sortBy stableModuleCmp (imp_finsts imports) -- sort to get into canonical order -- NB. remember to use lexicographic ordering } @@ -174,14 +196,13 @@ mkDependencies home_unit mod imports plugin_mods = dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_orphs_update deps f = do r <- f (dep_orphs deps) - pure (deps { dep_orphs = sortBy stableModuleCmp r }) + pure (deps { dep_orphs_ = sortBy stableModuleCmp r }) -- | Update module dependencies containing family instances (used by Backpack) dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_finsts_update deps f = do r <- f (dep_finsts deps) - pure (deps { dep_finsts = sortBy stableModuleCmp r }) - + pure (deps { dep_finsts_ = sortBy stableModuleCmp r }) instance Binary Dependencies where put_ bh deps = do put_ bh (dep_direct_mods deps) @@ -201,36 +222,36 @@ instance Binary Dependencies where sms <- get bh os <- get bh fis <- get bh - return (Deps { dep_direct_mods = dms - , dep_direct_pkgs = dps - , dep_plugin_pkgs = plugin_pkgs - , dep_sig_mods = hsigms - , dep_boot_mods = sms - , dep_trusted_pkgs = tps - , dep_orphs = os, - dep_finsts = fis }) + return (Deps { dep_direct_mods_ = dms + , dep_direct_pkgs_ = dps + , dep_plugin_pkgs_ = plugin_pkgs + , dep_sig_mods_ = hsigms + , dep_boot_mods_ = sms + , dep_trusted_pkgs_ = tps + , dep_orphs_ = os, + dep_finsts_ = fis }) noDependencies :: Dependencies noDependencies = Deps - { dep_direct_mods = Set.empty - , dep_direct_pkgs = Set.empty - , dep_plugin_pkgs = Set.empty - , dep_sig_mods = [] - , dep_boot_mods = Set.empty - , dep_trusted_pkgs = Set.empty - , dep_orphs = [] - , dep_finsts = [] + { dep_direct_mods_ = Set.empty + , dep_direct_pkgs_ = Set.empty + , dep_plugin_pkgs_ = Set.empty + , dep_sig_mods_ = [] + , dep_boot_mods_ = Set.empty + , dep_trusted_pkgs_ = Set.empty + , dep_orphs_ = [] + , dep_finsts_ = [] } -- | Pretty-print unit dependencies pprDeps :: UnitState -> Dependencies -> SDoc -pprDeps unit_state (Deps { dep_direct_mods = dmods - , dep_boot_mods = bmods - , dep_plugin_pkgs = plgns - , dep_orphs = orphs - , dep_direct_pkgs = pkgs - , dep_trusted_pkgs = tps - , dep_finsts = finsts +pprDeps unit_state (Deps { dep_direct_mods_ = dmods + , dep_boot_mods_ = bmods + , dep_plugin_pkgs_ = plgns + , dep_orphs_ = orphs + , dep_direct_pkgs_ = pkgs + , dep_trusted_pkgs_ = tps + , dep_finsts_ = finsts }) = pprWithUnitState unit_state $ vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -11,18 +11,20 @@ module GHC.Unit.Module.ModIface ( ModIface , ModIface_ - ( mi_module + ( mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls , mi_defaults - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_top_env , mi_insts , mi_fam_insts @@ -31,12 +33,17 @@ module GHC.Unit.Module.ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn ) , pattern ModIface + , set_mi_mod_info , set_mi_module , set_mi_sig_of , set_mi_hsc_src @@ -52,24 +59,34 @@ module GHC.Unit.Module.ModIface , set_mi_rules , set_mi_decls , set_mi_defaults - , set_mi_extra_decls - , set_mi_foreign + , set_mi_simplified_core , set_mi_top_env , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches , set_mi_docs - , set_mi_final_exts + , set_mi_abi_hashes , set_mi_ext_fields + , set_mi_caches + , set_mi_decl_warn_fn + , set_mi_export_warn_fn + , set_mi_fix_fn + , set_mi_hash_fn , completePartialModIface , IfaceBinHandle(..) , PartialModIface - , ModIfaceBackend (..) - , ModIfaceSelfRecomp (..) + , IfaceAbiHashes (..) + , IfaceSelfRecomp (..) + , IfaceCache (..) + , IfaceSimplifiedCore (..) , withSelfRecomp , IfaceDeclExts - , IfaceBackendExts + , IfaceAbiHashesExts , IfaceExport + , IfacePublic_(..) + , IfacePublic + , PartialIfacePublic + , IfaceModInfo(..) , WhetherHasOrphans , WhetherHasFamInst , IfaceTopEnv (..) @@ -77,6 +94,7 @@ module GHC.Unit.Module.ModIface , mi_boot , mi_fix , mi_semantic_module + , mi_mod_info_semantic_module , mi_free_holes , mi_mnwib , mi_flag_hash @@ -85,6 +103,11 @@ module GHC.Unit.Module.ModIface , mi_plugin_hash , mi_src_hash , mi_usages + , mi_mod_hash + , mi_orphan + , mi_finsts + , mi_exp_hash + , mi_orphan_hash , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,7 +129,7 @@ import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings -import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..)) import GHC.Types.Avail @@ -147,36 +170,36 @@ We can build a full interface file two ways: type PartialModIface = ModIface_ 'ModIfaceCore type ModIface = ModIface_ 'ModIfaceFinal --- | Extends a PartialModIface with information which is either: --- * Computed after codegen --- * Or computed just before writing the iface to disk. (Hashes) --- In order to fully instantiate it. -data ModIfaceBackend = ModIfaceBackend - { mi_mod_hash :: !Fingerprint +type PartialIfacePublic = IfacePublic_ 'ModIfaceCore +type IfacePublic = IfacePublic_ 'ModIfaceFinal + +-- | Extends a PartialModIface with hashes of the ABI. +-- +-- * The mi_mod_hash is the hash of the entire ABI +-- * THe other fields are more specific hashes of parts of the ABI +data IfaceAbiHashes = IfaceAbiHashes + { mi_abi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_orphan :: !WhetherHasOrphans + , mi_abi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans - , mi_finsts :: !WhetherHasFamInst + , mi_abi_finsts :: !WhetherHasFamInst -- ^ Whether this module has family instances. See Note [The type family -- instance consistency story]. - , mi_exp_hash :: !Fingerprint + , mi_abi_exp_hash :: !Fingerprint -- ^ Hash of export list - , mi_orphan_hash :: !Fingerprint + , mi_abi_orphan_hash :: !Fingerprint -- ^ Hash for orphan rules, class and family instances combined + -- NOT transitive + } - -- Cached environments for easy lookup. These are computed (lazily) from - -- other fields and are not put into the interface file. - -- Not really produced by the backend but there is no need to create them - -- any earlier. - , mi_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) +data IfaceCache = IfaceCache + { mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for declaration deprecations - , mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) + , mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for export deprecations - , mi_fix_fn :: !(OccName -> Maybe Fixity) + , mi_cache_fix_fn :: !(OccName -> Maybe Fixity) -- ^ Cached lookup for 'mi_fixities' - , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) + , mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that -- the thing isn't in decls. It's useful to know that when seeing if we are -- up to date wrt. the old interface. The 'OccName' is the parent of the @@ -195,9 +218,9 @@ type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where IfaceDeclExts 'ModIfaceCore = IfaceDecl IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) -type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where - IfaceBackendExts 'ModIfaceCore = () - IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend +type family IfaceAbiHashesExts (phase :: ModIfacePhase) = bk | bk -> phase where + IfaceAbiHashesExts 'ModIfaceCore = () + IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes -- | In-memory byte array representation of a 'ModIface'. -- @@ -212,7 +235,7 @@ data IfaceBinHandle (phase :: ModIfacePhase) where FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp :: ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r withSelfRecomp iface nk jk = case mi_self_recomp_info iface of Nothing -> nk @@ -220,34 +243,80 @@ withSelfRecomp iface nk jk = --- | A 'ModIface' plus a 'ModDetails' summarises everything we know --- about a compiled module. The 'ModIface' is the stuff *before* linking, --- and can be written out to an interface file. The 'ModDetails is after --- linking and can be completely recovered from just the 'ModIface'. +-- | A 'ModIface' summarises everything we know +-- about a compiled module. -- --- When we read an interface file, we also construct a 'ModIface' from it, --- except that we explicitly make the 'mi_decls' and a few other fields empty; --- as when reading we consolidate the declarations etc. into a number of indexed --- maps and environments in the 'ExternalPackageState'. +-- See Note [Structure of ModIface] for information about what belongs in each field. -- --- See Note [Strictness in ModIface] to learn about why some fields are --- strict and others are not. +-- See Note [Strictness in ModIface] to learn about why all the fields are lazy. -- -- See Note [Private fields in ModIface] to learn why we don't export any of the -- fields. data ModIface_ (phase :: ModIfacePhase) = PrivateModIface { - mi_module_ :: !Module, -- ^ Name of the module we are for - mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? + mi_hi_bytes_ :: !(IfaceBinHandle phase), + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. + mi_iface_hash_ :: Fingerprint, -- A hash of the whole interface - mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? + mi_mod_info_ :: IfaceModInfo, + -- ^ Meta information about the module the interface file is for mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) + -- MP: Needs to be refactored (#25844) + + mi_public_ :: IfacePublic_ phase, + -- ^ The parts of interface which are used by other modules when + -- importing this module. The main, original part of an interface. - mi_exports_ :: ![IfaceExport], + + mi_self_recomp_ :: Maybe IfaceSelfRecomp, + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] + + mi_simplified_core_ :: Maybe IfaceSimplifiedCore, + -- ^ The part of the interface written when `-fwrite-if-simplified-core` is enabled. + -- These parts are used to restart bytecode generation. + + mi_docs_ :: Maybe Docs, + -- ^ Docstrings and related data for use by haddock, the ghci + -- @:doc@ command, and other tools. + -- + -- @Just _@ @<=>@ the module was built with @-haddock at . + + mi_top_env_ :: IfaceTopEnv, + -- ^ Just enough information to reconstruct the top level environment in + -- the /original source/ code for this module. which + -- is NOT the same as mi_exports, nor mi_decls (which + -- may contains declarations for things not actually + -- defined by the user). Used for GHCi and for inspecting + -- the contents of modules via the GHC API only. + + mi_ext_fields_ :: ExtensibleFields + -- ^ Additional optional fields, where the Map key represents + -- the field name, resulting in a (size, serialized data) pair. + -- Because the data is intended to be serialized through the + -- internal `Binary` class (increasing compatibility with types + -- using `Name` and `FastString`, such as HIE), this format is + -- chosen over `ByteString`s. + } + +-- | Meta information about the module the interface file is for +data IfaceModInfo = IfaceModInfo { + mi_mod_info_module :: Module, -- ^ Name of the module we are for + mi_mod_info_sig_of :: Maybe Module, -- ^ Are we a sig of another mod? + mi_mod_info_hsc_src :: HscSource -- ^ Boot? Signature? +} + +-- | The public interface of a module which are used by other modules when importing this module. +-- The ABI of a module. +data IfacePublic_ phase = IfacePublic { + mi_exports_ :: [IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things @@ -273,25 +342,10 @@ data ModIface_ (phase :: ModIfacePhase) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], - -- ^ Extra variable definitions which are **NOT** exposed but when - -- combined with mi_decls allows us to restart code generation. - -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - - mi_foreign_ :: !IfaceForeign, - -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. - -- See Note [Foreign stubs and TH bytecode linking] mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: IfaceTopEnv, - -- ^ Just enough information to reconstruct the top level environment in - -- the /original source/ code for this module. which - -- is NOT the same as mi_exports, nor mi_decls (which - -- may contains declarations for things not actually - -- defined by the user). Used for GHCi and for inspecting - -- the contents of modules via the GHC API only. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -299,53 +353,81 @@ data ModIface_ (phase :: ModIfacePhase) mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_trust_ :: !IfaceTrustInfo, + mi_trust_ :: IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg_ :: !Bool, + mi_trust_pkg_ :: Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches_ :: ![IfaceCompleteMatch], + mi_complete_matches_ :: [IfaceCompleteMatch], + -- ^ {-# COMPLETE #-} declarations - mi_docs_ :: !(Maybe Docs), - -- ^ Docstrings and related data for use by haddock, the ghci - -- @:doc@ command, and other tools. - -- - -- @Just _@ @<=>@ the module was built with @-haddock at . + mi_caches_ :: IfaceCache, + -- ^ Cached lookups of some parts of mi_public - mi_final_exts_ :: !(IfaceBackendExts phase), - -- ^ Either `()` or `ModIfaceBackend` for + mi_abi_hashes_ :: (IfaceAbiHashesExts phase) + -- ^ Either `()` or `IfaceAbiHashes` for -- a fully instantiated interface. - - mi_ext_fields_ :: !ExtensibleFields, - -- ^ Additional optional fields, where the Map key represents - -- the field name, resulting in a (size, serialized data) pair. - -- Because the data is intended to be serialized through the - -- internal `Binary` class (increasing compatibility with types - -- using `Name` and `FastString`, such as HIE), this format is - -- chosen over `ByteString`s. - -- - - mi_hi_bytes_ :: !(IfaceBinHandle phase), - -- ^ A serialised in-memory buffer of this 'ModIface'. - -- If this handle is given, we can avoid serialising the 'ModIface' - -- when writing this 'ModIface' to disk, and write this buffer to disk instead. - -- See Note [Sharing of ModIface]. - - mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) - -- ^ Information needed for checking self-recompilation. - -- See Note [Self recompilation information in interface files] - } + -- These fields are hashes of different parts of the public interface. +} + +mkIfacePublic :: [IfaceExport] + -> [IfaceDeclExts 'ModIfaceFinal] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDefault] + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> IfaceAbiHashes + -> IfacePublic +mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes = IfacePublic { + mi_exports_ = exports, + mi_decls_ = decls, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_defaults_ = defaults, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, + mi_cache_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, + mi_cache_fix_fn = mkIfaceFixCache fixities, + mi_cache_hash_fn = mkIfaceHashCache decls + }, + mi_abi_hashes_ = abi_hashes +} + +-- | The information needed to restart bytecode generation. +-- Enabled by `-fwrite-if-simplified-core`. +data IfaceSimplifiedCore = IfaceSimplifiedCore { + mi_sc_extra_decls :: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -- ^ Extra variable definitions which are **NOT** exposed but when + -- combined with mi_decls allows us to restart code generation. + -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] + , mi_sc_foreign :: IfaceForeign + -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. + -- See Note [Foreign stubs and TH bytecode linking] +} -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff - , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module + { ifaceTopExports :: DetOrdAvails -- ^ all top level things in this module, including unexported stuff + , ifaceImports :: [IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where @@ -362,6 +444,35 @@ instance Binary IfaceTopEnv where {- +Note [Structure of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The ModIface structure is divided into several logical parts: + +1. mi_mod_info: Basic module metadata (name, version, etc.) + +2. mi_public: The public interface of the module, which includes: + - Exports, declarations, fixities, warnings, annotations + - Class and type family instances + - Rewrite rules and COMPLETE pragmas + - Safe Haskell and package trust information + - ABI hashes for recompilation checking + +4. mi_self_recomp: Information needed for self-recompilation checking + (see Note [Self recompilation information in interface files]) + +5. mi_simplified_core: Optional simplified Core for bytecode generation + (only present when -fwrite-if-simplified-core is enabled) + +6. mi_docs: Optional documentation (only present when -haddock is enabled) + +7. mi_top_env: Information about the top-level environment of the original source + +8. mi_ext_fields: Additional fields for extensibility + +This structure helps organize the interface data according to its purpose and usage +patterns. Different parts of the compiler use different fields. By separating them +logically in the interface we can arrange to only deserialize the fields that are needed. + Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -371,7 +482,7 @@ The ModIface is the Haskell representation of an interface (.hi) file. that we have just compiled * For packages that we depend on we load the ModIface from disk. -Some fields in the ModIface are deliberately lazy because when we read +All fields in the ModIface are deliberately lazy because when we read an interface file we don't always need all the parts. For example, an interface file contains information about documentation which is often not needed during compilation. This is achieved using the lazyPut/lazyGet pair. @@ -384,23 +495,43 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) -mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ +mi_flag_hash :: ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags) +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint -mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_ mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint -mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_ mi_src_hash :: ModIface_ phase -> Maybe Fingerprint -mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_ mi_usages :: ModIface_ phase -> Maybe [Usage] -mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ +mi_usages = fmap mi_sr_usages . mi_self_recomp_ mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint -mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_ + +-- | Accessor for the module hash of the ABI from a ModIface. +mi_mod_hash :: ModIface -> Fingerprint +mi_mod_hash iface = mi_abi_mod_hash (mi_abi_hashes iface) + +-- | Accessor for whether this module has orphans from a ModIface. +mi_orphan :: ModIface -> WhetherHasOrphans +mi_orphan iface = mi_abi_orphan (mi_abi_hashes iface) + +-- | Accessor for whether this module has family instances from a ModIface. +mi_finsts :: ModIface -> WhetherHasFamInst +mi_finsts iface = mi_abi_finsts (mi_abi_hashes iface) + +-- | Accessor for the hash of the export list from a ModIface. +mi_exp_hash :: ModIface -> Fingerprint +mi_exp_hash iface = mi_abi_exp_hash (mi_abi_hashes iface) + +-- | Accessor for the hash of orphan rules, class and family instances combined from a ModIface. +mi_orphan_hash :: ModIface -> Fingerprint +mi_orphan_hash iface = mi_abi_orphan_hash (mi_abi_hashes iface) -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. @@ -415,16 +546,19 @@ mi_mnwib iface = GWIB (moduleName $ mi_module iface) (mi_boot iface) -- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be -- found, 'defaultFixity' is returned instead. mi_fix :: ModIface -> OccName -> Fixity -mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity +mi_fix iface name = mi_fix_fn iface name `orElse` defaultFixity -- | The semantic module for this interface; e.g., if it's a interface -- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module' -- will be @<A>@. -mi_semantic_module :: ModIface_ a -> Module -mi_semantic_module iface = case mi_sig_of iface of - Nothing -> mi_module iface +mi_mod_info_semantic_module :: IfaceModInfo -> Module +mi_mod_info_semantic_module iface = case mi_mod_info_sig_of iface of + Nothing -> mi_mod_info_module iface Just mod -> mod +mi_semantic_module :: ModIface_ a -> Module +mi_semantic_module iface = mi_mod_info_semantic_module (mi_mod_info iface) + -- | The "precise" free holes, e.g., the signatures that this -- 'ModIface' depends on. mi_free_holes :: ModIface -> UniqDSet ModuleName @@ -455,191 +589,229 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + put_ bh (PrivateModIface + { mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then -- we likely have a good reason, and do not want to reuse -- the byte array. -- See Note [Private fields in ModIface] + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_anns_ = anns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - mi_complete_matches_ = complete_matches, + mi_public_ = public, mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_self_recomp_info_ = self_recomp, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash - }}) = do - put_ bh mod - put_ bh sig_of - put_ bh hsc_src - put_ bh self_recomp - put_ bh mod_hash + mi_self_recomp_ = self_recomp, + mi_simplified_core_ = simplified_core + }) = do + put_ bh mod_info put_ bh iface_hash - put_ bh orphan - put_ bh hasFamInsts lazyPut bh deps - put_ bh exports - put_ bh exp_hash - put_ bh fixities - lazyPut bh warns - lazyPut bh anns - put_ bh decls - put_ bh extra_decls - put_ bh defaults - put_ bh foreign_ - put_ bh insts - put_ bh fam_insts - lazyPut bh rules - put_ bh orphan_hash - put_ bh trust - put_ bh trust_pkg - put_ bh complete_matches + lazyPut bh public lazyPut bh top_env lazyPutMaybe bh docs + lazyPutMaybe bh self_recomp + lazyPutMaybe bh simplified_core get bh = do - mod <- get bh - sig_of <- get bh - hsc_src <- get bh - self_recomp_info <- get bh - mod_hash <- get bh + mod_info <- get bh iface_hash <- get bh - orphan <- get bh - hasFamInsts <- get bh deps <- lazyGet bh - exports <- {-# SCC "bin_exports" #-} get bh - exp_hash <- get bh - fixities <- {-# SCC "bin_fixities" #-} get bh - warns <- {-# SCC "bin_warns" #-} lazyGet bh - anns <- {-# SCC "bin_anns" #-} lazyGet bh - decls <- {-# SCC "bin_tycldecls" #-} get bh - extra_decls <- get bh - defaults <- get bh - foreign_ <- get bh - insts <- {-# SCC "bin_insts" #-} get bh - fam_insts <- {-# SCC "bin_fam_insts" #-} get bh - rules <- {-# SCC "bin_rules" #-} lazyGet bh - orphan_hash <- get bh - trust <- get bh - trust_pkg <- get bh - complete_matches <- get bh + public <- lazyGet bh top_env <- lazyGet bh docs <- lazyGetMaybe bh + self_recomp <- lazyGetMaybe bh + simplified_core <- lazyGetMaybe bh + return (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = - -- We can't populate this field here, as we are - -- missing the 'mi_ext_fields_' field, which is - -- handled in 'getIfaceWithExtFields'. - FullIfaceBinHandle Strict.Nothing, + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_anns_ = anns, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - -- And build the cached values - mi_complete_matches_ = complete_matches, + mi_public_ = public, + mi_simplified_core_ = simplified_core, mi_docs_ = docs, mi_top_env_ = top_env, - mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt - -- with specially when the file is read - mi_self_recomp_info_ = self_recomp_info, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash, - mi_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, - mi_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, - mi_fix_fn = mkIfaceFixCache fixities, - mi_hash_fn = mkIfaceHashCache decls - }}) + mi_self_recomp_ = self_recomp, + -- placeholder because this is dealt + -- with specially when the file is read + mi_ext_fields_ = emptyExtensibleFields, + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + }) + +instance Binary IfaceModInfo where + put_ bh (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) = do + put_ bh mod + put_ bh sig_of + put_ bh hsc_src + get bh = do + mod <- get bh + sig_of <- get bh + hsc_src <- get bh + return (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) + + +instance Binary (IfacePublic_ 'ModIfaceFinal) where + put_ bh (IfacePublic { mi_exports_ = exports + , mi_decls_ = decls + , mi_fixities_ = fixities + , mi_warns_ = warns + , mi_anns_ = anns + , mi_defaults_ = defaults + , mi_insts_ = insts + , mi_fam_insts_ = fam_insts + , mi_rules_ = rules + , mi_trust_ = trust + , mi_trust_pkg_ = trust_pkg + , mi_complete_matches_ = complete_matches + , mi_abi_hashes_ = abi_hashes + }) = do + + lazyPut bh exports + lazyPut bh decls + lazyPut bh fixities + lazyPut bh warns + lazyPut bh anns + lazyPut bh defaults + lazyPut bh insts + lazyPut bh fam_insts + lazyPut bh rules + lazyPut bh trust + lazyPut bh trust_pkg + lazyPut bh complete_matches + lazyPut bh abi_hashes + + get bh = do + exports <- lazyGet bh + decls <- lazyGet bh + fixities <- lazyGet bh + warns <- lazyGet bh + anns <- lazyGet bh + defaults <- lazyGet bh + insts <- lazyGet bh + fam_insts <- lazyGet bh + rules <- lazyGet bh + trust <- lazyGet bh + trust_pkg <- lazyGet bh + complete_matches <- lazyGet bh + abi_hashes <- lazyGet bh + return (mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes) + +instance Binary IfaceAbiHashes where + put_ bh (IfaceAbiHashes { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = orphan + , mi_abi_finsts = hasFamInsts + , mi_abi_exp_hash = exp_hash + , mi_abi_orphan_hash = orphan_hash + }) = do + put_ bh mod_hash + put_ bh orphan + put_ bh hasFamInsts + put_ bh exp_hash + put_ bh orphan_hash + get bh = do + mod_hash <- get bh + orphan <- get bh + hasFamInsts <- get bh + exp_hash <- get bh + orphan_hash <- get bh + return $ IfaceAbiHashes { + mi_abi_mod_hash = mod_hash, + mi_abi_orphan = orphan, + mi_abi_finsts = hasFamInsts, + mi_abi_exp_hash = exp_hash, + mi_abi_orphan_hash = orphan_hash + } + +instance Binary IfaceSimplifiedCore where + put_ bh (IfaceSimplifiedCore eds fs) = do + put_ bh eds + put_ bh fs + + get bh = do + eds <- get bh + fs <- get bh + return (IfaceSimplifiedCore eds fs) emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface - { mi_module_ = mod, - mi_sig_of_ = Nothing, - mi_hsc_src_ = HsSrcFile, + { mi_mod_info_ = emptyIfaceModInfo mod, + mi_iface_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_exports_ = [], - mi_fixities_ = [], - mi_warns_ = IfWarnSome [] [], - mi_anns_ = [], - mi_defaults_ = [], - mi_insts_ = [], - mi_fam_insts_ = [], - mi_rules_ = [], - mi_decls_ = [], - mi_extra_decls_ = Nothing, - mi_foreign_ = emptyIfaceForeign, + mi_public_ = emptyPublicModIface (), + mi_simplified_core_ = Nothing, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_trust_ = noIfaceTrustInfo, - mi_trust_pkg_ = False, - mi_complete_matches_ = [], mi_docs_ = Nothing, - mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields, - mi_self_recomp_info_ = Nothing + mi_self_recomp_ = Nothing, + mi_ext_fields_ = emptyExtensibleFields + } +emptyIfaceModInfo :: Module -> IfaceModInfo +emptyIfaceModInfo mod = IfaceModInfo + { mi_mod_info_module = mod + , mi_mod_info_sig_of = Nothing + , mi_mod_info_hsc_src = HsSrcFile + } + + +emptyPublicModIface :: IfaceAbiHashesExts phase -> IfacePublic_ phase +emptyPublicModIface abi_hashes = IfacePublic + { mi_exports_ = [] + , mi_decls_ = [] + , mi_fixities_ = [] + , mi_warns_ = IfWarnSome [] [] + , mi_anns_ = [] + , mi_defaults_ = [] + , mi_insts_ = [] + , mi_fam_insts_ = [] + , mi_rules_ = [] + , mi_abi_hashes_ = abi_hashes + , mi_trust_ = noIfaceTrustInfo + , mi_trust_pkg_ = False + , mi_caches_ = emptyModIfaceCache + , mi_complete_matches_ = [] + } + +emptyModIfaceCache :: IfaceCache +emptyModIfaceCache = IfaceCache { + mi_cache_decl_warn_fn = emptyIfaceWarnCache, + mi_cache_export_warn_fn = emptyIfaceWarnCache, + mi_cache_fix_fn = emptyIfaceFixCache, + mi_cache_hash_fn = emptyIfaceHashCache +} + +emptyIfaceBackend :: IfaceAbiHashes +emptyIfaceBackend = IfaceAbiHashes + { mi_abi_mod_hash = fingerprint0, + mi_abi_orphan = False, + mi_abi_finsts = False, + mi_abi_exp_hash = fingerprint0, + mi_abi_orphan_hash = fingerprint0 + } + emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls_ = [] - , mi_self_recomp_info_ = Nothing + { mi_public_ = emptyPublicModIface emptyIfaceBackend , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing - , mi_final_exts_ = ModIfaceBackend - { mi_mod_hash = fingerprint0, - mi_iface_hash = fingerprint0, - mi_orphan = False, - mi_finsts = False, - mi_exp_hash = fingerprint0, - mi_orphan_hash = fingerprint0, - mi_decl_warn_fn = emptyIfaceWarnCache, - mi_export_warn_fn = emptyIfaceWarnCache, - mi_fix_fn = emptyIfaceFixCache, - mi_hash_fn = emptyIfaceHashCache } } + } + -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface' mkIfaceHashCache :: [(Fingerprint,IfaceDecl)] @@ -657,11 +829,11 @@ emptyIfaceHashCache _occ = Nothing -- ModIface is completely forced since it will live in memory for a long time. -- If forcing it uses a lot of memory, then store less things in ModIface. -instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) +instance ( NFData (IfaceAbiHashesExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) - = rnf a1 + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = (a1 :: IfaceBinHandle phase) `seq` rnf a2 `seq` rnf a3 `seq` rnf a4 @@ -671,24 +843,27 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 - `seq` rnf a11 - `seq` rnf a12 - `seq` rnf a13 - `seq` rnf a14 - `seq` rnf a15 - `seq` rnf a16 - `seq` rnf a17 - `seq` rnf a18 - `seq` rnf a19 - `seq` rnf a20 - `seq` rnf a21 - `seq` rnf a22 - -- IfaceBinHandle - `seq` (a23 :: IfaceBinHandle phase) - `seq` rnf a24 - -instance NFData ModIfaceBackend where - rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + +instance NFData IfaceModInfo where + rnf (IfaceModInfo a1 a2 a3) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + + +instance NFData IfaceSimplifiedCore where + rnf (IfaceSimplifiedCore eds fs) = rnf eds `seq` rnf fs + +instance NFData IfaceAbiHashes where + rnf (IfaceAbiHashes a1 a2 a3 a4 a5) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + +instance (NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) where + rnf (IfacePublic a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = rnf a1 `seq` rnf a2 `seq` rnf a3 @@ -699,6 +874,18 @@ instance NFData ModIfaceBackend where `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +instance NFData IfaceCache where + rnf (IfaceCache a1 a2 a3 a4) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + forceModIface :: ModIface -> IO () @@ -745,28 +932,38 @@ to serialise the 'ModIface' to disk again. -- | Given a 'PartialModIface', turn it into a 'ModIface' by completing -- missing fields. completePartialModIface :: PartialModIface + -> Fingerprint -> [(Fingerprint, IfaceDecl)] - -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - -> ModIfaceBackend + -> Maybe IfaceSimplifiedCore + -> IfaceAbiHashes + -> IfaceCache -> ModIface -completePartialModIface partial decls extra_decls final_exts = partial - { mi_decls_ = decls - , mi_extra_decls_ = extra_decls - , mi_final_exts_ = final_exts +completePartialModIface partial iface_hash decls extra_decls final_exts cache = partial + { mi_public_ = completePublicModIface decls final_exts cache (mi_public_ partial) + , mi_simplified_core_ = extra_decls , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_iface_hash_ = iface_hash } + where -set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase -set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } - -set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase -set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } +-- | Given a 'PartialIfacePublic', turn it into an 'IfacePublic' by completing +-- missing fields. +completePublicModIface :: [(Fingerprint, IfaceDecl)] + -> IfaceAbiHashes + -> IfaceCache + -> PartialIfacePublic + -> IfacePublic +completePublicModIface decls abi_hashes cache partial = partial + { mi_decls_ = decls + , mi_abi_hashes_ = abi_hashes + , mi_caches_ = cache + } -set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase -set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } +set_mi_mod_info :: IfaceModInfo -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info val iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = val } -set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase -set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } +set_mi_self_recomp :: Maybe IfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -774,59 +971,100 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } +set_mi_public :: (IfacePublic_ phase -> IfacePublic_ phase) -> ModIface_ phase -> ModIface_ phase +set_mi_public f iface = clear_mi_hi_bytes $ iface { mi_public_ = f (mi_public_ iface) } + +set_mi_simplified_core :: Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase +set_mi_simplified_core val iface = clear_mi_hi_bytes $ iface { mi_simplified_core_ = val } + +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +{- Settings for mi_public interface fields -} + set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase -set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } +set_mi_exports val = set_mi_public (\iface -> iface { mi_exports_ = val }) set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase -set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } +set_mi_fixities val = set_mi_public (\iface -> iface { mi_fixities_ = val }) set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase -set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } +set_mi_warns val = set_mi_public (\iface -> iface { mi_warns_ = val }) set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase -set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } +set_mi_anns val = set_mi_public (\iface -> iface { mi_anns_ = val }) set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase -set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } +set_mi_insts val = set_mi_public (\iface -> iface { mi_insts_ = val }) set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase -set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } +set_mi_fam_insts val = set_mi_public (\iface -> iface { mi_fam_insts_ = val }) set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase -set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } +set_mi_rules val = set_mi_public (\iface -> iface { mi_rules_ = val }) set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase -set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } +set_mi_decls val = set_mi_public (\iface -> iface { mi_decls_ = val }) set_mi_defaults :: [IfaceDefault] -> ModIface_ phase -> ModIface_ phase -set_mi_defaults val iface = clear_mi_hi_bytes $ iface { mi_defaults_ = val } - -set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase -set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } - -set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase -set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } - -set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase -set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } +set_mi_defaults val = set_mi_public (\iface -> iface { mi_defaults_ = val }) set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase -set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } +set_mi_trust val = set_mi_public (\iface -> iface { mi_trust_ = val }) set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase -set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } +set_mi_trust_pkg val = set_mi_public (\iface -> iface { mi_trust_pkg_ = val }) set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase -set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } +set_mi_complete_matches val = set_mi_public (\iface -> iface { mi_complete_matches_ = val }) + +set_mi_abi_hashes :: IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_abi_hashes val = set_mi_public (\iface -> iface { mi_abi_hashes_ = val }) + +{- Setters for mi_caches interface fields -} + +set_mi_decl_warn_fn :: (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_decl_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_decl_warn_fn = val } }) + +set_mi_export_warn_fn :: (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_export_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_export_warn_fn = val } }) + +set_mi_fix_fn :: (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase +set_mi_fix_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_fix_fn = val } }) + +set_mi_hash_fn :: (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase +set_mi_hash_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_hash_fn = val } }) + +set_mi_caches :: IfaceCache -> ModIface_ phase -> ModIface_ phase +set_mi_caches val = set_mi_public (\iface -> iface { mi_caches_ = val }) + +{- + +-} + +{- Setters for mi_mod_info interface fields -} + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val = set_mi_mod_info_field (\info -> info { mi_mod_info_module = val }) + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val = set_mi_mod_info_field (\info -> info { mi_mod_info_sig_of = val }) + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val = set_mi_mod_info_field (\info -> info { mi_mod_info_hsc_src = val }) + +-- | Helper function for setting fields in mi_mod_info_ +set_mi_mod_info_field :: (IfaceModInfo -> IfaceModInfo) -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info_field f iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = f (mi_mod_info_ iface) } -set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase -set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } -set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase -set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } -set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase -set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } -- | Invalidate any byte array buffer we might have. clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase @@ -887,18 +1125,20 @@ However, with the pragma, the correct core is generated: -- See Note [Inline Pattern synonym of ModIface] for why we have all these -- inline pragmas. -{-# INLINE ModIface #-} +{-# INLINE mi_mod_info #-} +{-# INLINE mi_iface_hash #-} {-# INLINE mi_module #-} {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} +{-# INLINE mi_public #-} {-# INLINE mi_exports #-} {-# INLINE mi_fixities #-} {-# INLINE mi_warns #-} {-# INLINE mi_anns #-} {-# INLINE mi_decls #-} -{-# INLINE mi_extra_decls #-} -{-# INLINE mi_foreign #-} +{-# INLINE mi_simplified_core #-} +{-# INLINE mi_defaults #-} {-# INLINE mi_top_env #-} {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} @@ -907,32 +1147,62 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} {-# INLINE mi_docs #-} -{-# INLINE mi_final_exts #-} +{-# INLINE mi_abi_hashes #-} {-# INLINE mi_ext_fields #-} {-# INLINE mi_hi_bytes #-} +{-# INLINE mi_self_recomp_info #-} +{-# INLINE mi_fix_fn #-} +{-# INLINE mi_hash_fn #-} +{-# INLINE mi_decl_warn_fn #-} +{-# INLINE mi_export_warn_fn #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> - [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> - [IfaceAnnotation] -> [IfaceDeclExts phase] -> - Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> + IfaceModInfo + -> Module + -> Maybe Module + -> HscSource + -> Fingerprint + -> Dependencies + -> IfacePublic_ phase + -> [IfaceExport] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDeclExts phase] + -> Maybe IfaceSimplifiedCore + -> [IfaceDefault] + -> IfaceTopEnv + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> Maybe Docs + -> IfaceAbiHashesExts phase + -> ExtensibleFields + -> IfaceBinHandle phase + -> Maybe IfaceSelfRecomp + -> (OccName -> Maybe Fixity) + -> (OccName -> Maybe (OccName, Fingerprint)) + -> (OccName -> Maybe (WarningTxt GhcRn)) + -> (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase pattern ModIface - { mi_module + { mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_defaults , mi_top_env , mi_insts @@ -942,33 +1212,45 @@ pattern ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_hash_fn + , mi_decl_warn_fn + , mi_export_warn_fn } <- PrivateModIface - { mi_module_ = mi_module - , mi_sig_of_ = mi_sig_of - , mi_hsc_src_ = mi_hsc_src + { mi_mod_info_ = mi_mod_info at IfaceModInfo { mi_mod_info_module = mi_module + , mi_mod_info_sig_of = mi_sig_of + , mi_mod_info_hsc_src = mi_hsc_src } + , mi_iface_hash_ = mi_iface_hash , mi_deps_ = mi_deps - , mi_exports_ = mi_exports - , mi_fixities_ = mi_fixities - , mi_warns_ = mi_warns - , mi_anns_ = mi_anns - , mi_decls_ = mi_decls - , mi_extra_decls_ = mi_extra_decls - , mi_foreign_ = mi_foreign - , mi_defaults_ = mi_defaults - , mi_top_env_ = mi_top_env - , mi_insts_ = mi_insts - , mi_fam_insts_ = mi_fam_insts - , mi_rules_ = mi_rules - , mi_trust_ = mi_trust - , mi_trust_pkg_ = mi_trust_pkg - , mi_complete_matches_ = mi_complete_matches + , mi_public_ = mi_public at IfacePublic { + mi_exports_ = mi_exports + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_defaults_ = mi_defaults + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mi_decl_warn_fn, + mi_cache_export_warn_fn = mi_export_warn_fn, + mi_cache_fix_fn = mi_fix_fn, + mi_cache_hash_fn = mi_hash_fn + } + , mi_abi_hashes_ = mi_abi_hashes + } , mi_docs_ = mi_docs - , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields , mi_hi_bytes_ = mi_hi_bytes - , mi_self_recomp_info_ = mi_self_recomp_info + , mi_self_recomp_ = mi_self_recomp_info + , mi_simplified_core_ = mi_simplified_core + , mi_top_env_ = mi_top_env } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -107,6 +107,9 @@ module GHC.Utils.Binary simpleBindingNameReader, FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, BinArray, + + -- * FingerprintWithValue + FingerprintWithValue(..) ) where import GHC.Prelude @@ -2088,3 +2091,39 @@ source location as part of a larger structure. instance (Binary v) => Binary (IntMap v) where put_ bh m = put_ bh (IntMap.toAscList m) get bh = IntMap.fromAscList <$> get bh + + +{- +Note [FingerprintWithValue] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +FingerprintWithValue is a wrapper which allows us to store a fingerprint and +optionally the value which was used to create the fingerprint. + +This is useful for storing information in interface files, where we want to +store the fingerprint of the interface file, but also the value which was used +to create the fingerprint (e.g. the DynFlags). + +The wrapper is useful to ensure that the fingerprint can be read quickly without +having to deserialise the value itself. + +-} + +-- | A wrapper which allows us to store a fingerprint and optionally the value which +-- was used to create the fingerprint. +data FingerprintWithValue a = FingerprintWithValue !Fingerprint (Maybe a) + deriving Functor + +instance Binary a => Binary (FingerprintWithValue a) where + put_ bh (FingerprintWithValue fp val) = do + put_ bh fp + lazyPutMaybe bh val + + get bh = do + fp <- get bh + val <- lazyGetMaybe bh + return $ FingerprintWithValue fp val + +instance NFData a => NFData (FingerprintWithValue a) where + rnf (FingerprintWithValue fp mflags) + = rnf fp `seq` rnf mflags `seq` () \ No newline at end of file ===================================== ghc/Main.hs ===================================== @@ -1133,6 +1133,8 @@ abiHash strs = do mods <- mapM find_it strs + -- MP: loadUserInterface is inefficient here since we will never find a cached + -- interface. computeInterface is probably better. let get_iface modl = loadUserInterface NotBoot (text "abiHash") modl ifaces <- initIfaceCheck (text "abiHash") hsc_env $ mapM get_iface mods @@ -1140,7 +1142,7 @@ abiHash strs = do put_ bh hiVersion -- package hashes change when the compiler version changes (for now) -- see #5328 - mapM_ (put_ bh . mi_mod_hash . mi_final_exts) ifaces + mapM_ (put_ bh . mi_mod_hash) ifaces f <- fingerprintBinMem bh putStrLn (showPpr dflags f) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/99dca0b9d01bf833352425c5ca3f16f7df746f56 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/99dca0b9d01bf833352425c5ca3f16f7df746f56 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/690a47f6/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 13:21:07 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 13 Mar 2025 09:21:07 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T25856 Message-ID: <67d2dbc39da18_2b4aaa4841895568@gitlab.mail> Ben Gamari pushed new branch wip/T25856 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25856 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/db0f1c7e/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 13 13:55:18 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 13 Mar 2025 09:55:18 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] Gettting there Message-ID: <67d2e3c69ff31_2b4aa113fa14112681@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: 016bd2bf by Simon Peyton Jones at 2025-03-13T13:55:06+00:00 Gettting there - - - - - 3 changed files: - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Env.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Core.Opt.Simplify.Env ( seArityOpts, seCaseCase, seCaseFolding, seCaseMerge, seCastSwizzle, seDoEtaReduction, seEtaExpand, seFloatEnable, seInline, seNames, seOptCoercionOpts, sePhase, sePlatform, sePreInline, - seRuleOpts, seRules, seUnfoldingOpts, seHasEmptySubst, + seRuleOpts, seRules, seUnfoldingOpts, mkSimplEnv, extendIdSubst, extendCvIdSubst, extendTvSubst, extendCvSubst, zapSubstEnv, setSubstEnv, bumpCaseDepth, @@ -24,6 +24,8 @@ module GHC.Core.Opt.Simplify.Env ( getSimplRules, enterRecGroupRHSs, reSimplifying, + SimplEnvIS, checkSimplEnvIS, pprBadSimplEnvIS, + -- * Substitution results SimplSR(..), mkContEx, substId, lookupRecBndr, @@ -202,6 +204,19 @@ data SimplEnv -- See Note [Inline depth] } +type SimplEnvIS = SimplEnv + -- Invariant: the substitution is empty + -- We want this SimplEnv for its InScopeSet and flags + +checkSimplEnvIS :: SimplEnvIS -> Bool +-- Check the invariant for SimplEnvIS +checkSimplEnvIS (SimplEnv { seIdSubst = id_env, seTvSubst = tv_env, seCvSubst = cv_env }) + = isEmptyVarEnv id_env && isEmptyVarEnv tv_env && isEmptyVarEnv cv_env + +pprBadSimplEnvIS :: SimplEnvIS -> SDoc +-- Print a SimplEnv that fails checkSimplEnvIS +pprBadSimplEnvIS env = ppr (getFullSubst (seInScope env) env) + seArityOpts :: SimplEnv -> ArityOpts seArityOpts env = sm_arity_opts (seMode env) @@ -253,10 +268,6 @@ seRules env = sm_rules (seMode env) seUnfoldingOpts :: SimplEnv -> UnfoldingOpts seUnfoldingOpts env = sm_uf_opts (seMode env) -seHasEmptySubst :: SimplEnv -> Bool -seHasEmptySubst (SimplEnv { seIdSubst = id_env, seTvSubst = tv_env, seCvSubst = cv_env }) - = isEmptyVarEnv id_env && isEmptyVarEnv tv_env && isEmptyVarEnv cv_env - -- See Note [The environments of the Simplify pass] data SimplMode = SimplMode -- See comments in GHC.Core.Opt.Simplify.Monad { sm_phase :: !CompilerPhase @@ -1267,8 +1278,8 @@ getTCvSubst :: SimplEnv -> Subst getTCvSubst (SimplEnv { seInScope = in_scope, seTvSubst = tv_env, seCvSubst = cv_env }) = mkSubst in_scope emptyVarEnv tv_env cv_env -getFullSubst :: SimplEnv -> Subst -getFullSubst (SimplEnv { seInScope = in_scope, seIdSubst = id_env, seTvSubst = tv_env, seCvSubst = cv_env }) +getFullSubst :: InScopeSet -> SimplEnv -> Subst +getFullSubst in_scope (SimplEnv { seIdSubst = id_env, seTvSubst = tv_env, seCvSubst = cv_env }) = mk_full_subst in_scope tv_env cv_env id_env mk_full_subst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> SimplIdSubst -> Subst ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -69,7 +69,6 @@ import GHC.Utils.Misc import Control.Monad import Data.List.NonEmpty (NonEmpty (..)) -import Data.Maybe {- The guts of the simplifier is in this module, but the driver loop for @@ -1520,17 +1519,15 @@ simplTick env tickish expr cont ************************************************************************ -} -type SimplEnvIS = SimplEnv --- Invariant: the substition is empty - rebuild :: SimplEnv -> OutExpr -> SimplCont -> SimplM (SimplFloats, OutExpr) --- At this point the substitution in the SimplEnv is empty. --- Only the in-scope set matters, plus the flags +-- At this point the substitution in the SimplEnv is irrelevant; +-- only the in-scope set matters, plus the flags. +-- So zap it before calling `rebuild_go` rebuild env expr cont = rebuild_go (zapSubstEnv env) expr cont rebuild_go :: SimplEnvIS -> OutExpr -> SimplCont -> SimplM (SimplFloats, OutExpr) rebuild_go env expr cont - = assertPpr (seHasEmptySubst env) (ppr (getFullSubst env) $$ ppr expr) $ + = assertPpr (checkSimplEnvIS env) (pprBadSimplEnvIS env) $ case cont of Stop {} -> return (emptyFloats env, expr) TickIt t cont -> rebuild_go env (mkTick t expr) cont @@ -1667,7 +1664,7 @@ on each successive composition -- that's at least quadratic. So: -} -optOutCoercion :: SimplEnv -> OutCoercion -> Bool -> OutCoercion +optOutCoercion :: SimplEnvIS -> OutCoercion -> Bool -> OutCoercion -- See Note [Avoid re-simplifying coercions] optOutCoercion env co already_optimised | already_optimised = co -- See Note [Avoid re-simplifying coercions] @@ -1717,7 +1714,7 @@ simplCast env body co0 cont0 , sc_dup = dup, sc_cont = tail , sc_hole_ty = fun_ty }) | not opt -- pushCoValArg duplicates the coercion, so optimise first - = addCoerce (optOutCoercion env co opt) True cont + = addCoerce (optOutCoercion (zapSubstEnv env) co opt) True cont | Just (m_co1, m_co2) <- pushCoValArg co , fixed_rep m_co1 @@ -1837,9 +1834,9 @@ simpl_lam env bndr body (ApplyToVal { sc_arg = arg, sc_env = arg_se -- But fun_ty is an OutType, so is fully substituted ; if | Just env' <- let res = preInlineUnconditionally env NotTopLevel bndr arg arg_se - in pprTrace "simpl_lam" - (vcat [ ppr bndr, ppr arg, ppr (seIdSubst arg_se) - , ppr (isJust res) ]) $ + in -- pprTrace "simpl_lam" + -- (vcat [ ppr bndr, ppr arg, ppr (seIdSubst arg_se) + -- , ppr (isJust res) ]) $ res , not (needsCaseBindingL arg_levity arg) , not ( isSimplified dup && @@ -1851,8 +1848,7 @@ simpl_lam env bndr body (ApplyToVal { sc_arg = arg, sc_env = arg_se tick (PreInlineUnconditionally bndr) ; simplLam env' body cont } - | pprTrace "simpl_lam2" (ppr arg) $ - isSimplified dup -- Don't re-simplify if we've simplified it once + | isSimplified dup -- Don't re-simplify if we've simplified it once -- Including don't preInlineUnconditionally -- See Note [Avoiding simplifying repeatedly] -> completeBindX env from_what bndr arg body cont @@ -2330,11 +2326,12 @@ simplOutId env fun cont = do { rule_base <- getSimplRules ; let rules_for_me = getRules rule_base fun - ; mb_match <- if activeUnfolding (seMode env) fun - then tryRules zapped_env rules_for_me fun cont1 - else return Nothing + ; mb_match <- -- if activeUnfolding (seMode env) fun + -- then + -- else return Nothing + tryRules zapped_env rules_for_me fun cont1 ; case mb_match of { - Just (rhs, cont2) -> pprTrace "tryRules1" (ppr fun) $ + Just (rhs, cont2) -> -- pprTrace "tryRules1" (ppr fun) $ simplExprF zapped_env rhs cont2 ; Nothing -> @@ -2355,18 +2352,19 @@ simplOutId env fun cont --------------------------------------------------------- -- Dealing with a call site -rebuildCall, rebuildCall_go :: SimplEnv -> ArgInfo -> SimplCont - -> SimplM (SimplFloats, OutExpr) +rebuildCall :: SimplEnvIS -> ArgInfo -> SimplCont + -> SimplM (SimplFloats, OutExpr) -- At this point the substitution in the SimplEnv is irrelevant; -- it is usually empty, and regardless should be ignored. -- Only the in-scope set matters, plus the seMode flags -reubildCall env arg_info cont - = assertPpr (seHasEmptySubst env) (ppr (getFullSubst env) $$ ppr expr) $ - rebuildCall_go env arg_info cont +-- Check the invariant +rebuildCall env arg_info _cont + | assertPpr (checkSimplEnvIS env) (pprBadSimplEnvIS env $$ ppr arg_info) False + = pprPanic "rebuildCall" empty ---------- Bottoming applications -------------- -rebuildCall_go env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_dmds = [] }) cont +rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_dmds = [] }) cont -- When we run out of strictness args, it means -- that the call is definitely bottom; see GHC.Core.Opt.Simplify.Utils.mkArgInfo -- Then we want to discard the entire strict continuation. E.g. @@ -2432,16 +2430,16 @@ rebuildCall env info@(ArgInfo { ai_fun = fun, ai_args = rev_args -} ---------- Simplify type applications and casts -------------- -rebuildCall_go env info (CastIt { sc_co = co, sc_opt = opt, sc_cont = cont }) +rebuildCall env info (CastIt { sc_co = co, sc_opt = opt, sc_cont = cont }) = rebuildCall env (addCastTo info co') cont where co' = optOutCoercion env co opt -rebuildCall-go env info (ApplyToTy { sc_arg_ty = arg_ty, sc_hole_ty = hole_ty, sc_cont = cont }) +rebuildCall env info (ApplyToTy { sc_arg_ty = arg_ty, sc_hole_ty = hole_ty, sc_cont = cont }) = rebuildCall env (addTyArgTo info arg_ty hole_ty) cont ---------- Simplify value arguments -------------------- -rebuildCall_go env fun_info +rebuildCall env fun_info (ApplyToVal { sc_arg = arg, sc_env = arg_se , sc_dup = dup_flag, sc_hole_ty = fun_ty , sc_cont = cont }) @@ -2470,14 +2468,14 @@ rebuildCall_go env fun_info ; rebuildCall env (addValArgTo fun_info arg' fun_ty) cont } ---------- No further useful info, revert to generic rebuild ------------ -rebuildCall_go env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) cont +rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) cont | null rules = rebuild env (argInfoExpr fun rev_args) cont | otherwise -- Try rules again = do { let full_cont = pushSimplifiedRevArgs env rev_args cont ; mb_match <- tryRules env rules fun full_cont ; case mb_match of - Just (rhs, cont2) -> pprTrace "tryRules2" (ppr fun $$ ppr (seIdSubst env)) $ + Just (rhs, cont2) -> -- pprTrace "tryRules2" (ppr fun $$ ppr (seIdSubst env)) $ simplExprF env rhs cont2 Nothing -> rebuild env (argInfoExpr fun rev_args) cont } @@ -2647,7 +2645,7 @@ tryRules env rules fn cont | null rules = return Nothing - | Just (rule, rule_rhs) <- -- pprTrace "tryRules" (ppr fn) $ + | Just (rule, rule_rhs) <- -- pprTrace "tryRules" (ppr fn <+> vcat (map ppr out_args)) $ lookupRule ropts in_scope_env act_fun fn out_args rules -- Fire a rule for the function @@ -2674,7 +2672,7 @@ tryRules env rules fn cont where ropts = seRuleOpts env :: RuleOpts in_scope_env = getUnfoldingInRuleMatch env :: InScopeEnv - out_args = contOutArgs cont :: [OutExpr] + out_args = contOutArgs (seInScope env) cont :: [OutExpr] act_fun = activeRule (seMode env) :: Activation -> Bool printRuleModule rule @@ -3883,13 +3881,17 @@ mkDupableCont :: SimplEnv -- extra let/join-floats and in-scope variables , SimplCont) -- dup_cont: duplicable continuation mkDupableCont env cont - = mkDupableContWithDmds env (repeat topDmd) cont + = mkDupableContWithDmds (zapSubstEnv env) (repeat topDmd) cont mkDupableContWithDmds - :: SimplEnv -> [Demand] -- Demands on arguments; always infinite + :: SimplEnvIS -> [Demand] -- Demands on arguments; always infinite -> SimplCont -> SimplM ( SimplFloats, SimplCont) mkDupableContWithDmds env _ cont + -- Check the invariant + | assertPpr (checkSimplEnvIS env) (pprBadSimplEnvIS env) False + = pprPanic "mkDupableContWithDmds" empty + | contIsDupable cont = return (emptyFloats env, cont) ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -282,7 +282,7 @@ instance Outputable SimplCont where = (text "TickIt" <+> ppr t) $$ ppr cont ppr (ApplyToTy { sc_arg_ty = ty, sc_cont = cont }) = (text "ApplyToTy" <+> pprParendType ty) $$ ppr cont - ppr (ApplyToVal { sc_arg = arg, sc_dup = dup, sc_cont = cont, sc_hole_ty = hole_ty, sc_env = env }) + ppr (ApplyToVal { sc_arg = arg, sc_dup = dup, sc_cont = cont, sc_hole_ty = hole_ty }) = (hang (text "ApplyToVal" <+> ppr dup <+> text "hole-ty:" <+> pprParendType hole_ty) 2 (pprParendExpr arg)) $$ ppr cont @@ -588,17 +588,19 @@ contArgs cont -- Do *not* use short-cutting substitution here -- because we want to get as much IdInfo as possible -contOutArgs :: SimplCont -> [OutExpr] +contOutArgs :: GHC.Core.Subst.InScopeSet -> SimplCont -> [OutExpr] -- Get the leading arguments from the `SimplCont`, as /OutExprs/ -contOutArgs (ApplyToTy { sc_arg_ty = ty, sc_cont = cont }) - = Type ty : contOutArgs cont -contOutArgs (ApplyToVal { sc_dup = dup, sc_arg = arg, sc_env = env, sc_cont = cont }) +contOutArgs in_scope (ApplyToTy { sc_arg_ty = ty, sc_cont = cont }) + = Type ty : contOutArgs in_scope cont +contOutArgs in_scope (ApplyToVal { sc_dup = dup, sc_arg = arg, sc_env = env, sc_cont = cont }) | isSimplified dup - = arg : contOutArgs cont + = arg : contOutArgs in_scope cont | otherwise = -- pprTrace "contOutArgs" (ppr arg $$ ppr (seIdSubst env)) $ - GHC.Core.Subst.substExprSC (getFullSubst env) arg : contOutArgs cont -contOutArgs _ + GHC.Core.Subst.substExpr (getFullSubst in_scope env) arg : contOutArgs in_scope cont + -- NOT substExprSC: we want to get the benefit of knowing what is + -- evaluated etc, via the in-scope set +contOutArgs _ _ = [] dropContArgs :: FullArgCount -> SimplCont -> SimplCont View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/016bd2bf3b48f57d4aba0333ea3a8f5cb31055e0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/016bd2bf3b48f57d4aba0333ea3a8f5cb31055e0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/9cb5636c/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 15:04:59 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Thu, 13 Mar 2025 11:04:59 -0400 Subject: [Git][ghc/ghc][wip/T25647] clear up candidateQTyVarsWithBinders Message-ID: <67d2f41b5bd3d_2b4aa19bee9c1241ae@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 002e69f9 by Patrick at 2025-03-13T23:04:48+08:00 clear up candidateQTyVarsWithBinders - - - - - 3 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Zonk/TcType.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -253,14 +253,12 @@ tcFamInstLHSBinders :: TcLevel -> SkolemInfo -> HsOuterFamEqnTyVarBndrs GhcTc -> -> [TcTyVar] -> Type -> WantedConstraints -> IOEnv (Env TcGblEnv TcLclEnv) ([TyCoVar], [TcTyVar]) tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted = do - -- See Note [Type variables in type families instance decl] ; let outer_exp_tvs = scopedSort $ explicitOuterTyVars outer_bndrs ; let outer_imp_tvs = implicitOuterTyVars outer_bndrs ; checkFamTelescope tclvl hs_outer_bndrs outer_exp_tvs - ; wc_itvs <- liftZonkM $ zonkInvariants wcs - ; outer_imp_itvs <- liftZonkM $ zonkInvariants outer_imp_tvs -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; dvs <- candidateQTyVarsWithBinders (outer_exp_tvs ++ outer_imp_tvs ++ wcs) lhs_ty + -- See Note [Type variables in type families instance decl] + ; (dvs, wc_itvs, outer_imp_itvs) <- candidateQTyVarsWithBinders outer_exp_tvs outer_imp_tvs wcs lhs_ty ; (qtvs, outer_imp_qtvs) <- quantifyTyVarsWithBinders wc_itvs outer_imp_itvs skol_info dvs -- Have to make a same defaulting choice for result kind here -- and the `kindGeneralizeAll` in `tcConDecl`. ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1369,6 +1369,11 @@ candidateVars (DV { dv_kvs = dep_kv_set, dv_tvs = nondep_tkv_set }) candidateKindVars :: CandidatesQTvs -> TyVarSet candidateKindVars dvs = dVarSetToVarSet (dv_kvs dvs) +intersectCandidates :: CandidatesQTvs -> [Var] -> [Var] +intersectCandidates (DV { dv_kvs = kvs, dv_tvs = tvs }) varList + = dVarSetElems $ kvs `intersectDVarSet` vars `unionDVarSet` (tvs `intersectDVarSet` vars) + where vars = mkDVarSet varList + delCandidates :: CandidatesQTvs -> [Var] -> CandidatesQTvs delCandidates (DV { dv_kvs = kvs, dv_tvs = tvs, dv_cvs = cvs }) vars = DV { dv_kvs = kvs `delDVarSetList` vars @@ -1384,21 +1389,23 @@ partitionCandidates dvs@(DV { dv_kvs = kvs, dv_tvs = tvs }) pred (extracted_tvs, rest_tvs) = partitionDVarSet pred tvs extracted = dVarSetToVarSet extracted_kvs `unionVarSet` dVarSetToVarSet extracted_tvs -candidateQTyVarsWithBinders :: [TyVar] -> Type -> TcM CandidatesQTvs +candidateQTyVarsWithBinders :: [TyVar] -> [TyVar] -> [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar], [TyVar]) -- (candidateQTyVarsWithBinders tvs ty) returns the candidateQTyVars -- of (forall tvs. ty), but do not treat 'tvs' as bound for the purpose -- of Note [Naughty quantification candidates]. Why? -- Because we are going to scoped-sort the quantified variables -- in among the tvs -candidateQTyVarsWithBinders bound_tvs ty +candidateQTyVarsWithBinders outer_exp_tvs outer_imp_tvs wcs ty = do { kvs <- candidateQTyVarsOfKinds (map tyVarKind bound_tvs) ; cur_lvl <- getTcLevel ; all_tvs <- collect_cand_qtvs ty False cur_lvl emptyVarSet kvs ty - ; return (all_tvs `delCandidates` bound_tvs)} + ; return (all_tvs `delCandidates` bound_tvs, intersectCandidates all_tvs outer_imp_tvs, intersectCandidates all_tvs wcs) } + where + bound_tvs = outer_exp_tvs ++ outer_imp_tvs ++ wcs -- | Gathers free variables to use as quantification candidates (in --- 'quantifyTyVarsWithBinders). This might output the same var +-- 'quantifyTyVarsWithBinders'). This might output the same var -- in both sets, if it's used in both a type and a kind. -- The variables to quantify must have a TcLevel strictly greater than -- the ambient level. (See Wrinkle in Note [Naughty quantification candidates]) @@ -1763,7 +1770,7 @@ quantifyTyVarsWithBinders :: -- to the restrictions in Note [quantifyTyVars]. -- for wildcards, do not default, just skolemise add to the list of quantified --- for outer_imp_qtvs, do not default and skolemise, and return separately +-- for outer_imp_qtvs, do not default, just skolemise, and return separately quantifyTyVarsWithBinders wc_itvs outer_imp_itvs skol_info dvs -- short-circuit common case | isEmptyCandidates dvs && null wc_itvs && null outer_imp_itvs @@ -1780,10 +1787,9 @@ quantifyTyVarsWithBinders wc_itvs outer_imp_itvs skol_info dvs ; undefaulted <- defaultTyVars dvs ; (final_qtvs, out_imp_qtvs) <- liftZonkM $ do - qtvs <- mapMaybeM zonk_quant undefaulted - wc_qtv <- mapMaybeM zonk_quant wc_itvs + qtvs <- mapMaybeM zonk_quant (undefaulted ++ wc_itvs) out_imp_qtvs <- mapMaybeM zonk_quant outer_imp_itvs - return (qtvs ++ wc_qtv, out_imp_qtvs) + return (qtvs, out_imp_qtvs) ; traceTc "quantifyTyVars }" (vcat [ text "undefaulted:" <+> pprTyVars undefaulted @@ -1792,7 +1798,7 @@ quantifyTyVarsWithBinders wc_itvs outer_imp_itvs skol_info dvs ]) -- We should never quantify over coercion variables; check this - ; let co_vars = filter isCoVar final_qtvs + ; let co_vars = filter isCoVar (final_qtvs ++ out_imp_qtvs) ; massertPpr (null co_vars) (ppr co_vars) ; return (final_qtvs, out_imp_qtvs) } ===================================== compiler/GHC/Tc/Zonk/TcType.hs ===================================== @@ -20,7 +20,6 @@ module GHC.Tc.Zonk.TcType , zonkTcTyVarToTcTyVar, zonkTcTyVarsToTcTyVars , zonkInvisTVBinder , zonkCo - , zonkInvariants -- ** Zonking 'TyCon's , zonkTcTyCon @@ -270,13 +269,6 @@ zonkTcTyVar tv zonkTcTyVarsToTcTyVars :: HasDebugCallStack => [TcTyVar] -> ZonkM [TcTyVar] zonkTcTyVarsToTcTyVars = mapM zonkTcTyVarToTcTyVar --- let x = zonked and y = unzonked --- take intersection of x and y -zonkInvariants :: HasDebugCallStack => [TcTyVar] -> ZonkM [TcTyVar] -zonkInvariants y = do - x <- mapMaybeM (fmap getTyVar_maybe . zonkTcTyVar) y - return $ dVarSetElems $ mkDVarSet y `intersectDVarSet` mkDVarSet x - zonkTcTyVarToTcTyVar :: HasDebugCallStack => TcTyVar -> ZonkM TcTyVar zonkTcTyVarToTcTyVar tv View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/002e69f975752208c082b02c9c990ed985ba11d1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/002e69f975752208c082b02c9c990ed985ba11d1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/014aadac/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 16:07:55 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 13 Mar 2025 12:07:55 -0400 Subject: [Git][ghc/ghc][wip/T24359] 8 commits: mk-ghcup-metadata: Clean up and add type annotations Message-ID: <67d302dbcec92_7bcfa4a0164845b2@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - c8281dbd by sheaf at 2025-03-13T17:07:44+01:00 Fix buglet in isEmptyWorkList There was a missing case in GHC.Tc.Solver.InertSet.isEmptyWorkList; it mistakenly ignored the 'wl_rw_eqs' field. This commit simply fixes that. No test case. - - - - - 0fa438b3 by sheaf at 2025-03-13T17:07:44+01:00 Add mapMaybeTM method to TrieMap class This commit adds a new method to the TrieMap class, mapMaybeTM, and adds implementations to all the instances. mapMaybeTM is useful when filtering containers that contain other containers. - - - - - 2fe794e1 by Simon Peyton Jones at 2025-03-13T17:07:46+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - 23a14c10 by Simon Peyton Jones at 2025-03-13T17:07:46+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 196 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot/GHC/Serialized.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - rts/HeapStackCheck.cmm - rts/PrimOps.cmm - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/dump-decls/Main.hs - utils/haddock/haddock-api/src/Haddock/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b8323c5e05bab4712038bdabe8e1eb68ed35f6bf...23a14c10d080648574722240a2b6647d1a3cdf86 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b8323c5e05bab4712038bdabe8e1eb68ed35f6bf...23a14c10d080648574722240a2b6647d1a3cdf86 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/ef9c1cbf/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 17:09:51 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Thu, 13 Mar 2025 13:09:51 -0400 Subject: [Git][ghc/ghc][wip/T25647] 94 commits: interfaces: Ensure that forceModIface deeply forces a ModIface Message-ID: <67d3115fbd27d_9ff0b17789850837@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 751143c4 by Simon Peyton Jones at 2025-03-13T17:09:45+00:00 WIP towards #25267 - - - - - 9d4fe45d by Simon Peyton Jones at 2025-03-13T17:09:45+00:00 Wibbles - - - - - 4e9009e5 by Simon Peyton Jones at 2025-03-13T17:09:45+00:00 Default tyvars in data/newtype insnstances This is what fixes #25647 - - - - - 0c6cd562 by Simon Peyton Jones at 2025-03-13T17:09:45+00:00 wibbles Including fix for #25725 - - - - - 235f0cdf by Simon Peyton Jones at 2025-03-13T17:09:45+00:00 Wibble - - - - - ae48bb27 by Patrick at 2025-03-13T17:09:45+00:00 add more tests - - - - - 82e39f18 by Patrick at 2025-03-13T17:09:45+00:00 Fix up T25611d with explicit kind annotation - - - - - b8bbf46c by Patrick at 2025-03-13T17:09:45+00:00 fix up T25647_fail - - - - - 0cb6ab60 by Patrick at 2025-03-13T17:09:45+00:00 cleanup whitespace - - - - - 3f4c40bd by Patrick at 2025-03-13T17:09:45+00:00 fix up T23512a - - - - - f4fc3983 by Patrick at 2025-03-13T17:09:45+00:00 add more examples to T25647b - - - - - 5185cbc4 by Patrick at 2025-03-13T17:09:45+00:00 add Dix6 to T25647_fail - - - - - 13f84d7e by Patrick at 2025-03-13T17:09:45+00:00 add Dix7 for T25647a - - - - - b330762c by Patrick at 2025-03-13T17:09:45+00:00 change DefaultingStrategy of tcTyFamInstEqnGuts as well - - - - - c0a6467d by Patrick at 2025-03-13T17:09:45+00:00 align wildcard with named typevar on wether it is skolem - - - - - d4de3198 by Patrick at 2025-03-13T17:09:45+00:00 fix T17536c - - - - - 76f10899 by Patrick at 2025-03-13T17:09:45+00:00 Fix T9357 - - - - - 1f2080b7 by Patrick at 2025-03-13T17:09:45+00:00 remove wildcard usage - - - - - 6ff9f18c by Patrick at 2025-03-13T17:09:45+00:00 Revert "align wildcard with named typevar on wether it is skolem" This reverts commit d1f61858328cc190de9b34c9a24e8d6b28ee5fa9. - - - - - bd4c36d0 by Patrick at 2025-03-13T17:09:45+00:00 add WildCardTv to forbid wildcard from defaulting - - - - - 72ffe798 by Patrick at 2025-03-13T17:09:45+00:00 Fix wildcard related tests - - - - - 984159ad by Patrick at 2025-03-13T17:09:45+00:00 add wildcards testcase for T25647a - - - - - 78f422a3 by Patrick at 2025-03-13T17:09:45+00:00 Fix T25647a - - - - - 2a7d2af1 by Patrick at 2025-03-13T17:09:45+00:00 Revert "Fix wildcard related tests" This reverts commit 8756ab87f4e3d74968d3937f84f811f78a861852. - - - - - 2f60a017 by Patrick at 2025-03-13T17:09:45+00:00 limit WildCardTv to only HM_FamPat - - - - - 14707bcc by Patrick at 2025-03-13T17:09:45+00:00 fix - - - - - f3aaa8e3 by Patrick at 2025-03-13T17:09:45+00:00 Revert "remove wildcard usage" This reverts commit ccc9152f23177ab7a542852ffedf626edcdcef95. - - - - - 9f10b0ac by Patrick at 2025-03-13T17:09:45+00:00 rename WildCardTv to NoDefTauTv - - - - - fa4fc6a3 by Patrick at 2025-03-13T17:09:45+00:00 update note - - - - - ee6a594b by Patrick at 2025-03-13T17:09:45+00:00 rename isWildCardMetaTyVar to isNoDefTauMetaTyVar and fix defaultTyVarTcS - - - - - 78e0363d by Patrick at 2025-03-13T17:09:45+00:00 fix comment - - - - - 2990bc60 by Patrick at 2025-03-13T17:09:45+00:00 format - - - - - 58aa2ede by Patrick at 2025-03-13T17:09:45+00:00 remove NonStandardDefaultingStrategy and update Note [NoDefTauTv] - - - - - 94c28d18 by Patrick at 2025-03-13T17:09:45+00:00 add DixC10 to T25647a - - - - - 023a92d3 by Patrick at 2025-03-13T17:09:45+00:00 use TyVarTv for wildcard in HM_FamPat - - - - - b3103ae9 by Patrick at 2025-03-13T17:09:45+00:00 Revert "use TyVarTv for wildcard in HM_FamPat" This reverts commit 638d6763d0b972f3c9a0e2c4218d8c7ce34dc800. - - - - - 4362b189 by Patrick at 2025-03-13T17:09:45+00:00 Add FamArgType to in AssocInstInfo to guide the create of tv for wildcard - - - - - e496bc9b by Patrick at 2025-03-13T17:09:45+00:00 Fix mode args passing down - - - - - f106a6b0 by Patrick at 2025-03-13T17:09:45+00:00 Fix under application for data fam - - - - - 07376691 by Patrick at 2025-03-13T17:09:45+00:00 use HM_Sig for (a :: _) in type family - - - - - 74eb5258 by Patrick at 2025-03-13T17:09:45+00:00 add and use HM_FamSig for (a :: _) in type family - - - - - 7880a8a8 by Patrick at 2025-03-13T17:09:45+00:00 use TyVarTv instead of SkolemTv for freeArg `_`, since we also do not default TyVarTv in defaultTyVar and defaultTyVarTcS - - - - - 5d8926ff by Patrick at 2025-03-13T17:09:45+00:00 Revert "add and use HM_FamSig for (a :: _) in type family" and use ClassArg for _ in (a :: _) in type family This reverts commit 9ab780da39c2afbce2411c2b96fef4108d6b8b70. - - - - - 05e61b0b by Patrick at 2025-03-13T17:09:45+00:00 fix - - - - - 1b707a67 by Patrick at 2025-03-13T17:09:45+00:00 remove unused updateHoleMode function from TcTyMode - - - - - ab7a299f by Patrick at 2025-03-13T17:09:45+00:00 flip the classVar to TyVarTv to observe any breakage - - - - - bcd5d7ef by Patrick at 2025-03-13T17:09:45+00:00 fix - - - - - 2e49071a by Patrick at 2025-03-13T17:09:45+00:00 disable DixC10 from T25647a - - - - - 5d07dd5b by Patrick at 2025-03-13T17:09:45+00:00 update ExplicitForAllFams4b - - - - - edb4f27f by Patrick at 2025-03-13T17:09:45+00:00 cleanup NoDefTauTv - - - - - 6ec3a0a6 by Patrick at 2025-03-13T17:09:45+00:00 move [FamArgFlavour] to tyCon - - - - - e8608994 by Patrick at 2025-03-13T17:09:45+00:00 add note - - - - - 46426008 by Patrick at 2025-03-13T17:09:45+00:00 refactor documentation for FamArgFlavour and clean up comments - - - - - 5d5b3920 by Patrick at 2025-03-13T17:09:45+00:00 enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging - - - - - fc4404a6 by Patrick at 2025-03-13T17:09:45+00:00 Ensure wildcard behave correctly - - - - - d9f5a912 by Patrick at 2025-03-13T17:09:45+00:00 Revert "update ExplicitForAllFams4b" This reverts commit 90a2858278668bc6ad66ef43a5651808d8f24a0f. - - - - - fbdc08bb by Patrick at 2025-03-13T17:09:45+00:00 Add detailed notes on wildcard handling in type families and refine related documentation - - - - - 68d192e4 by Patrick at 2025-03-13T17:09:45+00:00 Refine documentation on wildcard handling in type families and clarify design choices for FamArgFlavour - - - - - 4b7a4859 by Patrick at 2025-03-13T17:09:45+00:00 Fix typos in documentation regarding wildcards in type families and clarify references - - - - - 7834a051 by Patrick at 2025-03-13T17:09:45+00:00 Clarify wildcard handling in type families documentation and improve explanations for FamArgFlavour - - - - - fa199c2c by Patrick at 2025-03-13T17:09:45+00:00 Enhance documentation on FamArgFlavour handling in type families and clarify implementation details in TyCon and HsType modules - - - - - 7a100fa4 by Patrick at 2025-03-13T17:09:45+00:00 format - - - - - 1fac9206 by Patrick at 2025-03-13T17:09:45+00:00 Refactor documentation on wildcards in type families and clarify implementation details in TyCon, Rename, and HsType modules - - - - - cdff711b by Patrick at 2025-03-13T17:09:45+00:00 Rename variable `famArgFlvs` to `fam_arg_flvs` for consistency in type inference functions - - - - - 4ba3cb01 by Patrick at 2025-03-13T17:09:45+00:00 Improve documentation on wildcard interpretation in type families, clarifying the relationship with class arguments and enhancing the explanation of FamArgFlavour categories. - - - - - edc6fa54 by Patrick at 2025-03-13T17:09:45+00:00 Add comment to clarify implementation details for wildcards in family instances - - - - - d1c22761 by Patrick at 2025-03-13T17:09:45+00:00 Refactor HsOuterTyVarBndrs to include implicit variable bindings and update related functions for consistency - - - - - 21833683 by Patrick at 2025-03-13T17:09:45+00:00 Enhance HsOuterTyVarBndrs to support implicit variable bindings and update related functions for consistency - - - - - fbcdcb2f by Patrick at 2025-03-13T17:09:45+00:00 Add new test case T25647d - - - - - c1b550fd by Patrick at 2025-03-13T17:09:45+00:00 Remove unused implicit variable bindings from HsOuterExplicit in addHsOuterSigTyVarBinds function - - - - - 4945f89d by Patrick at 2025-03-13T17:09:45+00:00 Add forall quantifiers to MultMul type family for clarity - - - - - 9bf59ca6 by Patrick at 2025-03-13T17:09:45+00:00 Refactor bindHsOuterTyVarBndrs' - - - - - 0e669622 by Patrick at 2025-03-13T17:09:45+00:00 Add empty implicit variable bindings to HsOuterExplicit in mkEmptySigType - - - - - c72b5a8c by Patrick at 2025-03-13T17:09:45+00:00 Add empty implicit variable bindings to HsOuterExplicit in synifyDataCon - - - - - 1eebc04d by Patrick at 2025-03-13T17:09:45+00:00 Add missing implicit variable bindings to HsOuterExplicit in ExactPrint instance - - - - - 82f361fd by Patrick at 2025-03-13T17:09:45+00:00 Add implicit variable bindings to HsOuterExplicit in various instances - - - - - adc10e19 by Patrick at 2025-03-13T17:09:45+00:00 Add forall quantifier to D Int newtype instance - - - - - 344bf147 by Patrick at 2025-03-13T17:09:45+00:00 zonk_quant outer binders for families - - - - - 2760c0bf by Patrick at 2025-03-13T17:09:45+00:00 revert to old behaviour - - - - - cf7f35b5 by Patrick at 2025-03-13T17:09:45+00:00 add note and comment - - - - - 11b34f02 by Patrick at 2025-03-13T17:09:45+00:00 refactor - - - - - 06b3a53e by Patrick at 2025-03-13T17:09:45+00:00 fix test T25647d - - - - - 2d18216b by Patrick at 2025-03-13T17:09:45+00:00 handle [Naughty quantification candidates] - - - - - d170be5f by Patrick at 2025-03-13T17:09:45+00:00 handle explicit implicit binders seperately - - - - - db42a12e by Patrick at 2025-03-13T17:09:45+00:00 handle explicit implicit binders seperately fix - - - - - 14ae3718 by Patrick at 2025-03-13T17:09:45+00:00 fix lint - - - - - ce9a64a0 by Patrick at 2025-03-13T17:09:45+00:00 some renaming - - - - - 4de3195f by Patrick at 2025-03-13T17:09:45+00:00 update tests to reflect changes in error messages - - - - - be0b9311 by Patrick at 2025-03-13T17:09:45+00:00 improve zonking logic for tcFamInstLHSBinders - - - - - cd13a999 by Patrick at 2025-03-13T17:09:45+00:00 clean up trace statements and remove unused function - - - - - 8e59f942 by Patrick at 2025-03-13T17:09:45+00:00 fix ppr - - - - - 96d82e31 by Patrick at 2025-03-13T17:09:45+00:00 clear up candidateQTyVarsWithBinders - - - - - 68 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Types/LclEnv.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - libraries/ghc-boot/GHC/Serialized.hs - + testsuite/tests/indexed-types/should_compile/T11450a.hs - testsuite/tests/indexed-types/should_compile/T25611d.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/SimpleFail2a.hs - testsuite/tests/indexed-types/should_fail/SimpleFail2a.stderr - testsuite/tests/indexed-types/should_fail/SimpleFail9.hs - testsuite/tests/indexed-types/should_fail/SimpleFail9.stderr - testsuite/tests/indexed-types/should_fail/T14230a.hs - testsuite/tests/indexed-types/should_fail/T14230a.stderr - testsuite/tests/indexed-types/should_fail/T14246.stderr - testsuite/tests/indexed-types/should_fail/T9357.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/rename/should_fail/T23512a.stderr - + testsuite/tests/typecheck/should_compile/T25647_fail.hs - + testsuite/tests/typecheck/should_compile/T25647_fail.stderr - + testsuite/tests/typecheck/should_compile/T25647a.hs - + testsuite/tests/typecheck/should_compile/T25647b.hs - + testsuite/tests/typecheck/should_compile/T25647c.hs - + testsuite/tests/typecheck/should_compile/T25647d.hs - + testsuite/tests/typecheck/should_compile/T25647d_fail.hs - + testsuite/tests/typecheck/should_compile/T25647d_fail.stderr - + testsuite/tests/typecheck/should_compile/T25725.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T18640b.stderr - utils/dump-decls/Main.hs - utils/haddock/haddock-api/src/Haddock/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/002e69f975752208c082b02c9c990ed985ba11d1...96d82e31961178022de2fd88972413f34f1de27f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/002e69f975752208c082b02c9c990ed985ba11d1...96d82e31961178022de2fd88972413f34f1de27f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/ef8afc84/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 17:13:35 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 13 Mar 2025 13:13:35 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/better-main-2 Message-ID: <67d3123fcefc8_9ff0b1778c05274a@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/better-main-2 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/better-main-2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/39fe0ccb/attachment.html> From gitlab at gitlab.haskell.org Thu Mar 13 17:29:36 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 13 Mar 2025 13:29:36 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] MOre... Message-ID: <67d3160068cc3_aab02c5c104564@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: 25caf4d3 by Simon Peyton Jones at 2025-03-13T17:29:09+00:00 MOre... - - - - - 3 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs Changes: ===================================== compiler/GHC/Core.hs ===================================== @@ -1335,7 +1335,7 @@ isAutoRule (Rule { ru_auto = is_auto }) = is_auto -- | The number of arguments the 'ru_fn' must be applied -- to before the rule can match on it -ruleArity :: CoreRule -> Int +ruleArity :: CoreRule -> FullArgCount ruleArity (BuiltinRule {ru_nargs = n}) = n ruleArity (Rule {ru_args = args}) = length args ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -799,8 +799,8 @@ makeTrivialArg :: HasDebugCallStack => SimplEnv -> ArgSpec -> SimplM (LetFloats, makeTrivialArg env arg@(ValArg { as_arg = e, as_dmd = dmd }) = do { (floats, e') <- makeTrivial env NotTopLevel dmd (fsLit "arg") e ; return (floats, arg { as_arg = e' }) } -makeTrivialArg _ arg - = return (emptyLetFloats, arg) -- CastBy, TyArg +makeTrivialArg _ arg@(TyArg {}) + = return (emptyLetFloats, arg) makeTrivial :: HasDebugCallStack => SimplEnv -> TopLevelFlag -> Demand @@ -1520,12 +1520,11 @@ simplTick env tickish expr cont -} rebuild :: SimplEnv -> OutExpr -> SimplCont -> SimplM (SimplFloats, OutExpr) --- At this point the substitution in the SimplEnv is irrelevant; --- only the in-scope set matters, plus the flags. --- So zap it before calling `rebuild_go` rebuild env expr cont = rebuild_go (zapSubstEnv env) expr cont rebuild_go :: SimplEnvIS -> OutExpr -> SimplCont -> SimplM (SimplFloats, OutExpr) +-- SimplEnvIS: at this point the substitution in the SimplEnv is irrelevant; +-- only the in-scope set matters, plus the flags. rebuild_go env expr cont = assertPpr (checkSimplEnvIS env) (pprBadSimplEnvIS env) $ case cont of @@ -2323,18 +2322,19 @@ simplOutId env fun cont simplOutId env fun cont - = do { rule_base <- getSimplRules - ; let rules_for_me = getRules rule_base fun + = do { let cont1 = trimJoinCont fun (idJoinPointHood fun) cont - ; mb_match <- -- if activeUnfolding (seMode env) fun - -- then - -- else return Nothing - tryRules zapped_env rules_for_me fun cont1 + -- Try rewrite rules + ; rule_base <- getSimplRules + ; let rules_for_me = getRules rule_base fun + out_args = contOutArgs env cont1 :: [OutExpr] + ; mb_match <- tryRules zapped_env rules_for_me fun out_args ; case mb_match of { - Just (rhs, cont2) -> -- pprTrace "tryRules1" (ppr fun) $ - simplExprF zapped_env rhs cont2 ; + Just (rule_arity, rhs) -> simplExprF zapped_env rhs $ + dropContArgs rule_arity cont1 ; Nothing -> + -- Try inlining do { logger <- getLogger ; mb_inline <- tryInlining env logger fun cont1 ; case mb_inline of{ @@ -2342,19 +2342,19 @@ simplOutId env fun cont ; simplExprF zapped_env expr cont1 } ; Nothing -> - do { let arg_info = mkArgInfo env rules_for_me fun cont1 + -- Neither worked, so just rebuild + do { let arg_info = mkArgInfo env fun rules_for_me cont1 ; rebuildCall zapped_env arg_info cont1 } } } } } where zapped_env = zapSubstEnv env -- See Note [zapSubstEnv] - cont1 = trimJoinCont fun (idJoinPointHood fun) cont --------------------------------------------------------- -- Dealing with a call site rebuildCall :: SimplEnvIS -> ArgInfo -> SimplCont -> SimplM (SimplFloats, OutExpr) --- At this point the substitution in the SimplEnv is irrelevant; +-- SimplEnvIS: at this point the substitution in the SimplEnv is irrelevant; -- it is usually empty, and regardless should be ignored. -- Only the in-scope set matters, plus the seMode flags @@ -2384,57 +2384,7 @@ rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_dmds = [] }) con res = argInfoExpr fun rev_args cont_ty = contResultType cont -{- ----------- Try inlining, if ai_rewrite = TryInlining -------- --- In the TryInlining case we try inlining immediately, before simplifying --- any (more) arguments. Why? See Note [Rewrite rules and inlining]. --- --- If there are rewrite rules we'll skip this case until we have --- simplified enough args to satisfy nr_wanted==0 in the TryRules case below --- Then we'll try the rules, and if that fails, we'll do TryInlining -rebuildCall env info@(ArgInfo { ai_fun = fun, ai_args = rev_args - , ai_rewrite = TryInlining }) cont - = do { logger <- getLogger - ; let full_cont = pushSimplifiedRevArgs env rev_args cont - ; mb_inline <- tryInlining env logger fun full_cont - ; case mb_inline of - Just expr -> do { checkedTick (UnfoldingDone fun) - ; let env1 = zapSubstEnv env - ; simplExprF env1 expr full_cont } - Nothing -> rebuildCall env (info { ai_rewrite = TryNothing }) cont - } --} - -{- ----------- Try rewrite RULES, if ai_rewrite = TryRules -------------- --- See Note [Rewrite rules and inlining] --- See also Note [Trying rewrite rules] -rebuildCall env info@(ArgInfo { ai_fun = fun, ai_args = rev_args - , ai_rewrite = TryRules rules }) cont - | no_more_args - = -- We've accumulated a simplified call in <fun,rev_args> - -- so try rewrite rules; see Note [RULES apply to simplified arguments] - -- See also Note [Rules for recursive functions] - do { mb_match <- tryRules env rules fun (reverse rev_args) cont - ; case mb_match of - Just (env', rhs, cont') -> simplExprF env' rhs cont' - Nothing -> rebuildCall env (info { ai_rewrite = TryInlining }) cont } - where - -- If we have run out of arguments, just try the rules; there might - -- be some with lower arity. Casts get in the way -- they aren't - -- allowed on rule LHSs - no_more_args = case cont of - ApplyToTy {} -> False - ApplyToVal {} -> False - _ -> True --} - ----------- Simplify type applications and casts -------------- -rebuildCall env info (CastIt { sc_co = co, sc_opt = opt, sc_cont = cont }) - = rebuildCall env (addCastTo info co') cont - where - co' = optOutCoercion env co opt - +---------- Simplify type applications -------------- rebuildCall env info (ApplyToTy { sc_arg_ty = arg_ty, sc_hole_ty = hole_ty, sc_cont = cont }) = rebuildCall env (addTyArgTo info arg_ty hole_ty) cont @@ -2472,11 +2422,11 @@ rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) | null rules = rebuild env (argInfoExpr fun rev_args) cont | otherwise -- Try rules again - = do { let full_cont = pushSimplifiedRevArgs env rev_args cont - ; mb_match <- tryRules env rules fun full_cont + = do { let args = reverse rev_args + ; mb_match <- tryRules env rules fun (map argSpecArg args) ; case mb_match of - Just (rhs, cont2) -> -- pprTrace "tryRules2" (ppr fun $$ ppr (seIdSubst env)) $ - simplExprF env rhs cont2 + Just (rule_arity, rhs) -> simplExprF env rhs $ + pushSimplifiedArgs env (drop rule_arity args) cont Nothing -> rebuild env (argInfoExpr fun rev_args) cont } ----------------------------------- @@ -2637,31 +2587,24 @@ See Note [No free join points in arityType] in GHC.Core.Opt.Arity -} tryRules :: SimplEnv -> [CoreRule] - -> OutId - -> SimplCont - -> SimplM (Maybe (CoreExpr, SimplCont)) + -> OutId -> [OutExpr] + -> SimplM (Maybe (FullArgCount, CoreExpr)) -tryRules env rules fn cont +tryRules env rules fn args | null rules = return Nothing | Just (rule, rule_rhs) <- -- pprTrace "tryRules" (ppr fn <+> vcat (map ppr out_args)) $ lookupRule ropts in_scope_env - act_fun fn out_args rules + act_fun fn args rules -- Fire a rule for the function = -- pprTrace "tryRules:success" (ppr fn) $ do { logger <- getLogger ; checkedTick (RuleFired (ruleName rule)) - ; let cont' = dropContArgs (ruleArity rule) cont - -- (ruleArity rule) says how - -- many args the rule consumed - - occ_anald_rhs = occurAnalyseExpr rule_rhs + ; let occ_anald_rhs = occurAnalyseExpr rule_rhs -- See Note [Occurrence-analyse after rule firing] ; dump logger rule rule_rhs - ; return (Just (occ_anald_rhs, cont')) } - -- The occ_anald_rhs and cont' are all Out things - -- hence zapping the environment + ; return (Just (ruleArity rule, occ_anald_rhs)) } | otherwise -- No rule fires = -- pprTrace "tryRules:fail" (ppr fn) $ @@ -2672,7 +2615,6 @@ tryRules env rules fn cont where ropts = seRuleOpts env :: RuleOpts in_scope_env = getUnfoldingInRuleMatch env :: InScopeEnv - out_args = contOutArgs (seInScope env) cont :: [OutExpr] act_fun = activeRule (seMode env) :: Activation -> Bool printRuleModule rule @@ -2686,7 +2628,7 @@ tryRules env rules fn cont [ text "Rule:" <+> ftext (ruleName rule) , text "Module:" <+> printRuleModule rule , text "Full arity:" <+> ppr (ruleArity rule) - , text "Before:" <+> hang (ppr fn) 2 (ppr cont) + , text "Before:" <+> hang (ppr fn) 2 (sep (map ppr args)) , text "After: " <+> pprCoreExpr rule_rhs ] | logHasDumpFlag logger Opt_D_dump_rule_firings @@ -2725,9 +2667,14 @@ trySeqRules :: SimplEnv trySeqRules in_env scrut rhs cont = do { rule_base <- getSimplRules ; let seq_rules = getRules rule_base seqId - ; tryRules out_env seq_rules seqId rule_cont } + ; mb_match <- tryRules in_env seq_rules seqId out_args + ; case mb_match of + Nothing -> return Nothing + Just (rule_arity, rhs) -> return (Just (rhs, cont')) + where + cont' = pushSimplifiedArgs in_env (drop rule_arity out_arg_specs) rule_cont + } where - out_env = zapSubstEnv in_env no_cast_scrut = drop_casts scrut -- All these are OutTypes @@ -2740,16 +2687,22 @@ trySeqRules in_env scrut rhs cont rhs_ty = substTy in_env (exprType rhs) rhs_rep = getRuntimeRep rhs_ty - rule_cont = ApplyToTy { sc_arg_ty = rhs_rep, sc_hole_ty = seq_id_ty, sc_cont = rule_cont1 } - rule_cont1 = ApplyToTy { sc_arg_ty = scrut_ty, sc_hole_ty = res1_ty, sc_cont = rule_cont2 } - rule_cont2 = ApplyToTy { sc_arg_ty = rhs_ty, sc_hole_ty = res2_ty, sc_cont = rule_cont3 } - rule_cont3 = ApplyToVal { sc_arg = no_cast_scrut, sc_hole_ty = res3_ty, sc_cont = rule_cont4 - , sc_dup = Simplified, sc_env = out_env } - rule_cont4 = ApplyToVal { sc_arg = rhs, sc_hole_ty = res4_ty, sc_cont = cont - , sc_dup = NoDup, sc_env = in_env } + out_args = [Type rhs_rep, Type scrut_ty, Type rhs_ty, no_cast_scrut] + -- Cheaper than (map argSpecArg out_arg_specs) + out_arg_specs = [ TyArg { as_arg_ty = rhs_rep + , as_hole_ty = seq_id_ty } + , TyArg { as_arg_ty = scrut_ty + , as_hole_ty = res1_ty } + , TyArg { as_arg_ty = rhs_ty + , as_hole_ty = res2_ty } + , ValArg { as_arg = no_cast_scrut + , as_dmd = seqDmd + , as_hole_ty = res3_ty } ] + rule_cont = ApplyToVal { sc_dup = NoDup, sc_arg = rhs + , sc_env = in_env, sc_cont = cont + , sc_hole_ty = res4_ty } -- Lazily evaluated, so we don't do most of this - drop_casts (Cast e _) = drop_casts e drop_casts e = e ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -30,9 +30,9 @@ module GHC.Core.Opt.Simplify.Utils ( interestingCallContext, -- ArgInfo - ArgInfo(..), ArgSpec(..), RewriteCall(..), mkArgInfo, - addValArgTo, addCastTo, addTyArgTo, - argInfoExpr, argInfoAppArgs, + ArgInfo(..), ArgSpec(..), mkArgInfo, + addValArgTo, addTyArgTo, + argInfoExpr, argSpecArg, pushSimplifiedArgs, pushSimplifiedRevArgs, isStrictArgInfo, lazyArgContext, @@ -325,11 +325,8 @@ data ArgInfo ai_args :: [ArgSpec], -- ...applied to these args (which are in *reverse* order) -- NB: all these argumennts are already simplified --- ai_rewrite :: RewriteCall, -- What transformation to try next for this call --- -- See Note [Rewrite rules and inlining] in GHC.Core.Opt.Simplify.Iteration - ai_rules :: [CoreRule], -- Rules for this function - ai_encl :: Bool, -- Flag saying whether this function + ai_encl :: Bool, -- Flag saying whether this function -- or an enclosing one has rules (recursively) -- True => be keener to inline in all args @@ -343,12 +340,6 @@ data ArgInfo -- Always infinite } -data RewriteCall -- What rewriting to try next for this call - -- See Note [Rewrite rules and inlining] in GHC.Core.Opt.Simplify.Iteration - = TryRules [CoreRule] - | TryInlining - | TryNothing - data ArgSpec = ValArg { as_dmd :: Demand -- Demand placed on this argument , as_arg :: OutExpr -- Apply to this (coercion or value); c.f. ApplyToVal @@ -357,9 +348,6 @@ data ArgSpec | TyArg { as_arg_ty :: OutType -- Apply to this type; c.f. ApplyToTy , as_hole_ty :: OutType } -- Type of the function (presumably forall a. blah) - | CastBy OutCoercion -- Cast by this; c.f. CastIt - -- Coercion is optimised - instance Outputable ArgInfo where ppr (ArgInfo { ai_fun = fun, ai_args = args, ai_dmds = dmds }) = text "ArgInfo" <+> braces @@ -370,7 +358,6 @@ instance Outputable ArgInfo where instance Outputable ArgSpec where ppr (ValArg { as_arg = arg }) = text "ValArg" <+> ppr arg ppr (TyArg { as_arg_ty = ty }) = text "TyArg" <+> ppr ty - ppr (CastBy c) = text "CastBy" <+> ppr c addValArgTo :: ArgInfo -> OutExpr -> OutType -> ArgInfo addValArgTo ai arg hole_ty @@ -389,21 +376,12 @@ addTyArgTo ai arg_ty hole_ty = ai { ai_args = arg_spec : ai_args ai } where arg_spec = TyArg { as_arg_ty = arg_ty, as_hole_ty = hole_ty } -addCastTo :: ArgInfo -> OutCoercion -> ArgInfo -addCastTo ai co = ai { ai_args = CastBy co : ai_args ai } - isStrictArgInfo :: ArgInfo -> Bool -- True if the function is strict in the next argument isStrictArgInfo (ArgInfo { ai_dmds = dmds }) | dmd:_ <- dmds = isStrUsedDmd dmd | otherwise = False -argInfoAppArgs :: [ArgSpec] -> [OutExpr] -argInfoAppArgs [] = [] -argInfoAppArgs (CastBy {} : _) = [] -- Stop at a cast -argInfoAppArgs (ValArg { as_arg = arg } : as) = arg : argInfoAppArgs as -argInfoAppArgs (TyArg { as_arg_ty = ty } : as) = Type ty : argInfoAppArgs as - pushSimplifiedArgs, pushSimplifiedRevArgs :: SimplEnv -> [ArgSpec] -- In normal, forward order for pushSimplifiedArgs, @@ -419,8 +397,10 @@ pushSimplifiedArg env (ValArg { as_arg = arg, as_hole_ty = hole_ty }) cont = ApplyToVal { sc_arg = arg, sc_env = env, sc_dup = Simplified -- The SubstEnv will be ignored since sc_dup=Simplified , sc_hole_ty = hole_ty, sc_cont = cont } -pushSimplifiedArg _ (CastBy c) cont - = CastIt { sc_co = c, sc_cont = cont, sc_opt = True } + +argSpecArg :: ArgSpec -> OutExpr +argSpecArg (ValArg { as_arg = arg }) = arg +argSpecArg (TyArg { as_arg_ty = ty }) = Type ty argInfoExpr :: OutId -> [ArgSpec] -> OutExpr -- NB: the [ArgSpec] is reversed so that the first arg @@ -431,25 +411,6 @@ argInfoExpr fun rev_args go [] = Var fun go (ValArg { as_arg = arg } : as) = go as `App` arg go (TyArg { as_arg_ty = ty } : as) = go as `App` Type ty - go (CastBy co : as) = mkCast (go as) co - -{- -mkRewriteCall :: Id -> RuleEnv -> RewriteCall --- See Note [Rewrite rules and inlining] in GHC.Core.Opt.Simplify.Iteration --- We try to skip any unnecessary stages: --- No rules => skip TryRules --- No unfolding => skip TryInlining --- This skipping is "just" for efficiency. But rebuildCall is --- quite a heavy hammer, so skipping stages is a good plan. --- And it's extremely simple to do. -mkRewriteCall fun rule_env - | not (null rules) = TryRules rules - | canUnfold unf = TryInlining - | otherwise = TryNothing - where - rules = getRules rule_env fun - unf = idUnfolding fun --} {- ************************************************************************ @@ -588,20 +549,24 @@ contArgs cont -- Do *not* use short-cutting substitution here -- because we want to get as much IdInfo as possible -contOutArgs :: GHC.Core.Subst.InScopeSet -> SimplCont -> [OutExpr] +contOutArgs :: SimplEnv -> SimplCont -> [OutExpr] -- Get the leading arguments from the `SimplCont`, as /OutExprs/ -contOutArgs in_scope (ApplyToTy { sc_arg_ty = ty, sc_cont = cont }) - = Type ty : contOutArgs in_scope cont -contOutArgs in_scope (ApplyToVal { sc_dup = dup, sc_arg = arg, sc_env = env, sc_cont = cont }) - | isSimplified dup - = arg : contOutArgs in_scope cont - | otherwise - = -- pprTrace "contOutArgs" (ppr arg $$ ppr (seIdSubst env)) $ - GHC.Core.Subst.substExpr (getFullSubst in_scope env) arg : contOutArgs in_scope cont - -- NOT substExprSC: we want to get the benefit of knowing what is - -- evaluated etc, via the in-scope set -contOutArgs _ _ - = [] +contOutArgs env cont + = go cont + where + in_scope = seInScope env + + go (ApplyToTy { sc_arg_ty = ty, sc_cont = cont }) + = Type ty : go cont + + go (ApplyToVal { sc_dup = dup, sc_arg = arg, sc_env = env, sc_cont = cont }) + | isSimplified dup = arg : go cont + | otherwise = GHC.Core.Subst.substExpr (getFullSubst in_scope env) arg : go cont + -- NOT substExprSC: we want to get the benefit of knowing what is + -- evaluated etc, via the in-scope set + + -- No more arguments + go _ = [] dropContArgs :: FullArgCount -> SimplCont -> SimplCont dropContArgs 0 cont = cont @@ -640,9 +605,8 @@ contEvalContext k = case k of -- and case binder dmds, see addCaseBndrDmd. No priority right now. ------------------- -mkArgInfo :: SimplEnv -> [CoreRule] -> Id -> SimplCont -> ArgInfo - -mkArgInfo env rules_for_fun fun cont +mkArgInfo :: SimplEnv -> Id -> [CoreRule] -> SimplCont -> ArgInfo +mkArgInfo env fun rules_for_fun cont | n_val_args < idArity fun -- Note [Unsaturated functions] = ArgInfo { ai_fun = fun, ai_args = [] , ai_rules = rules_for_fun View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/25caf4d3393a759e1cbe0cc37a89c9ca4aa116e1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/25caf4d3393a759e1cbe0cc37a89c9ca4aa116e1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/b1efed16/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 20:25:19 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 13 Mar 2025 16:25:19 -0400 Subject: [Git][ghc/ghc][wip/refactor-iface] iface: Store logical parts of ModIface together Message-ID: <67d33f2f3c5f7_e6fac152b6016de@gitlab.mail> Matthew Pickering pushed to branch wip/refactor-iface at Glasgow Haskell Compiler / GHC Commits: f339c87f by Matthew Pickering at 2025-03-13T20:24:39+00:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 - - - - - 17 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - ghc/Main.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -100,29 +100,37 @@ module GHC ( findGlobalAnns, mkNamePprCtxForModule, ModIface, - ModIface_( - mi_module, - mi_sig_of, - mi_hsc_src, - mi_hi_bytes, - mi_deps, - mi_exports, - mi_fixities, - mi_warns, - mi_anns, - mi_insts, - mi_fam_insts, - mi_rules, - mi_decls, - mi_extra_decls, - mi_top_env, - mi_trust, - mi_trust_pkg, - mi_complete_matches, - mi_docs, - mi_final_exts, - mi_ext_fields - ), + ModIface_( mi_mod_info + , mi_module + , mi_sig_of + , mi_hsc_src + , mi_iface_hash + , mi_deps + , mi_public + , mi_exports + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_defaults + , mi_simplified_core + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_abi_hashes + , mi_ext_fields + , mi_hi_bytes + , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn + ), pattern ModIface, SafeHaskellMode(..), ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -844,7 +844,7 @@ hscRecompStatus case recomp_if_result of OutOfDateItem reason mb_checked_iface -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ fmap (mi_iface_hash . mi_final_exts) mb_checked_iface + return $ HscRecompNeeded $ fmap mi_iface_hash mb_checked_iface UpToDateItem checked_iface -> do let lcl_dflags = ms_hspp_opts mod_summary if | not (backendGeneratesCode (backend lcl_dflags)) -> do @@ -862,7 +862,7 @@ hscRecompStatus , xopt LangExt.TemplateHaskell lcl_dflags -> do msg $ needsRecompileBecause THWithJS - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface | otherwise -> do -- Do need linkable @@ -918,7 +918,7 @@ hscRecompStatus return $ HscUpToDate checked_iface $ linkable OutOfDateItem reason _ -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface -- | Check that the .o files produced by compilation are already up-to-date -- or not. @@ -968,10 +968,8 @@ loadByteCode iface mod_sum = do let this_mod = ms_mod mod_sum if_date = fromJust $ ms_iface_date mod_sum - case mi_extra_decls iface of - Just extra_decls -> do - let fi = WholeCoreBindings extra_decls this_mod (ms_location mod_sum) - (mi_foreign iface) + case iface_core_bindings iface (ms_location mod_sum) of + Just fi -> do return (UpToDateItem (Linkable if_date this_mod (NE.singleton (CoreBindings fi)))) _ -> return $ outOfDateItemBecause MissingBytecode Nothing @@ -1019,15 +1017,15 @@ compile_for_interpreter hsc_env use = -- | Assemble 'WholeCoreBindings' if the interface contains Core bindings. iface_core_bindings :: ModIface -> ModLocation -> Maybe WholeCoreBindings iface_core_bindings iface wcb_mod_location = - mi_extra_decls <&> \ wcb_bindings -> + mi_simplified_core <&> \(IfaceSimplifiedCore bindings foreign') -> WholeCoreBindings { - wcb_bindings, + wcb_bindings = bindings, wcb_module = mi_module, wcb_mod_location, - wcb_foreign = mi_foreign + wcb_foreign = foreign' } where - ModIface {mi_module, mi_extra_decls, mi_foreign} = iface + ModIface {mi_module, mi_simplified_core} = iface -- | Return an 'IO' that hydrates Core bindings and compiles them to bytecode if -- the interface contains any, using the supplied type env for typechecking. @@ -1376,7 +1374,7 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do -- dynamic interfaces. Hopefully both the dynamic and the non-dynamic -- interfaces stay in sync... -- - let change = old_iface /= Just (mi_iface_hash (mi_final_exts iface)) + let change = old_iface /= Just (mi_iface_hash iface) let dt = dynamicTooState dflags ===================================== compiler/GHC/HsToCore/Usage.hs ===================================== @@ -185,7 +185,7 @@ mkObjectUsage pit plugins fc hug th_links_needed th_pkgs_needed = do case miface of Nothing -> pprPanic "mkObjectUsage" (ppr m) Just iface -> - return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash (mi_final_exts iface)) + return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash iface) librarySpecToUsage :: LibrarySpec -> IO [Usage] librarySpecToUsage (Objects os) = traverse (fing Nothing) os @@ -278,10 +278,10 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names usg_entities = Map.toList ent_hashs, usg_safe = imp_safe } where - finsts_mod = mi_finsts (mi_final_exts iface) - hash_env = mi_hash_fn (mi_final_exts iface) - mod_hash = mi_mod_hash (mi_final_exts iface) - export_hash | depend_on_exports = Just (mi_exp_hash (mi_final_exts iface)) + finsts_mod = mi_finsts iface + hash_env = mi_hash_fn iface + mod_hash = mi_mod_hash iface + export_hash | depend_on_exports = Just (mi_exp_hash iface) | otherwise = Nothing by_is_safe (ImportedByUser imv) = imv_is_safe imv ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -41,34 +41,28 @@ data IfaceDynFlags = IfaceDynFlags , ifaceCallerCCFilters :: [CallerCcFilter] } -pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc -pprIfaceDynFlags (f, mflags) = - vcat $ - [ text "fingerprint:" <+> (ppr f) - ] - ++ case mflags of - Nothing -> [missingExtraFlagInfo] - Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> - [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) - , text "safe-mode:" <+> ppr a2 - , text "lang:" <+> ppr a3 - , text "exts:" <+> ppr a4 - , text "cpp-options:" - , nest 2 $ ppr a5 - , text "js-options:" - , nest 2 $ ppr a6 - , text "cmm-options:" - , nest 2 $ ppr a7 - , text "paths:" <+> hcat (map text a8) - , text "prof:" <+> ppr a9 - , text "ticky:" - , nest 2 $ vcat (map ppr a10) - , text "codegen:" - , nest 2 $ vcat (map ppr a11) - , text "fat-iface:" <+> ppr a12 - , text "debug-level:" <+> ppr a13 - , text "caller-cc-filters:" <+> ppr a14 - ] +pprIfaceDynFlags :: IfaceDynFlags -> SDoc +pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + vcat [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] missingExtraFlagInfo :: SDoc missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,7 +59,6 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields -import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -74,7 +73,6 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Logger -import GHC.Utils.Fingerprint( Fingerprint ) import GHC.Settings.Constants @@ -644,7 +642,7 @@ loadInterface doc_str mod from & set_mi_fam_insts (panic "No mi_fam_insts in PIT") & set_mi_rules (panic "No mi_rules in PIT") & set_mi_anns (panic "No mi_anns in PIT") - & set_mi_extra_decls (panic "No mi_extra_decls in PIT") + & set_mi_simplified_core (panic "No mi_simplified_core in PIT") bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1083,7 +1081,7 @@ load_dynamic_too :: Logger -> NameCache -> UnitState -> DynFlags load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do read_file logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case Succeeded (dynIface, _) - | mi_mod_hash (mi_final_exts iface) == mi_mod_hash (mi_final_exts dynIface) + | mi_mod_hash iface == mi_mod_hash dynIface -> return (Succeeded ()) | otherwise -> do return $ (Failed $ DynamicHashMismatchError wanted_mod loc) @@ -1174,11 +1172,10 @@ ghcPrimIface & set_mi_exports ghcPrimExports & set_mi_decls [] & set_mi_fixities ghcPrimFixities - & set_mi_final_exts ((mi_final_exts empty_iface) - { mi_fix_fn = mkIfaceFixCache ghcPrimFixities - , mi_decl_warn_fn = mkIfaceDeclWarnCache ghcPrimWarns - , mi_export_warn_fn = mkIfaceExportWarnCache ghcPrimWarns - }) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) + & set_mi_decl_warn_fn (mkIfaceDeclWarnCache ghcPrimWarns) + & set_mi_export_warn_fn (mkIfaceExportWarnCache ghcPrimWarns) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] in GHC.Builtin.Utils & set_mi_warns (toIfaceWarnings ghcPrimWarns) -- See Note [GHC.Prim Deprecations] in GHC.Builtin.Utils @@ -1263,21 +1260,14 @@ pprModIface unit_state iface = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") - <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) - <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) + <+> (if mi_orphan iface then text "[orphan module]" else Outputable.empty) + <+> (if mi_finsts iface then text "[family instance module]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) - , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) - , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat - [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) - , nest 2 (text "opt_hash:" <+> ppr opt_hash) - , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) - , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) - , vcat (map pprUsage usages) - ] - , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) + , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash iface)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash iface)) + , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash iface)) + , withSelfRecomp iface empty ppr + , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "where") , text "exports:" @@ -1288,10 +1278,14 @@ pprModIface unit_state iface , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] - , case mi_extra_decls iface of + , case mi_simplified_core iface of Nothing -> empty - Just eds -> text "extra decls:" - $$ nest 2 (vcat ([ppr bs | bs <- eds])) + Just (IfaceSimplifiedCore eds fs) -> + vcat [ text "extra decls:" + $$ nest 2 (vcat ([ppr bs | bs <- eds])) + , text "foreign stubs:" + $$ nest 2 (ppr fs) + ] , vcat (map ppr (mi_insts iface)) , vcat (map ppr (mi_fam_insts iface)) , vcat (map ppr (mi_rules iface)) @@ -1303,7 +1297,6 @@ pprModIface unit_state iface , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where - exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" @@ -1329,35 +1322,6 @@ pprExport avail@(AvailTC n _) = pp_export [] = Outputable.empty pp_export names = braces (hsep (map ppr names)) -pprUsage :: Usage -> SDoc -pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } - = pprUsageImport mod hash safe -pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name - , usg_mod_hash = hash, usg_safe = safe - , usg_exports = exports, usg_entities = entities } - = pprUsageImport (mkModule unit_id mod_name) hash safe $$ - nest 2 ( - maybe Outputable.empty (\v -> text "exports: " <> ppr v) exports $$ - vcat [ ppr n <+> ppr v | (n,v) <- entities ] - ) -pprUsage usage at UsageFile{} - = hsep [text "addDependentFile", - doubleQuotes (ftext (usg_file_path usage)), - ppr (usg_file_hash usage)] -pprUsage usage at UsageMergedRequirement{} - = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] -pprUsage usage at UsageHomeModuleInterface{} - = hsep [text "implementation", ppr (usg_mod_name usage) - , ppr (usg_unit_id usage) - , ppr (usg_iface_hash usage)] - -pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc -pprUsageImport mod hash safe - = hsep [ text "import", pp_safe, ppr mod - , ppr hash ] - where - pp_safe | safe = text "safe" - | otherwise = text " -/ " pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -88,13 +88,13 @@ import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModSummary import GHC.Unit.Module.Deps -import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign, emptyIfaceForeign) import Data.Function import Data.List ( sortBy ) import Data.Ord import Data.IORef - +import Data.Traversable {- ************************************************************************ @@ -143,11 +143,13 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos stubs foreign_files = updateDecl (mi_decls partial_iface) mb_stg_infos mb_cmm_infos -- See Note [Foreign stubs and TH bytecode linking] - foreign_ <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + mi_simplified_core <- for (mi_simplified_core partial_iface) $ \simpl_core -> do + fs <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + return $ (simpl_core { mi_sc_foreign = fs }) full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env $ set_mi_foreign foreign_ $ set_mi_decls decls partial_iface + addFingerprints hsc_env $ set_mi_simplified_core mi_simplified_core $ set_mi_decls decls partial_iface -- Debug printing let unit_state = hsc_units hsc_env @@ -289,7 +291,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode - -> Maybe ModIfaceSelfRecomp + -> Maybe IfaceSelfRecomp -> Maybe Docs -> ModDetails -> PartialModIface @@ -316,8 +318,8 @@ mkIface_ hsc_env entities = typeEnvElts type_env show_linear_types = xopt LangExt.LinearTypes (hsc_dflags hsc_env) - extra_decls = if gopt Opt_WriteIfSimplifiedCore dflags then Just [ toIfaceTopBind b | b <- core_prog ] - else Nothing + simplified_core = if gopt Opt_WriteIfSimplifiedCore dflags then Just (IfaceSimplifiedCore [ toIfaceTopBind b | b <- core_prog ] emptyIfaceForeign) + else Nothing decls = [ tyThingToIfaceDecl show_linear_types entity | entity <- entities, let name = getName entity, @@ -370,12 +372,12 @@ mkIface_ hsc_env & set_mi_anns annotations & set_mi_top_env rdrs & set_mi_decls decls - & set_mi_extra_decls extra_decls + & set_mi_simplified_core simplified_core & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) & set_mi_docs docs - & set_mi_final_exts () + & set_mi_abi_hashes () & set_mi_ext_fields emptyExtensibleFields & set_mi_hi_bytes PartialIfaceBinHandle ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -88,6 +88,7 @@ import Data.Ord import Data.Containers.ListUtils import Data.Bifunctor import GHC.Iface.Errors.Ppr +import Data.Functor {- ----------------------------------------------- @@ -325,8 +326,8 @@ check_old_iface hsc_env mod_summary maybe_iface maybe_dyn_iface <- liftIO $ loadIface (setDynamicNow dflags) (msDynHiFilePath mod_summary) case maybe_dyn_iface of Nothing -> return $ outOfDateItemBecause MissingDynHiFile Nothing - Just dyn_iface | mi_iface_hash (mi_final_exts dyn_iface) - /= mi_iface_hash (mi_final_exts normal_iface) + Just dyn_iface | mi_iface_hash dyn_iface + /= mi_iface_hash normal_iface -> return $ outOfDateItemBecause MismatchedDynHiFile Nothing Just {} -> return res _ -> return res @@ -382,7 +383,7 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface - -> ModIfaceSelfRecomp + -> IfaceSelfRecomp -> IfG (MaybeValidated ModIface) checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger @@ -435,7 +436,7 @@ checkVersions hsc_env mod_summary iface self_recomp -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins :: Plugins -> IfaceSelfRecomp -> IfG RecompileRequired checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp @@ -528,10 +529,10 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash :: HscEnv -> Module -> IfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + let FingerprintWithValue old_fp old_flags = mi_sr_flag_hash self_recomp (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally if old_fp == new_fp then up_to_date logger (text "Module flags unchanged") @@ -573,7 +574,7 @@ checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkOptimHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env let old_hash = mi_sr_opt_hash iface @@ -589,7 +590,7 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env let old_hash = mi_sr_hpc_hash self_recomp @@ -606,7 +607,7 @@ checkHpcHash hsc_env self_recomp = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures :: HscEnv -> ModSummary -> IfaceSelfRecomp -> IO RecompileRequired checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env @@ -748,7 +749,7 @@ checkModUsage _ UsagePackageModule{ logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChanged (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) -- We only track the ABI hash of package modules, rather than -- individual entity usages, so if the ABI hash changes we must -- recompile. This is safe but may entail more recompilation when @@ -758,7 +759,7 @@ checkModUsage _ UsageMergedRequirement{ usg_mod = mod, usg_mod_hash = old_mod_ha logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedRaw (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name , usg_unit_id = uid , usg_iface_hash = old_mod_hash } = do @@ -766,7 +767,7 @@ checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedIface mod_name - checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash (mi_final_exts iface)) + checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash iface) checkModUsage _ UsageHomeModule{ usg_mod_name = mod_name, @@ -779,9 +780,9 @@ checkModUsage _ UsageHomeModule{ logger <- getLogger needInterface mod $ \iface -> do let - new_mod_hash = mi_mod_hash (mi_final_exts iface) - new_decl_hash = mi_hash_fn (mi_final_exts iface) - new_export_hash = mi_exp_hash (mi_final_exts iface) + new_mod_hash = mi_mod_hash iface + new_decl_hash = mi_hash_fn iface + new_export_hash = mi_exp_hash iface reason = ModuleChanged (moduleName mod) @@ -986,7 +987,7 @@ we use is: -- | Compute the information needed for self-recompilation checking. This -- information can be computed before the backend phase. -mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO IfaceSelfRecomp mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env @@ -1000,10 +1001,10 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do let include_detailed_flags (flag_hash, flags) = if gopt Opt_WriteSelfRecompFlags dflags - then (flag_hash, Just flags) - else (flag_hash, Nothing) + then FingerprintWithValue flag_hash (Just flags) + else FingerprintWithValue flag_hash Nothing - return (ModIfaceSelfRecomp + return (IfaceSelfRecomp { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash @@ -1018,28 +1019,92 @@ addFingerprints :: HscEnv -> PartialModIface -> IO ModIface -addFingerprints hsc_env iface0 - = do - eps <- hscEPS hsc_env - let - decls = mi_decls iface0 - decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings $ mi_warns iface0) - export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ mi_warns iface0) - fix_fn = mkIfaceFixCache (mi_fixities iface0) +addFingerprints hsc_env iface0 = do + (abiHashes, caches, decls_w_hashes) <- addAbiHashes hsc_env (mi_mod_info iface0) (mi_public iface0) (mi_deps iface0) + + -- put the declarations in a canonical order, sorted by OccName + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ + [(getOccName d, e) | e@(_, d) <- decls_w_hashes] + + -- This key is safe because mi_extra_decls contains tidied things. + getOcc (IfGblTopBndr b) = getOccName b + getOcc (IfLclTopBndr fs _ _ details) = + case details of + IfRecSelId { ifRecSelFirstCon = first_con } + -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) + _ -> mkVarOccFS (ifLclNameFS fs) + + binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () + binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) + + sorted_extra_decls :: Maybe IfaceSimplifiedCore + sorted_extra_decls = mi_simplified_core iface0 <&> \simpl_core -> + IfaceSimplifiedCore (sortOn binding_key (mi_sc_extra_decls simpl_core)) (mi_sc_foreign simpl_core) + + -- The interface hash depends on: + -- - the ABI hash, plus + -- - the things which can affect whether a module is recompiled + -- - the module level annotations, + -- - deps (home and external packages, dependent files) + iface_hash <- computeFingerprint putNameLiterally + (mi_abi_mod_hash abiHashes, + mi_self_recomp_info iface0, + sorted_decls ) + + let final_iface = completePartialModIface iface0 iface_hash + sorted_decls sorted_extra_decls abiHashes caches + -- + return final_iface + + + +-- The ABI hash should depend on everything in IfacePublic +-- This is however computed in a very convoluted way, so be careful your +-- addition ends up in the right place. In essence all this function does is +-- compute a hash of the arguments. +-- +-- Why the convoluted way? Hashing individual declarations allows us to do fine-grained +-- recompilation checking for home package modules, which record precisely what they use +-- from each module. +addAbiHashes :: HscEnv -> IfaceModInfo -> PartialIfacePublic -> Dependencies -> IO (IfaceAbiHashes, IfaceCache, [(Fingerprint, IfaceDecl)]) +addAbiHashes hsc_env info iface_public deps = do + eps <- hscEPS hsc_env + let + -- If you have arrived here by accident then congratulations, + -- you have discovered the ABI hash. Your reward is to update the ABI hash to + -- account for your change to the interface file. Omitting your field using a + -- wildcard may lead to some unfortunate consequences. + + -- MP: TODO: Existing bug where defaults, trust_pkg and complete are not taken into account + -- when computing the ABI hash. + IfacePublic exports fixities warns anns decls _defaults insts fam_insts rules trust _trust_pkg _complete _cache () = iface_public + -- And these fields of deps should be in IfacePublic, but in good time. + Dependencies _ _ _ sig_mods trusted_pkgs boot_mods orph_mods fis_mods = deps + decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings warns) + export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ warns) + fix_fn = mkIfaceFixCache fixities + + this_mod = mi_mod_info_module info + semantic_mod = mi_mod_info_semantic_module info + (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph insts + (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph rules + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph fam_insts + ann_fn = mkIfaceAnnCache anns -- The ABI of a declaration represents everything that is made -- visible about the declaration that a client can depend on. -- see IfaceDeclABI below. - declABI :: IfaceDecl -> IfaceDeclABI + declABI :: IfaceDecl -> IfaceDeclABI -- TODO: I'm not sure if this should be semantic_mod or this_mod. -- See also Note [Identity versus semantic module] - declABI decl = (this_mod, decl, extras) + declABI decl = (this_mod, decl, extras) where extras = declExtras fix_fn ann_fn non_orph_rules non_orph_insts non_orph_fis top_lvl_name_env decl -- This is used for looking up the Name of a default method -- from its OccName. See Note [default method Name] - top_lvl_name_env = + top_lvl_name_env = mkOccEnv [ (nameOccName nm, nm) | IfaceId { ifName = nm } <- decls ] @@ -1047,15 +1112,15 @@ addFingerprints hsc_env iface0 -- This is computed by finding the free external names of each -- declaration, including IfaceDeclExtras (things that a -- declaration implicitly depends on). - edges :: [ Node OccName IfaceDeclABI ] - edges = [ DigraphNode abi (getOccName decl) out + edges :: [ Node OccName IfaceDeclABI ] + edges = [ DigraphNode abi (getOccName decl) out | decl <- decls , let abi = declABI decl , let out = localOccs $ freeNamesDeclABI abi ] - name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) - localOccs = + name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) + localOccs = map (getParent . getOccName) -- NB: names always use semantic module, so -- filtering must be on the semantic module! @@ -1073,17 +1138,17 @@ addFingerprints hsc_env iface0 -- maps OccNames to their parents in the current module. -- e.g. a reference to a constructor must be turned into a reference -- to the TyCon for the purposes of calculating dependencies. - parent_map :: OccEnv OccName - parent_map = foldl' extend emptyOccEnv decls + parent_map :: OccEnv OccName + parent_map = foldl' extend emptyOccEnv decls where extend env d = extendOccEnvList env [ (b,n) | b <- ifaceDeclImplicitBndrs d ] where n = getOccName d -- Strongly-connected groups of declarations, in dependency order - groups :: [SCC IfaceDeclABI] - groups = stronglyConnCompFromEdgedVerticesOrd edges + groups :: [SCC IfaceDeclABI] + groups = stronglyConnCompFromEdgedVerticesOrd edges - global_hash_fn = mkHashFun hsc_env eps + global_hash_fn = mkHashFun hsc_env eps -- How to output Names when generating the data to fingerprint. -- Here we want to output the fingerprint for each top-level @@ -1091,9 +1156,9 @@ addFingerprints hsc_env iface0 -- module. In this way, the fingerprint for a declaration will -- change if the fingerprint for anything it refers to (transitively) -- changes. - mk_put_name :: OccEnv (OccName,Fingerprint) + mk_put_name :: OccEnv (OccName,Fingerprint) -> WriteBinHandle -> Name -> IO () - mk_put_name local_env bh name + mk_put_name local_env bh name | isWiredInName name = putNameLiterally bh name -- wired-in names don't have fingerprints | otherwise @@ -1120,21 +1185,21 @@ addFingerprints hsc_env iface0 -- take a strongly-connected group of declarations and compute -- its fingerprint. - fingerprint_group :: (OccEnv (OccName,Fingerprint), + fingerprint_group :: (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) -> SCC IfaceDeclABI -> IO (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) - fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) - = do let hash_fn = mk_put_name local_env - decl = abiDecl abi + fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) + = do let hash_fn = mk_put_name local_env + decl = abiDecl abi --pprTrace "fingerprinting" (ppr (ifName decl) ) $ do - hash <- computeFingerprint hash_fn abi - env' <- extend_hash_env local_env (hash,decl) - return (env', (hash,decl) : decls_w_hashes) + hash <- computeFingerprint hash_fn abi + env' <- extend_hash_env local_env (hash,decl) + return (env', (hash,decl) : decls_w_hashes) - fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) + fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) = do let stable_abis = sortBy cmp_abiNames abis stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env @@ -1150,33 +1215,27 @@ addFingerprints hsc_env iface0 return (local_env2, pairs ++ decls_w_hashes) -- Make a fingerprint from the ordinal position of a binding in its group. - mkRecFingerprint :: Word64 -> Fingerprint - mkRecFingerprint i = Fingerprint 0 i + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i - bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint - bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. -- - extend_hash_env :: OccEnv (OccName,Fingerprint) + extend_hash_env :: OccEnv (OccName,Fingerprint) -> (Fingerprint,IfaceDecl) -> IO (OccEnv (OccName,Fingerprint)) - extend_hash_env env0 (hash,d) = + extend_hash_env env0 (hash,d) = return (foldr (\(b,fp) env -> extendOccEnv env b (b,fp)) env0 (ifaceDeclFingerprints hash d)) -- - (local_env, decls_w_hashes) <- + (local_env, decls_w_hashes) <- foldM fingerprint_group (emptyOccEnv, []) groups - -- when calculating fingerprints, we always need to use canonical ordering - -- for lists of things. The mi_deps has various lists of modules and - -- suchlike, which are stored in canonical order: - let sorted_deps :: Dependencies - sorted_deps = mi_deps iface0 - -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way -- that changes in orphans get propagated all the way up the @@ -1202,10 +1261,11 @@ addFingerprints hsc_env iface0 -- External. It's true that Home1 will get rebuilt if the orphans -- of External, but we also need to make sure Home2 gets rebuilt -- as well. See #12733 for more details. - let orph_mods - = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] - $ dep_orphs sorted_deps - dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods + let orph_mods_no_self + = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] + $ orph_mods + dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods_no_self + -- Note [Do not update EPS with your own hi-boot] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1216,26 +1276,26 @@ addFingerprints hsc_env iface0 -- instances yourself, no need to consult hs-boot; if you do load the -- interface into EPS, you will see a duplicate orphan instance. - orphan_hash <- computeFingerprint (mk_put_name local_env) + orphan_hash <- computeFingerprint (mk_put_name local_env) (map ifDFun orph_insts, orph_rules, orph_fis) - -- Hash of the transitive things in dependencies - dep_hash <- computeFingerprint putNameLiterally - (dep_sig_mods (mi_deps iface0), - dep_boot_mods (mi_deps iface0), - -- Trusted packages are like orphans - dep_trusted_pkgs (mi_deps iface0), + -- Hash of the transitive things in dependencies + dep_hash <- computeFingerprint putNameLiterally + (sig_mods, + boot_mods, + -- Trusted packages are like orphans + trusted_pkgs, -- See Note [Export hash depends on non-orphan family instances] - dep_finsts (mi_deps iface0) ) + fis_mods ) - -- the export list hash doesn't depend on the fingerprints of - -- the Names it mentions, only the Names themselves, hence putNameLiterally. - export_hash <- computeFingerprint putNameLiterally - (mi_exports iface0, + -- the export list hash doesn't depend on the fingerprints of + -- the Names it mentions, only the Names themselves, hence putNameLiterally. + export_hash <- computeFingerprint putNameLiterally + (exports, orphan_hash, dep_hash, dep_orphan_hashes, - mi_trust iface0) + trust) -- Make sure change of Safe Haskell mode causes recomp. -- Note [Export hash depends on non-orphan family instances] @@ -1266,79 +1326,44 @@ addFingerprints hsc_env iface0 -- (also we didn't store it anywhere!) -- - -- put the declarations in a canonical order, sorted by OccName - let sorted_decls :: [(Fingerprint, IfaceDecl)] - sorted_decls = Map.elems $ Map.fromList $ - [(getOccName d, e) | e@(_, d) <- decls_w_hashes] - -- This key is safe because mi_extra_decls contains tidied things. - getOcc (IfGblTopBndr b) = getOccName b - getOcc (IfLclTopBndr fs _ _ details) = - case details of - IfRecSelId { ifRecSelFirstCon = first_con } - -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) - _ -> mkVarOccFS (ifLclNameFS fs) - - binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () - binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) - - sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - - -- the ABI hash depends on: - -- - decls - -- - export list - -- - orphans - -- - deprecations - -- - flag abi hash - -- - foreign stubs and files - mod_hash <- computeFingerprint putNameLiterally - (map fst sorted_decls, + -- the ABI hash depends on: + -- - decls + -- - export list + -- - orphans + -- - deprecations + -- - flag abi hash + mod_hash <- computeFingerprint putNameLiterally + (sort (map fst decls_w_hashes), export_hash, -- includes orphan_hash - mi_warns iface0, - mi_foreign iface0) - - - -- The interface hash depends on: - -- - the ABI hash, plus - -- - the things which can affect whether a module is recompiled - -- - the module level annotations, - -- - deps (home and external packages, dependent files) - iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_self_recomp_info iface0, - sorted_deps ) + ann_fn AnnModule, + warns) - let - final_iface_exts = ModIfaceBackend - { mi_mod_hash = mod_hash - , mi_iface_hash = iface_hash - , mi_orphan = not ( all ifRuleAuto orph_rules + -- Surely the ABI depends on "module" annotations? + -- Also named defaults + + + + let + final_iface_exts = IfaceAbiHashes + { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts && null orph_fis) - , mi_finsts = not (null (mi_fam_insts iface0)) - , mi_exp_hash = export_hash - , mi_orphan_hash = orphan_hash - , mi_decl_warn_fn = decl_warn_fn - , mi_export_warn_fn = export_warn_fn - , mi_fix_fn = fix_fn - , mi_hash_fn = lookupOccEnv local_env + , mi_abi_finsts = not (null fam_insts) + , mi_abi_exp_hash = export_hash + , mi_abi_orphan_hash = orphan_hash } - final_iface = completePartialModIface iface0 - sorted_decls sorted_extra_decls final_iface_exts - -- - return final_iface + caches = IfaceCache + { mi_cache_decl_warn_fn = decl_warn_fn + , mi_cache_export_warn_fn = export_warn_fn + , mi_cache_fix_fn = fix_fn + , mi_cache_hash_fn = lookupOccEnv local_env + } + return (final_iface_exts, caches, decls_w_hashes) where - this_mod = mi_module iface0 - semantic_mod = mi_semantic_module iface0 - (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) - (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) - (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - ann_fn = mkIfaceAnnCache (mi_anns iface0) - -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the @@ -1378,7 +1403,7 @@ getOrphanHashes hsc_env mods = do get_orph_hash mod = do iface <- initIfaceLoad hsc_env . withIfaceErr ctx $ loadInterface (text "getOrphanHashes") mod ImportBySystem - return (mi_orphan_hash (mi_final_exts iface)) + return (mi_orphan_hash iface) mapM get_orph_hash mods @@ -1531,7 +1556,7 @@ instance Binary IfaceIdExtras where put_ bh (IdExtras fix rules anns)= do { put_ bh fix; put_ bh rules; put_ bh anns } declExtras :: (OccName -> Maybe Fixity) - -> (OccName -> [AnnPayload]) + -> (AnnCacheKey -> [AnnPayload]) -> OccEnv [IfaceRule] -> OccEnv [IfaceClsInst] -> OccEnv [IfaceFamInst] @@ -1546,10 +1571,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl IfaceDataExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n) ++ map ifDFun (lookupOccEnvL inst_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) (map (id_extras . occName . ifConName) (visibleIfConDecls cons)) IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} -> - IfaceClassExtras (fix_fn n) insts (ann_fn n) meths defms + IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms where insts = (map ifDFun $ (concatMap at_extras ats) ++ lookupOccEnvL inst_env n) @@ -1562,17 +1587,16 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl , let dmOcc = mkDefaultMethodOcc (nameOccName bndr) , Just dmName <- [lookupOccEnv dm_env dmOcc] ] IfaceSynonym{} -> IfaceSynonymExtras (fix_fn n) - (ann_fn n) + (ann_fn (AnnOccName n)) IfaceFamily{} -> IfaceFamilyExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) _other -> IfaceOtherDeclExtras where n = getOccName decl - id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn occ) + id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl) - {- Note [default method Name] (see also #15970) ~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1685,20 +1709,25 @@ mkHashFun hsc_env eps name -- just one of the many horrible hacks in the backpack -- implementation. $ loadInterface (text "lookupVers2") mod ImportBySystem - return $ snd (mi_hash_fn (mi_final_exts iface) occ `orElse` + return $ snd (mi_hash_fn iface occ `orElse` pprPanic "lookupVers1" (ppr mod <+> ppr occ)) +data AnnCacheKey = AnnModule | AnnOccName OccName + -- | Creates cached lookup for the 'mi_anns' field of ModIface -- Hackily, we use "module" as the OccName for any module-level annotations -mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload] +mkIfaceAnnCache :: [IfaceAnnotation] -> AnnCacheKey -> [AnnPayload] mkIfaceAnnCache anns - = \n -> lookupOccEnv env n `orElse` [] + = \n -> case n of + AnnModule -> module_anns + AnnOccName occn -> lookupOccEnv env occn `orElse` [] where - pair (IfaceAnnotation target value) = - (case target of - NamedTarget occn -> occn - ModuleTarget _ -> mkVarOccFS (fsLit "module") - , [value]) + (module_anns, occ_anns) = partitionEithers $ map classify anns + classify (IfaceAnnotation target value) = + case target of + NamedTarget occn -> Right (occn, [value]) + ModuleTarget _ -> Left value + -- flipping (++), so the first argument is always short - env = mkOccEnv_C (flip (++)) (map pair anns) + env = mkOccEnv_C (flip (++)) occ_anns ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,5 +1,5 @@ module GHC.Iface.Recomp.Types ( - ModIfaceSelfRecomp(..), + IfaceSelfRecomp(..), IfaceDynFlags(..), pprIfaceDynFlags, missingExtraFlagInfo, @@ -9,7 +9,9 @@ import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable import GHC.Iface.Flags +import GHC.Types.SafeHaskell import GHC.Unit.Module.Deps +import GHC.Unit.Module import GHC.Utils.Binary @@ -59,8 +61,8 @@ proper way. -- itself. -- -- See Note [Self recompilation information in interface files] -data ModIfaceSelfRecomp = - ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint +data IfaceSelfRecomp = + IfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint -- ^ Hash of the .hs source, used for recompilation checking. , mi_sr_usages :: [Usage] -- ^ Usages; kept sorted so that it's easy to decide @@ -69,7 +71,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) + , mi_sr_flag_hash :: !(FingerprintWithValue IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -81,8 +83,8 @@ data ModIfaceSelfRecomp = } -instance Binary ModIfaceSelfRecomp where - put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do +instance Binary IfaceSelfRecomp where + put_ bh (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do put_ bh mi_sr_src_hash lazyPut bh mi_sr_usages put_ bh mi_sr_flag_hash @@ -97,19 +99,58 @@ instance Binary ModIfaceSelfRecomp where opt_hash <- get bh hpc_hash <- get bh plugin_hash <- get bh - return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + return $ IfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } -instance Outputable ModIfaceSelfRecomp where - ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) +instance Outputable IfaceSelfRecomp where + ppr (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash - , text "usages:" <+> ppr (length mi_sr_usages) - , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash + , text "flags:" <+> pprFingerprintWithValue missingExtraFlagInfo (fmap pprIfaceDynFlags mi_sr_flag_hash) , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash + , text "usages:" <+> ppr (map pprUsage mi_sr_usages) ])] -instance NFData ModIfaceSelfRecomp where - rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file +instance NFData IfaceSelfRecomp where + rnf (IfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () + +pprFingerprintWithValue :: SDoc -> FingerprintWithValue SDoc -> SDoc +pprFingerprintWithValue missingInfo (FingerprintWithValue fp mflags) + = vcat $ + [ text "fingerprint:" <+> (ppr fp) + ] + ++ case mflags of + Nothing -> [missingInfo] + Just doc -> [doc] + +pprUsage :: Usage -> SDoc +pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } + = pprUsageImport mod hash safe +pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name + , usg_mod_hash = hash, usg_safe = safe + , usg_exports = exports, usg_entities = entities } + = pprUsageImport (mkModule unit_id mod_name) hash safe $$ + nest 2 ( + maybe empty (\v -> text "exports: " <> ppr v) exports $$ + vcat [ ppr n <+> ppr v | (n,v) <- entities ] + ) +pprUsage usage at UsageFile{} + = hsep [text "addDependentFile", + doubleQuotes (ftext (usg_file_path usage)), + ppr (usg_file_hash usage)] +pprUsage usage at UsageMergedRequirement{} + = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] +pprUsage usage at UsageHomeModuleInterface{} + = hsep [text "implementation", ppr (usg_mod_name usage) + , ppr (usg_unit_id usage) + , ppr (usg_iface_hash usage)] + +pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc +pprUsageImport mod hash safe + = hsep [ text "import", pp_safe, ppr mod + , ppr hash ] + where + pp_safe | safe = text "safe" + | otherwise = text " -/ " \ No newline at end of file ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -183,7 +183,7 @@ lookupFixityRn_help name -- loadInterfaceForName will find B.hi even if B is a hidden module, -- and that's what we want. = do { iface <- loadInterfaceForName doc name - ; let mb_fix = mi_fix_fn (mi_final_exts iface) occ + ; let mb_fix = mi_fix_fn iface occ ; let msg = case mb_fix of Nothing -> text "looking up name" <+> ppr name ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -485,8 +485,8 @@ calculateAvails :: HomeUnit calculateAvails home_unit other_home_units iface mod_safe' want_boot imported_by = let imp_mod = mi_module iface imp_sem_mod= mi_semantic_module iface - orph_iface = mi_orphan (mi_final_exts iface) - has_finsts = mi_finsts (mi_final_exts iface) + orph_iface = mi_orphan iface + has_finsts = mi_finsts iface deps = mi_deps iface trust = getSafeMode $ mi_trust iface trust_pkg = mi_trust_pkg iface @@ -1397,7 +1397,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) _ -> failLookupWith err mk_depr_export_warning gre - = DeprecatedExport name <$> mi_export_warn_fn (mi_final_exts iface) name + = DeprecatedExport name <$> mi_export_warn_fn iface name where name = greName gre ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -539,9 +539,9 @@ warnIfDeclDeprecated gre@(GRE { gre_imp = iss }) lookupImpDeclDeprec :: ModIface -> GlobalRdrElt -> Maybe (WarningTxt GhcRn) lookupImpDeclDeprec iface gre -- Bleat if the thing, or its parent, is warn'd - = mi_decl_warn_fn (mi_final_exts iface) (greOccName gre) `mplus` + = mi_decl_warn_fn iface (greOccName gre) `mplus` case greParent gre of - ParentIs p -> mi_decl_warn_fn (mi_final_exts iface) (nameOccName p) + ParentIs p -> mi_decl_warn_fn iface (nameOccName p) NoParent -> Nothing warnIfExportDeprecated :: GlobalRdrElt -> RnM () @@ -562,7 +562,7 @@ warnIfExportDeprecated gre@(GRE { gre_imp = iss }) process_import_spec is = do let mod = is_mod $ is_decl is iface <- loadInterfaceForModule doc mod - let mb_warn_txt = mi_export_warn_fn (mi_final_exts iface) name + let mb_warn_txt = mi_export_warn_fn iface name return $ (moduleName mod, ) <$> mb_warn_txt ------------------------- ===================================== compiler/GHC/Tc/Instance/Family.hs ===================================== @@ -308,7 +308,7 @@ checkFamInstConsistency directlyImpMods ifc <- modIface mod deps <- dep_finsts . mi_deps <$> modIface mod pure $ - if mi_finsts (mi_final_exts ifc) + if mi_finsts ifc then mod:deps else deps ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -97,7 +97,7 @@ checkHsigDeclM sig_iface sig_thing real_thing = do -- implementation cases. checkBootDeclM Hsig sig_thing real_thing real_fixity <- lookupFixityRn name - let sig_fixity = case mi_fix_fn (mi_final_exts sig_iface) (occName name) of + let sig_fixity = case mi_fix_fn sig_iface (occName name) of Nothing -> defaultFixity Just f -> f when (real_fixity /= sig_fixity) $ @@ -850,7 +850,7 @@ mergeSignatures if outer_mod == mi_module iface -- Don't add ourselves! then tcg_merged tcg_env - else (mi_module iface, mi_mod_hash (mi_final_exts iface)) : tcg_merged tcg_env + else (mi_module iface, mi_mod_hash iface) : tcg_merged tcg_env } -- Note [Signature merging DFuns] ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -1,18 +1,20 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ExplicitNamespaces #-} -- | Dependencies and Usage of a module module GHC.Unit.Module.Deps - ( Dependencies - , mkDependencies - , noDependencies - , dep_direct_mods - , dep_direct_pkgs - , dep_sig_mods - , dep_trusted_pkgs - , dep_orphs - , dep_plugin_pkgs - , dep_finsts - , dep_boot_mods + ( Dependencies(dep_direct_mods + , dep_direct_pkgs + , dep_sig_mods + , dep_trusted_pkgs + , dep_orphs + , dep_plugin_pkgs + , dep_finsts + , dep_boot_mods + , Dependencies) , dep_orphs_update , dep_finsts_update + , mkDependencies + , noDependencies , pprDeps , Usage (..) , ImportAvails (..) @@ -52,38 +54,38 @@ import Control.DeepSeq -- -- See Note [Transitive Information in Dependencies] data Dependencies = Deps - { dep_direct_mods :: Set (UnitId, ModuleNameWithIsBoot) + { dep_direct_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All home-package modules which are directly imported by this one. -- This may include modules from other units when using multiple home units - , dep_direct_pkgs :: Set UnitId + , dep_direct_pkgs_ :: Set UnitId -- ^ All packages directly imported by this module -- I.e. packages to which this module's direct imports belong. -- Does not include other home units when using multiple home units. -- Modules from these units will go in `dep_direct_mods` - , dep_plugin_pkgs :: Set UnitId + , dep_plugin_pkgs_ :: Set UnitId -- ^ All units needed for plugins ------------------------------------ -- Transitive information below here - , dep_sig_mods :: ![ModuleName] + , dep_sig_mods_ :: ![ModuleName] -- ^ Transitive closure of hsig files in the home package - , dep_trusted_pkgs :: Set UnitId + , dep_trusted_pkgs_ :: Set UnitId -- Packages which we are required to trust -- when the module is imported as a safe import -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names - , dep_boot_mods :: Set (UnitId, ModuleNameWithIsBoot) + , dep_boot_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All modules which have boot files below this one, and whether we -- should use the boot file or not. -- This information is only used to populate the eps_is_boot field. -- See Note [Structure of dep_boot_mods] - , dep_orphs :: [Module] + , dep_orphs_ :: [Module] -- ^ Transitive closure of orphan modules (whether -- home or external pkg). -- @@ -93,7 +95,7 @@ data Dependencies = Deps -- which relies on dep_orphs having the complete list!) -- This does NOT include us, unlike 'imp_orphs'. - , dep_finsts :: [Module] + , dep_finsts_ :: [Module] -- ^ Transitive closure of depended upon modules which -- contain family instances (whether home or external). -- This is used by 'checkFamInstConsistency'. This @@ -105,6 +107,26 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +pattern Dependencies :: Set (UnitId, ModuleNameWithIsBoot) + -> Set UnitId + -> Set UnitId + -> [ModuleName] + -> Set UnitId + -> Set (UnitId, ModuleNameWithIsBoot) + -> [Module] + -> [Module] + -> Dependencies +pattern Dependencies {dep_direct_mods, dep_direct_pkgs, dep_plugin_pkgs, dep_sig_mods, dep_trusted_pkgs, dep_boot_mods, dep_orphs, dep_finsts} + <- Deps {dep_direct_mods_ = dep_direct_mods + , dep_direct_pkgs_ = dep_direct_pkgs + , dep_plugin_pkgs_ = dep_plugin_pkgs + , dep_sig_mods_ = dep_sig_mods + , dep_trusted_pkgs_ = dep_trusted_pkgs + , dep_boot_mods_ = dep_boot_mods + , dep_orphs_ = dep_orphs + , dep_finsts_ = dep_finsts} +{-# COMPLETE Dependencies #-} + instance NFData Dependencies where rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) = rnf dmods @@ -158,14 +180,14 @@ mkDependencies home_unit mod imports plugin_mods = sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports - in Deps { dep_direct_mods = direct_mods - , dep_direct_pkgs = direct_pkgs - , dep_plugin_pkgs = plugin_units - , dep_sig_mods = sort sig_mods - , dep_trusted_pkgs = trust_pkgs - , dep_boot_mods = source_mods - , dep_orphs = sortBy stableModuleCmp dep_orphs - , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) + in Deps { dep_direct_mods_ = direct_mods + , dep_direct_pkgs_ = direct_pkgs + , dep_plugin_pkgs_ = plugin_units + , dep_sig_mods_ = sort sig_mods + , dep_trusted_pkgs_ = trust_pkgs + , dep_boot_mods_ = source_mods + , dep_orphs_ = sortBy stableModuleCmp dep_orphs + , dep_finsts_ = sortBy stableModuleCmp (imp_finsts imports) -- sort to get into canonical order -- NB. remember to use lexicographic ordering } @@ -174,14 +196,13 @@ mkDependencies home_unit mod imports plugin_mods = dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_orphs_update deps f = do r <- f (dep_orphs deps) - pure (deps { dep_orphs = sortBy stableModuleCmp r }) + pure (deps { dep_orphs_ = sortBy stableModuleCmp r }) -- | Update module dependencies containing family instances (used by Backpack) dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_finsts_update deps f = do r <- f (dep_finsts deps) - pure (deps { dep_finsts = sortBy stableModuleCmp r }) - + pure (deps { dep_finsts_ = sortBy stableModuleCmp r }) instance Binary Dependencies where put_ bh deps = do put_ bh (dep_direct_mods deps) @@ -201,36 +222,36 @@ instance Binary Dependencies where sms <- get bh os <- get bh fis <- get bh - return (Deps { dep_direct_mods = dms - , dep_direct_pkgs = dps - , dep_plugin_pkgs = plugin_pkgs - , dep_sig_mods = hsigms - , dep_boot_mods = sms - , dep_trusted_pkgs = tps - , dep_orphs = os, - dep_finsts = fis }) + return (Deps { dep_direct_mods_ = dms + , dep_direct_pkgs_ = dps + , dep_plugin_pkgs_ = plugin_pkgs + , dep_sig_mods_ = hsigms + , dep_boot_mods_ = sms + , dep_trusted_pkgs_ = tps + , dep_orphs_ = os, + dep_finsts_ = fis }) noDependencies :: Dependencies noDependencies = Deps - { dep_direct_mods = Set.empty - , dep_direct_pkgs = Set.empty - , dep_plugin_pkgs = Set.empty - , dep_sig_mods = [] - , dep_boot_mods = Set.empty - , dep_trusted_pkgs = Set.empty - , dep_orphs = [] - , dep_finsts = [] + { dep_direct_mods_ = Set.empty + , dep_direct_pkgs_ = Set.empty + , dep_plugin_pkgs_ = Set.empty + , dep_sig_mods_ = [] + , dep_boot_mods_ = Set.empty + , dep_trusted_pkgs_ = Set.empty + , dep_orphs_ = [] + , dep_finsts_ = [] } -- | Pretty-print unit dependencies pprDeps :: UnitState -> Dependencies -> SDoc -pprDeps unit_state (Deps { dep_direct_mods = dmods - , dep_boot_mods = bmods - , dep_plugin_pkgs = plgns - , dep_orphs = orphs - , dep_direct_pkgs = pkgs - , dep_trusted_pkgs = tps - , dep_finsts = finsts +pprDeps unit_state (Deps { dep_direct_mods_ = dmods + , dep_boot_mods_ = bmods + , dep_plugin_pkgs_ = plgns + , dep_orphs_ = orphs + , dep_direct_pkgs_ = pkgs + , dep_trusted_pkgs_ = tps + , dep_finsts_ = finsts }) = pprWithUnitState unit_state $ vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -11,18 +11,20 @@ module GHC.Unit.Module.ModIface ( ModIface , ModIface_ - ( mi_module + ( mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls , mi_defaults - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_top_env , mi_insts , mi_fam_insts @@ -31,12 +33,17 @@ module GHC.Unit.Module.ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn ) , pattern ModIface + , set_mi_mod_info , set_mi_module , set_mi_sig_of , set_mi_hsc_src @@ -52,24 +59,34 @@ module GHC.Unit.Module.ModIface , set_mi_rules , set_mi_decls , set_mi_defaults - , set_mi_extra_decls - , set_mi_foreign + , set_mi_simplified_core , set_mi_top_env , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches , set_mi_docs - , set_mi_final_exts + , set_mi_abi_hashes , set_mi_ext_fields + , set_mi_caches + , set_mi_decl_warn_fn + , set_mi_export_warn_fn + , set_mi_fix_fn + , set_mi_hash_fn , completePartialModIface , IfaceBinHandle(..) , PartialModIface - , ModIfaceBackend (..) - , ModIfaceSelfRecomp (..) + , IfaceAbiHashes (..) + , IfaceSelfRecomp (..) + , IfaceCache (..) + , IfaceSimplifiedCore (..) , withSelfRecomp , IfaceDeclExts - , IfaceBackendExts + , IfaceAbiHashesExts , IfaceExport + , IfacePublic_(..) + , IfacePublic + , PartialIfacePublic + , IfaceModInfo(..) , WhetherHasOrphans , WhetherHasFamInst , IfaceTopEnv (..) @@ -77,6 +94,7 @@ module GHC.Unit.Module.ModIface , mi_boot , mi_fix , mi_semantic_module + , mi_mod_info_semantic_module , mi_free_holes , mi_mnwib , mi_flag_hash @@ -85,6 +103,11 @@ module GHC.Unit.Module.ModIface , mi_plugin_hash , mi_src_hash , mi_usages + , mi_mod_hash + , mi_orphan + , mi_finsts + , mi_exp_hash + , mi_orphan_hash , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,7 +129,7 @@ import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings -import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..)) import GHC.Types.Avail @@ -147,36 +170,36 @@ We can build a full interface file two ways: type PartialModIface = ModIface_ 'ModIfaceCore type ModIface = ModIface_ 'ModIfaceFinal --- | Extends a PartialModIface with information which is either: --- * Computed after codegen --- * Or computed just before writing the iface to disk. (Hashes) --- In order to fully instantiate it. -data ModIfaceBackend = ModIfaceBackend - { mi_mod_hash :: !Fingerprint +type PartialIfacePublic = IfacePublic_ 'ModIfaceCore +type IfacePublic = IfacePublic_ 'ModIfaceFinal + +-- | Extends a PartialModIface with hashes of the ABI. +-- +-- * The mi_mod_hash is the hash of the entire ABI +-- * THe other fields are more specific hashes of parts of the ABI +data IfaceAbiHashes = IfaceAbiHashes + { mi_abi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_orphan :: !WhetherHasOrphans + , mi_abi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans - , mi_finsts :: !WhetherHasFamInst + , mi_abi_finsts :: !WhetherHasFamInst -- ^ Whether this module has family instances. See Note [The type family -- instance consistency story]. - , mi_exp_hash :: !Fingerprint + , mi_abi_exp_hash :: !Fingerprint -- ^ Hash of export list - , mi_orphan_hash :: !Fingerprint + , mi_abi_orphan_hash :: !Fingerprint -- ^ Hash for orphan rules, class and family instances combined + -- NOT transitive + } - -- Cached environments for easy lookup. These are computed (lazily) from - -- other fields and are not put into the interface file. - -- Not really produced by the backend but there is no need to create them - -- any earlier. - , mi_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) +data IfaceCache = IfaceCache + { mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for declaration deprecations - , mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) + , mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for export deprecations - , mi_fix_fn :: !(OccName -> Maybe Fixity) + , mi_cache_fix_fn :: !(OccName -> Maybe Fixity) -- ^ Cached lookup for 'mi_fixities' - , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) + , mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that -- the thing isn't in decls. It's useful to know that when seeing if we are -- up to date wrt. the old interface. The 'OccName' is the parent of the @@ -195,9 +218,9 @@ type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where IfaceDeclExts 'ModIfaceCore = IfaceDecl IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) -type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where - IfaceBackendExts 'ModIfaceCore = () - IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend +type family IfaceAbiHashesExts (phase :: ModIfacePhase) = bk | bk -> phase where + IfaceAbiHashesExts 'ModIfaceCore = () + IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes -- | In-memory byte array representation of a 'ModIface'. -- @@ -212,7 +235,7 @@ data IfaceBinHandle (phase :: ModIfacePhase) where FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp :: ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r withSelfRecomp iface nk jk = case mi_self_recomp_info iface of Nothing -> nk @@ -220,34 +243,80 @@ withSelfRecomp iface nk jk = --- | A 'ModIface' plus a 'ModDetails' summarises everything we know --- about a compiled module. The 'ModIface' is the stuff *before* linking, --- and can be written out to an interface file. The 'ModDetails is after --- linking and can be completely recovered from just the 'ModIface'. +-- | A 'ModIface' summarises everything we know +-- about a compiled module. -- --- When we read an interface file, we also construct a 'ModIface' from it, --- except that we explicitly make the 'mi_decls' and a few other fields empty; --- as when reading we consolidate the declarations etc. into a number of indexed --- maps and environments in the 'ExternalPackageState'. +-- See Note [Structure of ModIface] for information about what belongs in each field. -- --- See Note [Strictness in ModIface] to learn about why some fields are --- strict and others are not. +-- See Note [Strictness in ModIface] to learn about why all the fields are lazy. -- -- See Note [Private fields in ModIface] to learn why we don't export any of the -- fields. data ModIface_ (phase :: ModIfacePhase) = PrivateModIface { - mi_module_ :: !Module, -- ^ Name of the module we are for - mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? + mi_hi_bytes_ :: !(IfaceBinHandle phase), + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. + mi_iface_hash_ :: Fingerprint, -- A hash of the whole interface - mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? + mi_mod_info_ :: IfaceModInfo, + -- ^ Meta information about the module the interface file is for mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) + -- MP: Needs to be refactored (#25844) + + mi_public_ :: IfacePublic_ phase, + -- ^ The parts of interface which are used by other modules when + -- importing this module. The main, original part of an interface. - mi_exports_ :: ![IfaceExport], + + mi_self_recomp_ :: Maybe IfaceSelfRecomp, + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] + + mi_simplified_core_ :: Maybe IfaceSimplifiedCore, + -- ^ The part of the interface written when `-fwrite-if-simplified-core` is enabled. + -- These parts are used to restart bytecode generation. + + mi_docs_ :: Maybe Docs, + -- ^ Docstrings and related data for use by haddock, the ghci + -- @:doc@ command, and other tools. + -- + -- @Just _@ @<=>@ the module was built with @-haddock at . + + mi_top_env_ :: IfaceTopEnv, + -- ^ Just enough information to reconstruct the top level environment in + -- the /original source/ code for this module. which + -- is NOT the same as mi_exports, nor mi_decls (which + -- may contains declarations for things not actually + -- defined by the user). Used for GHCi and for inspecting + -- the contents of modules via the GHC API only. + + mi_ext_fields_ :: ExtensibleFields + -- ^ Additional optional fields, where the Map key represents + -- the field name, resulting in a (size, serialized data) pair. + -- Because the data is intended to be serialized through the + -- internal `Binary` class (increasing compatibility with types + -- using `Name` and `FastString`, such as HIE), this format is + -- chosen over `ByteString`s. + } + +-- | Meta information about the module the interface file is for +data IfaceModInfo = IfaceModInfo { + mi_mod_info_module :: Module, -- ^ Name of the module we are for + mi_mod_info_sig_of :: Maybe Module, -- ^ Are we a sig of another mod? + mi_mod_info_hsc_src :: HscSource -- ^ Boot? Signature? +} + +-- | The public interface of a module which are used by other modules when importing this module. +-- The ABI of a module. +data IfacePublic_ phase = IfacePublic { + mi_exports_ :: [IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things @@ -273,25 +342,10 @@ data ModIface_ (phase :: ModIfacePhase) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], - -- ^ Extra variable definitions which are **NOT** exposed but when - -- combined with mi_decls allows us to restart code generation. - -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - - mi_foreign_ :: !IfaceForeign, - -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. - -- See Note [Foreign stubs and TH bytecode linking] mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: IfaceTopEnv, - -- ^ Just enough information to reconstruct the top level environment in - -- the /original source/ code for this module. which - -- is NOT the same as mi_exports, nor mi_decls (which - -- may contains declarations for things not actually - -- defined by the user). Used for GHCi and for inspecting - -- the contents of modules via the GHC API only. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -299,53 +353,81 @@ data ModIface_ (phase :: ModIfacePhase) mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_trust_ :: !IfaceTrustInfo, + mi_trust_ :: IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg_ :: !Bool, + mi_trust_pkg_ :: Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches_ :: ![IfaceCompleteMatch], + mi_complete_matches_ :: [IfaceCompleteMatch], + -- ^ {-# COMPLETE #-} declarations - mi_docs_ :: !(Maybe Docs), - -- ^ Docstrings and related data for use by haddock, the ghci - -- @:doc@ command, and other tools. - -- - -- @Just _@ @<=>@ the module was built with @-haddock at . + mi_caches_ :: IfaceCache, + -- ^ Cached lookups of some parts of mi_public - mi_final_exts_ :: !(IfaceBackendExts phase), - -- ^ Either `()` or `ModIfaceBackend` for + mi_abi_hashes_ :: (IfaceAbiHashesExts phase) + -- ^ Either `()` or `IfaceAbiHashes` for -- a fully instantiated interface. - - mi_ext_fields_ :: !ExtensibleFields, - -- ^ Additional optional fields, where the Map key represents - -- the field name, resulting in a (size, serialized data) pair. - -- Because the data is intended to be serialized through the - -- internal `Binary` class (increasing compatibility with types - -- using `Name` and `FastString`, such as HIE), this format is - -- chosen over `ByteString`s. - -- - - mi_hi_bytes_ :: !(IfaceBinHandle phase), - -- ^ A serialised in-memory buffer of this 'ModIface'. - -- If this handle is given, we can avoid serialising the 'ModIface' - -- when writing this 'ModIface' to disk, and write this buffer to disk instead. - -- See Note [Sharing of ModIface]. - - mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) - -- ^ Information needed for checking self-recompilation. - -- See Note [Self recompilation information in interface files] - } + -- These fields are hashes of different parts of the public interface. +} + +mkIfacePublic :: [IfaceExport] + -> [IfaceDeclExts 'ModIfaceFinal] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDefault] + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> IfaceAbiHashes + -> IfacePublic +mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes = IfacePublic { + mi_exports_ = exports, + mi_decls_ = decls, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_defaults_ = defaults, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, + mi_cache_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, + mi_cache_fix_fn = mkIfaceFixCache fixities, + mi_cache_hash_fn = mkIfaceHashCache decls + }, + mi_abi_hashes_ = abi_hashes +} + +-- | The information needed to restart bytecode generation. +-- Enabled by `-fwrite-if-simplified-core`. +data IfaceSimplifiedCore = IfaceSimplifiedCore { + mi_sc_extra_decls :: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -- ^ Extra variable definitions which are **NOT** exposed but when + -- combined with mi_decls allows us to restart code generation. + -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] + , mi_sc_foreign :: IfaceForeign + -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. + -- See Note [Foreign stubs and TH bytecode linking] +} -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff - , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module + { ifaceTopExports :: DetOrdAvails -- ^ all top level things in this module, including unexported stuff + , ifaceImports :: [IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where @@ -362,6 +444,35 @@ instance Binary IfaceTopEnv where {- +Note [Structure of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The ModIface structure is divided into several logical parts: + +1. mi_mod_info: Basic module metadata (name, version, etc.) + +2. mi_public: The public interface of the module, which includes: + - Exports, declarations, fixities, warnings, annotations + - Class and type family instances + - Rewrite rules and COMPLETE pragmas + - Safe Haskell and package trust information + - ABI hashes for recompilation checking + +4. mi_self_recomp: Information needed for self-recompilation checking + (see Note [Self recompilation information in interface files]) + +5. mi_simplified_core: Optional simplified Core for bytecode generation + (only present when -fwrite-if-simplified-core is enabled) + +6. mi_docs: Optional documentation (only present when -haddock is enabled) + +7. mi_top_env: Information about the top-level environment of the original source + +8. mi_ext_fields: Additional fields for extensibility + +This structure helps organize the interface data according to its purpose and usage +patterns. Different parts of the compiler use different fields. By separating them +logically in the interface we can arrange to only deserialize the fields that are needed. + Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -371,7 +482,7 @@ The ModIface is the Haskell representation of an interface (.hi) file. that we have just compiled * For packages that we depend on we load the ModIface from disk. -Some fields in the ModIface are deliberately lazy because when we read +All fields in the ModIface are deliberately lazy because when we read an interface file we don't always need all the parts. For example, an interface file contains information about documentation which is often not needed during compilation. This is achieved using the lazyPut/lazyGet pair. @@ -384,23 +495,43 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) -mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ +mi_flag_hash :: ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags) +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint -mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_ mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint -mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_ mi_src_hash :: ModIface_ phase -> Maybe Fingerprint -mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_ mi_usages :: ModIface_ phase -> Maybe [Usage] -mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ +mi_usages = fmap mi_sr_usages . mi_self_recomp_ mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint -mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_ + +-- | Accessor for the module hash of the ABI from a ModIface. +mi_mod_hash :: ModIface -> Fingerprint +mi_mod_hash iface = mi_abi_mod_hash (mi_abi_hashes iface) + +-- | Accessor for whether this module has orphans from a ModIface. +mi_orphan :: ModIface -> WhetherHasOrphans +mi_orphan iface = mi_abi_orphan (mi_abi_hashes iface) + +-- | Accessor for whether this module has family instances from a ModIface. +mi_finsts :: ModIface -> WhetherHasFamInst +mi_finsts iface = mi_abi_finsts (mi_abi_hashes iface) + +-- | Accessor for the hash of the export list from a ModIface. +mi_exp_hash :: ModIface -> Fingerprint +mi_exp_hash iface = mi_abi_exp_hash (mi_abi_hashes iface) + +-- | Accessor for the hash of orphan rules, class and family instances combined from a ModIface. +mi_orphan_hash :: ModIface -> Fingerprint +mi_orphan_hash iface = mi_abi_orphan_hash (mi_abi_hashes iface) -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. @@ -415,16 +546,19 @@ mi_mnwib iface = GWIB (moduleName $ mi_module iface) (mi_boot iface) -- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be -- found, 'defaultFixity' is returned instead. mi_fix :: ModIface -> OccName -> Fixity -mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity +mi_fix iface name = mi_fix_fn iface name `orElse` defaultFixity -- | The semantic module for this interface; e.g., if it's a interface -- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module' -- will be @<A>@. -mi_semantic_module :: ModIface_ a -> Module -mi_semantic_module iface = case mi_sig_of iface of - Nothing -> mi_module iface +mi_mod_info_semantic_module :: IfaceModInfo -> Module +mi_mod_info_semantic_module iface = case mi_mod_info_sig_of iface of + Nothing -> mi_mod_info_module iface Just mod -> mod +mi_semantic_module :: ModIface_ a -> Module +mi_semantic_module iface = mi_mod_info_semantic_module (mi_mod_info iface) + -- | The "precise" free holes, e.g., the signatures that this -- 'ModIface' depends on. mi_free_holes :: ModIface -> UniqDSet ModuleName @@ -455,191 +589,229 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + put_ bh (PrivateModIface + { mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then -- we likely have a good reason, and do not want to reuse -- the byte array. -- See Note [Private fields in ModIface] + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_anns_ = anns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - mi_complete_matches_ = complete_matches, + mi_public_ = public, mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_self_recomp_info_ = self_recomp, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash - }}) = do - put_ bh mod - put_ bh sig_of - put_ bh hsc_src - put_ bh self_recomp - put_ bh mod_hash + mi_self_recomp_ = self_recomp, + mi_simplified_core_ = simplified_core + }) = do + put_ bh mod_info put_ bh iface_hash - put_ bh orphan - put_ bh hasFamInsts lazyPut bh deps - put_ bh exports - put_ bh exp_hash - put_ bh fixities - lazyPut bh warns - lazyPut bh anns - put_ bh decls - put_ bh extra_decls - put_ bh defaults - put_ bh foreign_ - put_ bh insts - put_ bh fam_insts - lazyPut bh rules - put_ bh orphan_hash - put_ bh trust - put_ bh trust_pkg - put_ bh complete_matches + lazyPut bh public lazyPut bh top_env lazyPutMaybe bh docs + lazyPutMaybe bh self_recomp + lazyPutMaybe bh simplified_core get bh = do - mod <- get bh - sig_of <- get bh - hsc_src <- get bh - self_recomp_info <- get bh - mod_hash <- get bh + mod_info <- get bh iface_hash <- get bh - orphan <- get bh - hasFamInsts <- get bh deps <- lazyGet bh - exports <- {-# SCC "bin_exports" #-} get bh - exp_hash <- get bh - fixities <- {-# SCC "bin_fixities" #-} get bh - warns <- {-# SCC "bin_warns" #-} lazyGet bh - anns <- {-# SCC "bin_anns" #-} lazyGet bh - decls <- {-# SCC "bin_tycldecls" #-} get bh - extra_decls <- get bh - defaults <- get bh - foreign_ <- get bh - insts <- {-# SCC "bin_insts" #-} get bh - fam_insts <- {-# SCC "bin_fam_insts" #-} get bh - rules <- {-# SCC "bin_rules" #-} lazyGet bh - orphan_hash <- get bh - trust <- get bh - trust_pkg <- get bh - complete_matches <- get bh + public <- lazyGet bh top_env <- lazyGet bh docs <- lazyGetMaybe bh + self_recomp <- lazyGetMaybe bh + simplified_core <- lazyGetMaybe bh + return (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = - -- We can't populate this field here, as we are - -- missing the 'mi_ext_fields_' field, which is - -- handled in 'getIfaceWithExtFields'. - FullIfaceBinHandle Strict.Nothing, + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_anns_ = anns, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - -- And build the cached values - mi_complete_matches_ = complete_matches, + mi_public_ = public, + mi_simplified_core_ = simplified_core, mi_docs_ = docs, mi_top_env_ = top_env, - mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt - -- with specially when the file is read - mi_self_recomp_info_ = self_recomp_info, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash, - mi_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, - mi_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, - mi_fix_fn = mkIfaceFixCache fixities, - mi_hash_fn = mkIfaceHashCache decls - }}) + mi_self_recomp_ = self_recomp, + -- placeholder because this is dealt + -- with specially when the file is read + mi_ext_fields_ = emptyExtensibleFields, + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + }) + +instance Binary IfaceModInfo where + put_ bh (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) = do + put_ bh mod + put_ bh sig_of + put_ bh hsc_src + get bh = do + mod <- get bh + sig_of <- get bh + hsc_src <- get bh + return (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) + + +instance Binary (IfacePublic_ 'ModIfaceFinal) where + put_ bh (IfacePublic { mi_exports_ = exports + , mi_decls_ = decls + , mi_fixities_ = fixities + , mi_warns_ = warns + , mi_anns_ = anns + , mi_defaults_ = defaults + , mi_insts_ = insts + , mi_fam_insts_ = fam_insts + , mi_rules_ = rules + , mi_trust_ = trust + , mi_trust_pkg_ = trust_pkg + , mi_complete_matches_ = complete_matches + , mi_abi_hashes_ = abi_hashes + }) = do + + lazyPut bh exports + lazyPut bh decls + lazyPut bh fixities + lazyPut bh warns + lazyPut bh anns + lazyPut bh defaults + lazyPut bh insts + lazyPut bh fam_insts + lazyPut bh rules + lazyPut bh trust + lazyPut bh trust_pkg + lazyPut bh complete_matches + lazyPut bh abi_hashes + + get bh = do + exports <- lazyGet bh + decls <- lazyGet bh + fixities <- lazyGet bh + warns <- lazyGet bh + anns <- lazyGet bh + defaults <- lazyGet bh + insts <- lazyGet bh + fam_insts <- lazyGet bh + rules <- lazyGet bh + trust <- lazyGet bh + trust_pkg <- lazyGet bh + complete_matches <- lazyGet bh + abi_hashes <- lazyGet bh + return (mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes) + +instance Binary IfaceAbiHashes where + put_ bh (IfaceAbiHashes { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = orphan + , mi_abi_finsts = hasFamInsts + , mi_abi_exp_hash = exp_hash + , mi_abi_orphan_hash = orphan_hash + }) = do + put_ bh mod_hash + put_ bh orphan + put_ bh hasFamInsts + put_ bh exp_hash + put_ bh orphan_hash + get bh = do + mod_hash <- get bh + orphan <- get bh + hasFamInsts <- get bh + exp_hash <- get bh + orphan_hash <- get bh + return $ IfaceAbiHashes { + mi_abi_mod_hash = mod_hash, + mi_abi_orphan = orphan, + mi_abi_finsts = hasFamInsts, + mi_abi_exp_hash = exp_hash, + mi_abi_orphan_hash = orphan_hash + } + +instance Binary IfaceSimplifiedCore where + put_ bh (IfaceSimplifiedCore eds fs) = do + put_ bh eds + put_ bh fs + + get bh = do + eds <- get bh + fs <- get bh + return (IfaceSimplifiedCore eds fs) emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface - { mi_module_ = mod, - mi_sig_of_ = Nothing, - mi_hsc_src_ = HsSrcFile, + { mi_mod_info_ = emptyIfaceModInfo mod, + mi_iface_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_exports_ = [], - mi_fixities_ = [], - mi_warns_ = IfWarnSome [] [], - mi_anns_ = [], - mi_defaults_ = [], - mi_insts_ = [], - mi_fam_insts_ = [], - mi_rules_ = [], - mi_decls_ = [], - mi_extra_decls_ = Nothing, - mi_foreign_ = emptyIfaceForeign, + mi_public_ = emptyPublicModIface (), + mi_simplified_core_ = Nothing, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_trust_ = noIfaceTrustInfo, - mi_trust_pkg_ = False, - mi_complete_matches_ = [], mi_docs_ = Nothing, - mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields, - mi_self_recomp_info_ = Nothing + mi_self_recomp_ = Nothing, + mi_ext_fields_ = emptyExtensibleFields + } +emptyIfaceModInfo :: Module -> IfaceModInfo +emptyIfaceModInfo mod = IfaceModInfo + { mi_mod_info_module = mod + , mi_mod_info_sig_of = Nothing + , mi_mod_info_hsc_src = HsSrcFile + } + + +emptyPublicModIface :: IfaceAbiHashesExts phase -> IfacePublic_ phase +emptyPublicModIface abi_hashes = IfacePublic + { mi_exports_ = [] + , mi_decls_ = [] + , mi_fixities_ = [] + , mi_warns_ = IfWarnSome [] [] + , mi_anns_ = [] + , mi_defaults_ = [] + , mi_insts_ = [] + , mi_fam_insts_ = [] + , mi_rules_ = [] + , mi_abi_hashes_ = abi_hashes + , mi_trust_ = noIfaceTrustInfo + , mi_trust_pkg_ = False + , mi_caches_ = emptyModIfaceCache + , mi_complete_matches_ = [] + } + +emptyModIfaceCache :: IfaceCache +emptyModIfaceCache = IfaceCache { + mi_cache_decl_warn_fn = emptyIfaceWarnCache, + mi_cache_export_warn_fn = emptyIfaceWarnCache, + mi_cache_fix_fn = emptyIfaceFixCache, + mi_cache_hash_fn = emptyIfaceHashCache +} + +emptyIfaceBackend :: IfaceAbiHashes +emptyIfaceBackend = IfaceAbiHashes + { mi_abi_mod_hash = fingerprint0, + mi_abi_orphan = False, + mi_abi_finsts = False, + mi_abi_exp_hash = fingerprint0, + mi_abi_orphan_hash = fingerprint0 + } + emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls_ = [] - , mi_self_recomp_info_ = Nothing + { mi_public_ = emptyPublicModIface emptyIfaceBackend , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing - , mi_final_exts_ = ModIfaceBackend - { mi_mod_hash = fingerprint0, - mi_iface_hash = fingerprint0, - mi_orphan = False, - mi_finsts = False, - mi_exp_hash = fingerprint0, - mi_orphan_hash = fingerprint0, - mi_decl_warn_fn = emptyIfaceWarnCache, - mi_export_warn_fn = emptyIfaceWarnCache, - mi_fix_fn = emptyIfaceFixCache, - mi_hash_fn = emptyIfaceHashCache } } + } + -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface' mkIfaceHashCache :: [(Fingerprint,IfaceDecl)] @@ -657,11 +829,11 @@ emptyIfaceHashCache _occ = Nothing -- ModIface is completely forced since it will live in memory for a long time. -- If forcing it uses a lot of memory, then store less things in ModIface. -instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) +instance ( NFData (IfaceAbiHashesExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) - = rnf a1 + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = (a1 :: IfaceBinHandle phase) `seq` rnf a2 `seq` rnf a3 `seq` rnf a4 @@ -671,24 +843,27 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 - `seq` rnf a11 - `seq` rnf a12 - `seq` rnf a13 - `seq` rnf a14 - `seq` rnf a15 - `seq` rnf a16 - `seq` rnf a17 - `seq` rnf a18 - `seq` rnf a19 - `seq` rnf a20 - `seq` rnf a21 - `seq` rnf a22 - -- IfaceBinHandle - `seq` (a23 :: IfaceBinHandle phase) - `seq` rnf a24 - -instance NFData ModIfaceBackend where - rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + +instance NFData IfaceModInfo where + rnf (IfaceModInfo a1 a2 a3) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + + +instance NFData IfaceSimplifiedCore where + rnf (IfaceSimplifiedCore eds fs) = rnf eds `seq` rnf fs + +instance NFData IfaceAbiHashes where + rnf (IfaceAbiHashes a1 a2 a3 a4 a5) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + +instance (NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) where + rnf (IfacePublic a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = rnf a1 `seq` rnf a2 `seq` rnf a3 @@ -699,6 +874,18 @@ instance NFData ModIfaceBackend where `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +instance NFData IfaceCache where + rnf (IfaceCache a1 a2 a3 a4) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + forceModIface :: ModIface -> IO () @@ -745,28 +932,38 @@ to serialise the 'ModIface' to disk again. -- | Given a 'PartialModIface', turn it into a 'ModIface' by completing -- missing fields. completePartialModIface :: PartialModIface + -> Fingerprint -> [(Fingerprint, IfaceDecl)] - -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - -> ModIfaceBackend + -> Maybe IfaceSimplifiedCore + -> IfaceAbiHashes + -> IfaceCache -> ModIface -completePartialModIface partial decls extra_decls final_exts = partial - { mi_decls_ = decls - , mi_extra_decls_ = extra_decls - , mi_final_exts_ = final_exts +completePartialModIface partial iface_hash decls extra_decls final_exts cache = partial + { mi_public_ = completePublicModIface decls final_exts cache (mi_public_ partial) + , mi_simplified_core_ = extra_decls , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_iface_hash_ = iface_hash } + where -set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase -set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } - -set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase -set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } +-- | Given a 'PartialIfacePublic', turn it into an 'IfacePublic' by completing +-- missing fields. +completePublicModIface :: [(Fingerprint, IfaceDecl)] + -> IfaceAbiHashes + -> IfaceCache + -> PartialIfacePublic + -> IfacePublic +completePublicModIface decls abi_hashes cache partial = partial + { mi_decls_ = decls + , mi_abi_hashes_ = abi_hashes + , mi_caches_ = cache + } -set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase -set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } +set_mi_mod_info :: IfaceModInfo -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info val iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = val } -set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase -set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } +set_mi_self_recomp :: Maybe IfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -774,59 +971,100 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } +set_mi_public :: (IfacePublic_ phase -> IfacePublic_ phase) -> ModIface_ phase -> ModIface_ phase +set_mi_public f iface = clear_mi_hi_bytes $ iface { mi_public_ = f (mi_public_ iface) } + +set_mi_simplified_core :: Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase +set_mi_simplified_core val iface = clear_mi_hi_bytes $ iface { mi_simplified_core_ = val } + +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +{- Settings for mi_public interface fields -} + set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase -set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } +set_mi_exports val = set_mi_public (\iface -> iface { mi_exports_ = val }) set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase -set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } +set_mi_fixities val = set_mi_public (\iface -> iface { mi_fixities_ = val }) set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase -set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } +set_mi_warns val = set_mi_public (\iface -> iface { mi_warns_ = val }) set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase -set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } +set_mi_anns val = set_mi_public (\iface -> iface { mi_anns_ = val }) set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase -set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } +set_mi_insts val = set_mi_public (\iface -> iface { mi_insts_ = val }) set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase -set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } +set_mi_fam_insts val = set_mi_public (\iface -> iface { mi_fam_insts_ = val }) set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase -set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } +set_mi_rules val = set_mi_public (\iface -> iface { mi_rules_ = val }) set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase -set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } +set_mi_decls val = set_mi_public (\iface -> iface { mi_decls_ = val }) set_mi_defaults :: [IfaceDefault] -> ModIface_ phase -> ModIface_ phase -set_mi_defaults val iface = clear_mi_hi_bytes $ iface { mi_defaults_ = val } - -set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase -set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } - -set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase -set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } - -set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase -set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } +set_mi_defaults val = set_mi_public (\iface -> iface { mi_defaults_ = val }) set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase -set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } +set_mi_trust val = set_mi_public (\iface -> iface { mi_trust_ = val }) set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase -set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } +set_mi_trust_pkg val = set_mi_public (\iface -> iface { mi_trust_pkg_ = val }) set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase -set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } +set_mi_complete_matches val = set_mi_public (\iface -> iface { mi_complete_matches_ = val }) + +set_mi_abi_hashes :: IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_abi_hashes val = set_mi_public (\iface -> iface { mi_abi_hashes_ = val }) + +{- Setters for mi_caches interface fields -} + +set_mi_decl_warn_fn :: (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_decl_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_decl_warn_fn = val } }) + +set_mi_export_warn_fn :: (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_export_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_export_warn_fn = val } }) + +set_mi_fix_fn :: (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase +set_mi_fix_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_fix_fn = val } }) + +set_mi_hash_fn :: (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase +set_mi_hash_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_hash_fn = val } }) + +set_mi_caches :: IfaceCache -> ModIface_ phase -> ModIface_ phase +set_mi_caches val = set_mi_public (\iface -> iface { mi_caches_ = val }) + +{- + +-} + +{- Setters for mi_mod_info interface fields -} + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val = set_mi_mod_info_field (\info -> info { mi_mod_info_module = val }) + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val = set_mi_mod_info_field (\info -> info { mi_mod_info_sig_of = val }) + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val = set_mi_mod_info_field (\info -> info { mi_mod_info_hsc_src = val }) + +-- | Helper function for setting fields in mi_mod_info_ +set_mi_mod_info_field :: (IfaceModInfo -> IfaceModInfo) -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info_field f iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = f (mi_mod_info_ iface) } -set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase -set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } -set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase -set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } -set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase -set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } -- | Invalidate any byte array buffer we might have. clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase @@ -887,18 +1125,20 @@ However, with the pragma, the correct core is generated: -- See Note [Inline Pattern synonym of ModIface] for why we have all these -- inline pragmas. -{-# INLINE ModIface #-} +{-# INLINE mi_mod_info #-} +{-# INLINE mi_iface_hash #-} {-# INLINE mi_module #-} {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} +{-# INLINE mi_public #-} {-# INLINE mi_exports #-} {-# INLINE mi_fixities #-} {-# INLINE mi_warns #-} {-# INLINE mi_anns #-} {-# INLINE mi_decls #-} -{-# INLINE mi_extra_decls #-} -{-# INLINE mi_foreign #-} +{-# INLINE mi_simplified_core #-} +{-# INLINE mi_defaults #-} {-# INLINE mi_top_env #-} {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} @@ -907,32 +1147,63 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} {-# INLINE mi_docs #-} -{-# INLINE mi_final_exts #-} +{-# INLINE mi_abi_hashes #-} {-# INLINE mi_ext_fields #-} {-# INLINE mi_hi_bytes #-} +{-# INLINE mi_self_recomp_info #-} +{-# INLINE mi_fix_fn #-} +{-# INLINE mi_hash_fn #-} +{-# INLINE mi_decl_warn_fn #-} +{-# INLINE mi_export_warn_fn #-} +{-# INLINE ModIface #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> - [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> - [IfaceAnnotation] -> [IfaceDeclExts phase] -> - Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> + IfaceModInfo + -> Module + -> Maybe Module + -> HscSource + -> Fingerprint + -> Dependencies + -> IfacePublic_ phase + -> [IfaceExport] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDeclExts phase] + -> Maybe IfaceSimplifiedCore + -> [IfaceDefault] + -> IfaceTopEnv + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> Maybe Docs + -> IfaceAbiHashesExts phase + -> ExtensibleFields + -> IfaceBinHandle phase + -> Maybe IfaceSelfRecomp + -> (OccName -> Maybe Fixity) + -> (OccName -> Maybe (OccName, Fingerprint)) + -> (OccName -> Maybe (WarningTxt GhcRn)) + -> (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase pattern ModIface - { mi_module + { mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_defaults , mi_top_env , mi_insts @@ -942,33 +1213,45 @@ pattern ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_hash_fn + , mi_decl_warn_fn + , mi_export_warn_fn } <- PrivateModIface - { mi_module_ = mi_module - , mi_sig_of_ = mi_sig_of - , mi_hsc_src_ = mi_hsc_src + { mi_mod_info_ = mi_mod_info at IfaceModInfo { mi_mod_info_module = mi_module + , mi_mod_info_sig_of = mi_sig_of + , mi_mod_info_hsc_src = mi_hsc_src } + , mi_iface_hash_ = mi_iface_hash , mi_deps_ = mi_deps - , mi_exports_ = mi_exports - , mi_fixities_ = mi_fixities - , mi_warns_ = mi_warns - , mi_anns_ = mi_anns - , mi_decls_ = mi_decls - , mi_extra_decls_ = mi_extra_decls - , mi_foreign_ = mi_foreign - , mi_defaults_ = mi_defaults - , mi_top_env_ = mi_top_env - , mi_insts_ = mi_insts - , mi_fam_insts_ = mi_fam_insts - , mi_rules_ = mi_rules - , mi_trust_ = mi_trust - , mi_trust_pkg_ = mi_trust_pkg - , mi_complete_matches_ = mi_complete_matches + , mi_public_ = mi_public at IfacePublic { + mi_exports_ = mi_exports + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_defaults_ = mi_defaults + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mi_decl_warn_fn, + mi_cache_export_warn_fn = mi_export_warn_fn, + mi_cache_fix_fn = mi_fix_fn, + mi_cache_hash_fn = mi_hash_fn + } + , mi_abi_hashes_ = mi_abi_hashes + } , mi_docs_ = mi_docs - , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields , mi_hi_bytes_ = mi_hi_bytes - , mi_self_recomp_info_ = mi_self_recomp_info + , mi_self_recomp_ = mi_self_recomp_info + , mi_simplified_core_ = mi_simplified_core + , mi_top_env_ = mi_top_env } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -107,6 +107,9 @@ module GHC.Utils.Binary simpleBindingNameReader, FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, BinArray, + + -- * FingerprintWithValue + FingerprintWithValue(..) ) where import GHC.Prelude @@ -2088,3 +2091,39 @@ source location as part of a larger structure. instance (Binary v) => Binary (IntMap v) where put_ bh m = put_ bh (IntMap.toAscList m) get bh = IntMap.fromAscList <$> get bh + + +{- +Note [FingerprintWithValue] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +FingerprintWithValue is a wrapper which allows us to store a fingerprint and +optionally the value which was used to create the fingerprint. + +This is useful for storing information in interface files, where we want to +store the fingerprint of the interface file, but also the value which was used +to create the fingerprint (e.g. the DynFlags). + +The wrapper is useful to ensure that the fingerprint can be read quickly without +having to deserialise the value itself. + +-} + +-- | A wrapper which allows us to store a fingerprint and optionally the value which +-- was used to create the fingerprint. +data FingerprintWithValue a = FingerprintWithValue !Fingerprint (Maybe a) + deriving Functor + +instance Binary a => Binary (FingerprintWithValue a) where + put_ bh (FingerprintWithValue fp val) = do + put_ bh fp + lazyPutMaybe bh val + + get bh = do + fp <- get bh + val <- lazyGetMaybe bh + return $ FingerprintWithValue fp val + +instance NFData a => NFData (FingerprintWithValue a) where + rnf (FingerprintWithValue fp mflags) + = rnf fp `seq` rnf mflags `seq` () \ No newline at end of file ===================================== ghc/Main.hs ===================================== @@ -1133,6 +1133,8 @@ abiHash strs = do mods <- mapM find_it strs + -- MP: loadUserInterface is inefficient here since we will never find a cached + -- interface. computeInterface is probably better. let get_iface modl = loadUserInterface NotBoot (text "abiHash") modl ifaces <- initIfaceCheck (text "abiHash") hsc_env $ mapM get_iface mods @@ -1140,7 +1142,7 @@ abiHash strs = do put_ bh hiVersion -- package hashes change when the compiler version changes (for now) -- see #5328 - mapM_ (put_ bh . mi_mod_hash . mi_final_exts) ifaces + mapM_ (put_ bh . mi_mod_hash) ifaces f <- fingerprintBinMem bh putStrLn (showPpr dflags f) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f339c87f4ef589f8a7830e336b53e75892734402 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f339c87f4ef589f8a7830e336b53e75892734402 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/3a6ccc7e/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 21:24:27 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Thu, 13 Mar 2025 17:24:27 -0400 Subject: [Git][ghc/ghc][wip/T25647] fix ordering issue in tcFamInstLHSBinders Message-ID: <67d34d0b73f7c_f74243897e476931@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 3cc33fd8 by Patrick at 2025-03-14T05:24:15+08:00 fix ordering issue in tcFamInstLHSBinders - - - - - 4 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Zonk/TcType.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -258,13 +258,14 @@ tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted ; checkFamTelescope tclvl hs_outer_bndrs outer_exp_tvs -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] -- See Note [Type variables in type families instance decl] - ; (dvs, wc_itvs, outer_imp_itvs) <- candidateQTyVarsWithBinders outer_exp_tvs outer_imp_tvs wcs lhs_ty - ; (qtvs, outer_imp_qtvs) <- quantifyTyVarsWithBinders wc_itvs outer_imp_itvs skol_info dvs + ; (dvs, outer_wcs_imp_dvs) <- candidateQTyVarsWithBinders outer_exp_tvs (outer_imp_tvs ++ wcs) lhs_ty + ; qtvs <- quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs -- Have to make a same defaulting choice for result kind here -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; let final_tvs = scopedSort (qtvs ++ outer_exp_tvs ++ outer_imp_qtvs) + ; let final_tvs = scopedSort (qtvs ++ outer_exp_tvs) + ; let non_user_tvs = dVarSetElems $ mkDVarSet qtvs `delDVarSetList` outer_wcs_imp_dvs -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ; traceTc "tcFamInstLHSBinders" $ @@ -276,17 +277,16 @@ tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted , text "wcs:" <+> pprTyVars wcs -- after zonking - , text "wc_itvs:" <+> pprTyVars wc_itvs - , text "outer_imp_itvs:" <+> pprTyVars outer_imp_itvs , text "dvs:" <+> ppr dvs + , text "outer_wcs_imp_dvs:" <+> pprTyVars outer_wcs_imp_dvs -- after quantification - , text "qtvs(include wildcards):" <+> pprTyVars qtvs - , text "outer_imp_qtvs:" <+> pprTyVars outer_imp_qtvs + , text "qtvs:" <+> pprTyVars qtvs + , text "non_user_tvs:" <+> pprTyVars non_user_tvs , text "final_tvs:" <+> pprTyVars final_tvs ] ; reportUnsolvedEqualities skol_info final_tvs tclvl wanted - return (final_tvs, qtvs) + return (final_tvs, non_user_tvs) -- Gives the kind for every TyCon that has a standalone kind signature type KindSigEnv = NameEnv Kind ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -1347,7 +1347,8 @@ captureWildCards thing_inside ; res <- updLclEnv (\ env -> env { tcl_wcs = wcs_var}) $ thing_inside ; wcs <- readTcRef wcs_var - ; return (wcs, res) } + -- Reverse the list to preserve the order in which the wildcards were added + ; return (reverse wcs, res) } capture_messages :: TcM r -> TcM (r, Messages TcRnMessage) -- capture_messages simply captures and returns the ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -86,6 +86,7 @@ module GHC.Tc.Utils.TcMType ( candidateQTyVarsOfTypes, candidateQTyVarsOfKinds, candidateQTyVarsWithBinders, CandidatesQTvs(..), delCandidates, + intersectCandidates, candidateKindVars, partitionCandidates, ------------------------------ @@ -1389,20 +1390,20 @@ partitionCandidates dvs@(DV { dv_kvs = kvs, dv_tvs = tvs }) pred (extracted_tvs, rest_tvs) = partitionDVarSet pred tvs extracted = dVarSetToVarSet extracted_kvs `unionVarSet` dVarSetToVarSet extracted_tvs -candidateQTyVarsWithBinders :: [TyVar] -> [TyVar] -> [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar], [TyVar]) +candidateQTyVarsWithBinders :: [TyVar] -> [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar]) -- (candidateQTyVarsWithBinders tvs ty) returns the candidateQTyVars -- of (forall tvs. ty), but do not treat 'tvs' as bound for the purpose -- of Note [Naughty quantification candidates]. Why? -- Because we are going to scoped-sort the quantified variables -- in among the tvs -candidateQTyVarsWithBinders outer_exp_tvs outer_imp_tvs wcs ty +candidateQTyVarsWithBinders outer_exp_tvs outer_wcs_imp_tvs ty = do { kvs <- candidateQTyVarsOfKinds (map tyVarKind bound_tvs) ; cur_lvl <- getTcLevel ; all_tvs <- collect_cand_qtvs ty False cur_lvl emptyVarSet kvs ty - ; return (all_tvs `delCandidates` bound_tvs, intersectCandidates all_tvs outer_imp_tvs, intersectCandidates all_tvs wcs) } + ; return (all_tvs `delCandidates` outer_exp_tvs, all_tvs `intersectCandidates` outer_wcs_imp_tvs) } where - bound_tvs = outer_exp_tvs ++ outer_imp_tvs ++ wcs + bound_tvs = outer_exp_tvs ++ outer_wcs_imp_tvs -- | Gathers free variables to use as quantification candidates (in -- 'quantifyTyVarsWithBinders'). This might output the same var @@ -1752,15 +1753,14 @@ quantifyTyVars :: SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] -- Already zonked -> TcM [TcTyVar] -quantifyTyVars ski tvs = fst <$> quantifyTyVarsWithBinders [] [] ski tvs +quantifyTyVars ski tvs = quantifyTyVarsWithBinders ski tvs [] quantifyTyVarsWithBinders :: - [TcTyVar] - -> [TcTyVar] - -> SkolemInfo + SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] -- Already zonked - -> TcM ([TcTyVar], [TcTyVar]) + -> [TcTyVar] + -> TcM [TcTyVar] -- See Note [quantifyTyVars] -- Can be given a mixture of TcTyVars and TyVars, in the case of -- associated type declarations. Also accepts covars, but *never* returns any. @@ -1769,39 +1769,36 @@ quantifyTyVarsWithBinders :: -- free in the environment here. Just quantify unconditionally, subject -- to the restrictions in Note [quantifyTyVars]. --- for wildcards, do not default, just skolemise add to the list of quantified --- for outer_imp_qtvs, do not default, just skolemise, and return separately -quantifyTyVarsWithBinders wc_itvs outer_imp_itvs skol_info dvs +-- for outer_wcs_imp_tvs, do not default, just skolemise add to the list of quantified +quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_tvs -- short-circuit common case - | isEmptyCandidates dvs && null wc_itvs && null outer_imp_itvs + | isEmptyCandidates dvs && null outer_wcs_imp_tvs = do { traceTc "quantifyTyVars has nothing to quantify" empty - ; return ([], []) } + ; return [] } | otherwise = do { traceTc "quantifyTyVars {" ( vcat [ text "dvs =" <+> ppr dvs, - text "wc_qtvs =" <+> ppr wc_itvs, - text "outer_imp_qtvs =" <+> ppr outer_imp_itvs + text "outer_wc_imp_qtvs=" <+> ppr outer_wcs_imp_tvs ]) - ; undefaulted <- defaultTyVars dvs - ; (final_qtvs, out_imp_qtvs) <- liftZonkM $ do - qtvs <- mapMaybeM zonk_quant (undefaulted ++ wc_itvs) - out_imp_qtvs <- mapMaybeM zonk_quant outer_imp_itvs - return (qtvs, out_imp_qtvs) + ; undefaulted <- defaultTyVars $ dvs `delCandidates` outer_wcs_imp_tvs + ; final_qtvs <- liftZonkM $ do + -- resume order and then skolemise + qtvs <- mapMaybeM zonk_quant $ dvs `intersectCandidates` (undefaulted ++ outer_wcs_imp_tvs) + return qtvs ; traceTc "quantifyTyVars }" (vcat [ text "undefaulted:" <+> pprTyVars undefaulted , text "final_qtvs:" <+> pprTyVars final_qtvs - , text "out_imp_qtvs:" <+> pprTyVars out_imp_qtvs ]) -- We should never quantify over coercion variables; check this - ; let co_vars = filter isCoVar (final_qtvs ++ out_imp_qtvs) + ; let co_vars = filter isCoVar final_qtvs ; massertPpr (null co_vars) (ppr co_vars) - ; return (final_qtvs, out_imp_qtvs) } + ; return final_qtvs } where -- zonk_quant returns a tyvar if it should be quantified over; -- otherwise, it returns Nothing. The latter case happens for ===================================== compiler/GHC/Tc/Zonk/TcType.hs ===================================== @@ -83,7 +83,7 @@ import GHC.Core.Predicate import GHC.Utils.Constants import GHC.Utils.Outputable import GHC.Utils.Misc -import GHC.Utils.Monad ( mapAccumLM, mapMaybeM ) +import GHC.Utils.Monad ( mapAccumLM ) import GHC.Utils.Panic import GHC.Data.Bag @@ -269,7 +269,6 @@ zonkTcTyVar tv zonkTcTyVarsToTcTyVars :: HasDebugCallStack => [TcTyVar] -> ZonkM [TcTyVar] zonkTcTyVarsToTcTyVars = mapM zonkTcTyVarToTcTyVar - zonkTcTyVarToTcTyVar :: HasDebugCallStack => TcTyVar -> ZonkM TcTyVar zonkTcTyVarToTcTyVar tv = do { ty <- zonkTcTyVar tv View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3cc33fd819469dc0c41e5c05e6a01c22ea43e9e6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3cc33fd819469dc0c41e5c05e6a01c22ea43e9e6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/d42a3e9b/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 22:38:17 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Thu, 13 Mar 2025 18:38:17 -0400 Subject: [Git][ghc/ghc][wip/az/ghc-cpp] Working on getting check-exact to work properly Message-ID: <67d35e59e26cb_111438592bd057881@gitlab.mail> Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC Commits: 3a1904ad by Alan Zimmerman at 2025-03-13T22:37:47+00:00 Working on getting check-exact to work properly - - - - - 5 changed files: - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PreProcess.hs - utils/check-cpp/PreProcess.hs - utils/check-exact/Main.hs - utils/check-exact/Preprocess.hs Changes: ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -1006,7 +1006,7 @@ data Token | ITblockComment String PsSpan -- ^ comment in {- -} -- GHC CPP extension. See Note [GhcCPP Token] - | ITcpp Bool FastString -- ^ CPP #-prefixed line, or continuation. + | ITcpp Bool FastString PsSpan -- ^ CPP #-prefixed line, or continuation. deriving Show instance Outputable Token where @@ -1262,6 +1262,7 @@ cppTokenCont = doCppToken Nothing doCppToken :: (Maybe Int) -> Action p doCppToken code span buf len _buf2 = do + lt <- getLastLocIncludingComments let pushLexStateMaybe Nothing = return () pushLexStateMaybe (Just code) = pushLexState code @@ -1275,7 +1276,8 @@ doCppToken code span buf len _buf2 = ('\n':_) -> return (len - 1, False) _ -> return (len, False) let span' = cppSpan span len0 - return (L span' (ITcpp continue $! lexemeToFastString buf len0)) + let !s = lexemeToFastString buf len0 + return (L span' (ITcpp continue s lt)) -- cppToken :: Int -> Action p @@ -1313,10 +1315,12 @@ cppSpan span len = mkPsSpan start_loc end_loc BufPos sb = psBufPos start_loc end_loc = PsLoc real_loc (BufPos (sb + len + 1)) -cppTokenPop :: (FastString -> Token)-> Action p +cppTokenPop :: (FastString -> PsSpan -> Token)-> Action p cppTokenPop t span buf len _buf2 = do _ <- popLexState - return (L span (t $! lexemeToFastString buf len)) + lt <- getLastLocIncludingComments + let !s = lexemeToFastString buf len + return (L span (t s lt)) -- See Note [Nested comment line pragmas] failLinePrag1 :: Action p @@ -3821,6 +3825,7 @@ commentToAnnotation (L l (ITdocComment s ll)) = mkLEpaComment l ll (EpaDocComm commentToAnnotation (L l (ITdocOptions s ll)) = mkLEpaComment l ll (EpaDocOptions s) commentToAnnotation (L l (ITlineComment s ll)) = mkLEpaComment l ll (EpaLineComment s) commentToAnnotation (L l (ITblockComment s ll)) = mkLEpaComment l ll (EpaBlockComment s) +commentToAnnotation (L l (ITcpp _ s ll)) = mkLEpaComment l ll (EpaLineComment (unpackFS s)) commentToAnnotation _ = panic "commentToAnnotation" -- see Note [PsSpan in Comments] ===================================== compiler/GHC/Parser/PreProcess.hs ===================================== @@ -201,7 +201,7 @@ ppLexer queueComments cont = Just inp -> do Lexer.setInput inp ppLexer queueComments cont - L l (ITcpp continuation s) -> do + L l (ITcpp continuation s sp) -> do ghcpp <- ghcCppEnabled -- Only process the directive if GhcCpp is explicitly enabled. -- Otherwise we are scanning for pragmas @@ -216,7 +216,7 @@ ppLexer queueComments cont = case mdump of Just dump -> -- We have a dump of the state, put it into an ignored token - contIgnoreTok (L l (ITcpp continuation (appendFS s (fsLit dump)))) + contIgnoreTok (L l (ITcpp continuation (appendFS s (fsLit dump)) sp)) Nothing -> contIgnoreTok tk else contInner tk _ -> do @@ -232,7 +232,7 @@ ppLexer queueComments cont = processCppToks :: FastString -> PP (Maybe String) processCppToks fs = do let - get (L _ (ITcpp _ s)) = s + get (L _ (ITcpp _ s _)) = s get _ = error "should not" -- Combine any prior continuation tokens cs <- popContinuation ===================================== utils/check-cpp/PreProcess.hs ===================================== @@ -49,6 +49,8 @@ dumpGhcCpp dflags pst = output ++ sepa ++ show bare_toks ++ sepa + ++ show lll + ++ sepa -- ++ show all_toks ++ sepa -- Note: pst is the state /before/ the parser runs, so we can use it to lex. (pst_final, bare_toks) = lexAll pst @@ -67,6 +69,9 @@ dumpGhcCpp dflags pst = output toks = addSourceToTokens startLoc buf1 all_toks final = renderCombinedToks toks + lll = case Lexer.lexTokenStream () (options pst) (buffer pst) startLoc of + POk _ x -> x + _ -> error $ "wtf" cmpBs :: Located Token -> Located Token -> Ordering cmpBs (L (RealSrcSpan _ (Strict.Just bs1)) _) (L (RealSrcSpan _ (Strict.Just bs2)) _) = @@ -158,8 +163,9 @@ showDefines defines = Map.foldlWithKey' (\acc k d -> acc ++ "\n" ++ renderDefine "#define " ++ n ++ "(" ++ (intercalate "," args) ++ ") " ++ (intercalate " " (map PM.t_str rhs)) lexAll :: Lexer.PState PpState -> (Lexer.PState PpState, [Located Token]) --- lexAll state = case unP (lexer True return) state of -lexAll state = case unP (lexerDbg True return) state of +lexAll state = case unP (lexer True return) state of +-- lexAll state = case unP (lexerDbg True return) state of +-- lexAll state = case unP (Lexer.lexerDbg True return) state of POk s t@(L _ ITeof) -> (s, [t]) -- POk state' t -> (ss, t : rest) POk state' t -> (ss, trace ("lexAll:" ++ show t) t : rest) ===================================== utils/check-exact/Main.hs ===================================== @@ -218,7 +218,8 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/worktree/bisect/_b -- "../../testsuite/tests/printer/Test22771.hs" Nothing -- "../../testsuite/tests/printer/Test23465.hs" Nothing -- "../../testsuite/tests/printer/Test25454.hs" Nothing - "../../testsuite/tests/printer/Test25467.hs" Nothing + -- "../../testsuite/tests/printer/Test25467.hs" Nothing + "../../testsuite/tests/printer/CppCommentPlacement.hs" Nothing -- cloneT does not need a test, function can be retired ===================================== utils/check-exact/Preprocess.hs ===================================== @@ -20,11 +20,13 @@ import qualified Control.Monad.IO.Class as GHC import qualified GHC.Data.FastString as GHC import qualified GHC.Data.StringBuffer as GHC import qualified GHC.Driver.Config.Parser as GHC +import qualified GHC.Driver.DynFlags as GHC import qualified GHC.Driver.Env as GHC import qualified GHC.Driver.Errors.Types as GHC import qualified GHC.Driver.Phases as GHC import qualified GHC.Driver.Pipeline as GHC import qualified GHC.Parser.Lexer as GHC +import qualified GHC.Parser.PreProcess.State as GHC import qualified GHC.Settings as GHC import qualified GHC.Types.Error as GHC import qualified GHC.Types.SourceError as GHC @@ -37,7 +39,7 @@ import qualified GHC.Utils.Panic.Plain as GHC import GHC.Types.SrcLoc (mkSrcSpan, mkSrcLoc) import GHC.Data.FastString (mkFastString) -import Data.List (isPrefixOf) +import Data.List (isPrefixOf, partition) import Data.Maybe import Types import Utils @@ -45,7 +47,8 @@ import qualified Data.Set as Set import qualified GHC.Data.Strict as Strict --- import Debug.Trace +import Debug.Trace +import qualified GHC.LanguageExtensions as LangExt -- -- --------------------------------------------------------------------- @@ -106,16 +109,27 @@ getCppTokensAsComments cppOptions sourceFile = do source <- GHC.liftIO $ GHC.hGetStringBuffer sourceFile let startLoc = GHC.mkRealSrcLoc (GHC.mkFastString sourceFile) 1 1 (_txt,strSrcBuf,flags2') <- getPreprocessedSrcDirectPrim cppOptions sourceFile + + let flags2g = GHC.xopt_set flags2' LangExt.GhcCpp let flags2 = GHC.initParserOpts flags2' + let flags2'' = GHC.initParserOpts flags2g + -- let flags2'' = flags2 { GHC.pExtsBitmap = GHC.xset GHC.GhcCppBit (GHC.pExtsBitmap flags2)} -- hash-ifdef tokens - directiveToks <- GHC.liftIO $ getPreprocessorAsComments sourceFile + -- directiveToks <- GHC.liftIO $ getPreprocessorAsComments sourceFile -- Tokens without hash-ifdef nonDirectiveToks <- tokeniseOriginalSrc startLoc flags2 source - case GHC.lexTokenStream () flags2 strSrcBuf startLoc of + case GHC.lexTokenStream () (GHC.enableGhcCpp flags2) source startLoc of GHC.POk _ ts -> do - let toks = GHC.addSourceToTokens startLoc source ts - cppCommentToks = getCppTokens directiveToks nonDirectiveToks toks + let + isCppTok (GHC.L _ (GHC.ITcpp _ _ _)) = True + isCppTok _ = False + toks = GHC.addSourceToTokens startLoc source + (trace ("bitmap:" ++ show (GHC.pExtsBitmap flags2)) ts) + (directiveToks, toks') = partition (\(t,_) -> isCppTok t) toks + -- (directiveToks, toks') = partition (\(t,_) -> isCppTok t) + -- (trace ("toks:" ++ show toks) toks) + cppCommentToks = getCppTokens directiveToks nonDirectiveToks toks' return $ filter goodComment $ map (GHC.commentToAnnotation . toRealLocated . fst) cppCommentToks GHC.PFailed pst -> parseError pst @@ -131,7 +145,7 @@ goodComment c = isGoodComment (tokComment c) toRealLocated :: GHC.Located a -> GHC.PsLocated a toRealLocated (GHC.L (GHC.RealSrcSpan s (Strict.Just b)) x) = GHC.L (GHC.PsSpan s b) x -toRealLocated (GHC.L _ _) = GHC.panic "toRealLocated" +toRealLocated (GHC.L l _) = GHC.panic $ "toRealLocated:" ++ show l -- --------------------------------------------------------------------- @@ -150,8 +164,9 @@ getCppTokens :: -> [(GHC.Located GHC.Token, String)] -> [(GHC.Located GHC.Token, String)] -> [(GHC.Located GHC.Token, String)] -getCppTokens directiveToks origSrcToks postCppToks = toks +getCppTokens directiveToks' origSrcToks postCppToks = toks where + directiveToks = trace ("directiveToks: " ++ show directiveToks') directiveToks' locFn (GHC.L l1 _,_) (GHC.L l2 _,_) = compare (rs l1) (rs l2) m1Toks = mergeBy locFn postCppToks directiveToks @@ -262,6 +277,23 @@ alterToolSettings f dynFlags = dynFlags { GHC.toolSettings = f (GHC.toolSettings -- --------------------------------------------------------------------- +-- | Get the preprocessor directives as comment tokens from the +-- source. +getPreprocessorAsComments' :: FilePath -> IO [(GHC.Located GHC.Token, String)] +getPreprocessorAsComments' srcFile = do + fcontents <- readFileGhc srcFile + let directives = filter (\(_lineNum,line) -> case line of '#' : _ -> True; _ -> False) + $ zip [1..] (lines fcontents) + + let mkTok (lineNum,line) = (GHC.L l (GHC.ITlineComment line (makeBufSpan l)),line) + where + start = GHC.mkSrcLoc (GHC.mkFastString srcFile) lineNum 1 + end = GHC.mkSrcLoc (GHC.mkFastString srcFile) lineNum (length line) + l = GHC.mkSrcSpan start end + + let toks = map mkTok directives + return toks + -- | Get the preprocessor directives as comment tokens from the -- source. getPreprocessorAsComments :: FilePath -> IO [(GHC.Located GHC.Token, String)] @@ -279,7 +311,22 @@ getPreprocessorAsComments srcFile = do let toks = map mkTok directives return toks +-- TODO: possibly use the one from GHC.Parser.PreProcess, depending on +-- which lexer it ends up using. Or have specific versions of lexAll +-- for the two lexers. +lexAll :: GHC.PState GHC.PpState -> (GHC.PState GHC.PpState, [GHC.Located GHC.Token]) +lexAll state = case GHC.unP (GHC.lexer True return) state of +-- lexAll state = case unP (lexerDbg True return) state of +-- lexAll state = case unP (Lexer.lexerDbg True return) state of + GHC.POk s t@(GHC.L _ GHC.ITeof) -> (s, [t]) + -- POk state' t -> (ss, t : rest) + GHC.POk state' t -> (ss, trace ("lexAll:" ++ show t) t : rest) + where + (ss, rest) = lexAll state' + GHC.PFailed _pst -> GHC.panic $ "GHC.Parser.PreProcess.lexAll failed" + makeBufSpan :: GHC.SrcSpan -> GHC.PsSpan +makeBufSpan (GHC.RealSrcSpan s (Strict.Just bs)) = GHC.PsSpan s bs makeBufSpan ss = pspan where bl = GHC.BufPos 0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3a1904adb2edd1efd1f70707e7317a47d32dc4f0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3a1904adb2edd1efd1f70707e7317a47d32dc4f0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/f615e60b/attachment-0001.html> From gitlab at gitlab.haskell.org Thu Mar 13 23:46:13 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Thu, 13 Mar 2025 19:46:13 -0400 Subject: [Git][ghc/ghc][wip/T25647] fix Message-ID: <67d36e4525589_111438b9dcdc586c9@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 7dca599f by Patrick at 2025-03-14T07:46:02+08:00 fix - - - - - 1 changed file: - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1786,7 +1786,7 @@ quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_tvs ; undefaulted <- defaultTyVars $ dvs `delCandidates` outer_wcs_imp_tvs ; final_qtvs <- liftZonkM $ do -- resume order and then skolemise - qtvs <- mapMaybeM zonk_quant $ dvs `intersectCandidates` (undefaulted ++ outer_wcs_imp_tvs) + qtvs <- mapMaybeM zonk_quant $ undefaulted ++ outer_wcs_imp_tvs return qtvs ; traceTc "quantifyTyVars }" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7dca599f89be578ba5d4db44437930e3637d928a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7dca599f89be578ba5d4db44437930e3637d928a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250313/be1c685d/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 14 07:56:09 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Fri, 14 Mar 2025 03:56:09 -0400 Subject: [Git][ghc/ghc][wip/T25647] now we experiment default both wildcards and implicit binders Message-ID: <67d3e1194e5fa_1babac895ad045218@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: dc226dee by Patrick at 2025-03-14T15:55:59+08:00 now we experiment default both wildcards and implicit binders - - - - - 1 changed file: - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1783,10 +1783,10 @@ quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_tvs text "outer_wc_imp_qtvs=" <+> ppr outer_wcs_imp_tvs ]) - ; undefaulted <- defaultTyVars $ dvs `delCandidates` outer_wcs_imp_tvs + ; undefaulted <- defaultTyVars dvs ; final_qtvs <- liftZonkM $ do -- resume order and then skolemise - qtvs <- mapMaybeM zonk_quant $ undefaulted ++ outer_wcs_imp_tvs + qtvs <- mapMaybeM zonk_quant undefaulted return qtvs ; traceTc "quantifyTyVars }" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dc226deea84021e3a41b1dffdd95da9442f401a5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dc226deea84021e3a41b1dffdd95da9442f401a5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/c83dfbee/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 09:20:10 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 14 Mar 2025 05:20:10 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/direct-sbs Message-ID: <67d3f4ca3af76_1babac11db3d85012a@gitlab.mail> Matthew Pickering pushed new branch wip/direct-sbs at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/direct-sbs You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/5b7e30c5/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 14 09:31:40 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 14 Mar 2025 05:31:40 -0400 Subject: [Git][ghc/ghc][wip/refactor-iface] iface: Store logical parts of ModIface together Message-ID: <67d3f77c5deb3_1f51becebd023881@gitlab.mail> Matthew Pickering pushed to branch wip/refactor-iface at Glasgow Haskell Compiler / GHC Commits: 0203403c by Matthew Pickering at 2025-03-14T09:30:59+00:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 - - - - - 17 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - ghc/Main.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -100,29 +100,37 @@ module GHC ( findGlobalAnns, mkNamePprCtxForModule, ModIface, - ModIface_( - mi_module, - mi_sig_of, - mi_hsc_src, - mi_hi_bytes, - mi_deps, - mi_exports, - mi_fixities, - mi_warns, - mi_anns, - mi_insts, - mi_fam_insts, - mi_rules, - mi_decls, - mi_extra_decls, - mi_top_env, - mi_trust, - mi_trust_pkg, - mi_complete_matches, - mi_docs, - mi_final_exts, - mi_ext_fields - ), + ModIface_( mi_mod_info + , mi_module + , mi_sig_of + , mi_hsc_src + , mi_iface_hash + , mi_deps + , mi_public + , mi_exports + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_defaults + , mi_simplified_core + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_abi_hashes + , mi_ext_fields + , mi_hi_bytes + , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn + ), pattern ModIface, SafeHaskellMode(..), ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -844,7 +844,7 @@ hscRecompStatus case recomp_if_result of OutOfDateItem reason mb_checked_iface -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ fmap (mi_iface_hash . mi_final_exts) mb_checked_iface + return $ HscRecompNeeded $ fmap mi_iface_hash mb_checked_iface UpToDateItem checked_iface -> do let lcl_dflags = ms_hspp_opts mod_summary if | not (backendGeneratesCode (backend lcl_dflags)) -> do @@ -862,7 +862,7 @@ hscRecompStatus , xopt LangExt.TemplateHaskell lcl_dflags -> do msg $ needsRecompileBecause THWithJS - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface | otherwise -> do -- Do need linkable @@ -918,7 +918,7 @@ hscRecompStatus return $ HscUpToDate checked_iface $ linkable OutOfDateItem reason _ -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface -- | Check that the .o files produced by compilation are already up-to-date -- or not. @@ -968,10 +968,8 @@ loadByteCode iface mod_sum = do let this_mod = ms_mod mod_sum if_date = fromJust $ ms_iface_date mod_sum - case mi_extra_decls iface of - Just extra_decls -> do - let fi = WholeCoreBindings extra_decls this_mod (ms_location mod_sum) - (mi_foreign iface) + case iface_core_bindings iface (ms_location mod_sum) of + Just fi -> do return (UpToDateItem (Linkable if_date this_mod (NE.singleton (CoreBindings fi)))) _ -> return $ outOfDateItemBecause MissingBytecode Nothing @@ -1019,15 +1017,15 @@ compile_for_interpreter hsc_env use = -- | Assemble 'WholeCoreBindings' if the interface contains Core bindings. iface_core_bindings :: ModIface -> ModLocation -> Maybe WholeCoreBindings iface_core_bindings iface wcb_mod_location = - mi_extra_decls <&> \ wcb_bindings -> + mi_simplified_core <&> \(IfaceSimplifiedCore bindings foreign') -> WholeCoreBindings { - wcb_bindings, + wcb_bindings = bindings, wcb_module = mi_module, wcb_mod_location, - wcb_foreign = mi_foreign + wcb_foreign = foreign' } where - ModIface {mi_module, mi_extra_decls, mi_foreign} = iface + ModIface {mi_module, mi_simplified_core} = iface -- | Return an 'IO' that hydrates Core bindings and compiles them to bytecode if -- the interface contains any, using the supplied type env for typechecking. @@ -1376,7 +1374,7 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do -- dynamic interfaces. Hopefully both the dynamic and the non-dynamic -- interfaces stay in sync... -- - let change = old_iface /= Just (mi_iface_hash (mi_final_exts iface)) + let change = old_iface /= Just (mi_iface_hash iface) let dt = dynamicTooState dflags ===================================== compiler/GHC/HsToCore/Usage.hs ===================================== @@ -185,7 +185,7 @@ mkObjectUsage pit plugins fc hug th_links_needed th_pkgs_needed = do case miface of Nothing -> pprPanic "mkObjectUsage" (ppr m) Just iface -> - return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash (mi_final_exts iface)) + return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash iface) librarySpecToUsage :: LibrarySpec -> IO [Usage] librarySpecToUsage (Objects os) = traverse (fing Nothing) os @@ -278,10 +278,10 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names usg_entities = Map.toList ent_hashs, usg_safe = imp_safe } where - finsts_mod = mi_finsts (mi_final_exts iface) - hash_env = mi_hash_fn (mi_final_exts iface) - mod_hash = mi_mod_hash (mi_final_exts iface) - export_hash | depend_on_exports = Just (mi_exp_hash (mi_final_exts iface)) + finsts_mod = mi_finsts iface + hash_env = mi_hash_fn iface + mod_hash = mi_mod_hash iface + export_hash | depend_on_exports = Just (mi_exp_hash iface) | otherwise = Nothing by_is_safe (ImportedByUser imv) = imv_is_safe imv ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -41,34 +41,28 @@ data IfaceDynFlags = IfaceDynFlags , ifaceCallerCCFilters :: [CallerCcFilter] } -pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc -pprIfaceDynFlags (f, mflags) = - vcat $ - [ text "fingerprint:" <+> (ppr f) - ] - ++ case mflags of - Nothing -> [missingExtraFlagInfo] - Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> - [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) - , text "safe-mode:" <+> ppr a2 - , text "lang:" <+> ppr a3 - , text "exts:" <+> ppr a4 - , text "cpp-options:" - , nest 2 $ ppr a5 - , text "js-options:" - , nest 2 $ ppr a6 - , text "cmm-options:" - , nest 2 $ ppr a7 - , text "paths:" <+> hcat (map text a8) - , text "prof:" <+> ppr a9 - , text "ticky:" - , nest 2 $ vcat (map ppr a10) - , text "codegen:" - , nest 2 $ vcat (map ppr a11) - , text "fat-iface:" <+> ppr a12 - , text "debug-level:" <+> ppr a13 - , text "caller-cc-filters:" <+> ppr a14 - ] +pprIfaceDynFlags :: IfaceDynFlags -> SDoc +pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + vcat [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] missingExtraFlagInfo :: SDoc missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,7 +59,6 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields -import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -74,7 +73,6 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Logger -import GHC.Utils.Fingerprint( Fingerprint ) import GHC.Settings.Constants @@ -644,7 +642,7 @@ loadInterface doc_str mod from & set_mi_fam_insts (panic "No mi_fam_insts in PIT") & set_mi_rules (panic "No mi_rules in PIT") & set_mi_anns (panic "No mi_anns in PIT") - & set_mi_extra_decls (panic "No mi_extra_decls in PIT") + & set_mi_simplified_core (panic "No mi_simplified_core in PIT") bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1083,7 +1081,7 @@ load_dynamic_too :: Logger -> NameCache -> UnitState -> DynFlags load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do read_file logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case Succeeded (dynIface, _) - | mi_mod_hash (mi_final_exts iface) == mi_mod_hash (mi_final_exts dynIface) + | mi_mod_hash iface == mi_mod_hash dynIface -> return (Succeeded ()) | otherwise -> do return $ (Failed $ DynamicHashMismatchError wanted_mod loc) @@ -1174,11 +1172,10 @@ ghcPrimIface & set_mi_exports ghcPrimExports & set_mi_decls [] & set_mi_fixities ghcPrimFixities - & set_mi_final_exts ((mi_final_exts empty_iface) - { mi_fix_fn = mkIfaceFixCache ghcPrimFixities - , mi_decl_warn_fn = mkIfaceDeclWarnCache ghcPrimWarns - , mi_export_warn_fn = mkIfaceExportWarnCache ghcPrimWarns - }) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) + & set_mi_decl_warn_fn (mkIfaceDeclWarnCache ghcPrimWarns) + & set_mi_export_warn_fn (mkIfaceExportWarnCache ghcPrimWarns) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] in GHC.Builtin.Utils & set_mi_warns (toIfaceWarnings ghcPrimWarns) -- See Note [GHC.Prim Deprecations] in GHC.Builtin.Utils @@ -1263,21 +1260,14 @@ pprModIface unit_state iface = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") - <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) - <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) + <+> (if mi_orphan iface then text "[orphan module]" else Outputable.empty) + <+> (if mi_finsts iface then text "[family instance module]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) - , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) - , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat - [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) - , nest 2 (text "opt_hash:" <+> ppr opt_hash) - , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) - , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) - , vcat (map pprUsage usages) - ] - , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) + , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash iface)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash iface)) + , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash iface)) + , withSelfRecomp iface empty ppr + , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "where") , text "exports:" @@ -1288,10 +1278,14 @@ pprModIface unit_state iface , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] - , case mi_extra_decls iface of + , case mi_simplified_core iface of Nothing -> empty - Just eds -> text "extra decls:" - $$ nest 2 (vcat ([ppr bs | bs <- eds])) + Just (IfaceSimplifiedCore eds fs) -> + vcat [ text "extra decls:" + $$ nest 2 (vcat ([ppr bs | bs <- eds])) + , text "foreign stubs:" + $$ nest 2 (ppr fs) + ] , vcat (map ppr (mi_insts iface)) , vcat (map ppr (mi_fam_insts iface)) , vcat (map ppr (mi_rules iface)) @@ -1303,7 +1297,6 @@ pprModIface unit_state iface , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where - exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" @@ -1329,35 +1322,6 @@ pprExport avail@(AvailTC n _) = pp_export [] = Outputable.empty pp_export names = braces (hsep (map ppr names)) -pprUsage :: Usage -> SDoc -pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } - = pprUsageImport mod hash safe -pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name - , usg_mod_hash = hash, usg_safe = safe - , usg_exports = exports, usg_entities = entities } - = pprUsageImport (mkModule unit_id mod_name) hash safe $$ - nest 2 ( - maybe Outputable.empty (\v -> text "exports: " <> ppr v) exports $$ - vcat [ ppr n <+> ppr v | (n,v) <- entities ] - ) -pprUsage usage at UsageFile{} - = hsep [text "addDependentFile", - doubleQuotes (ftext (usg_file_path usage)), - ppr (usg_file_hash usage)] -pprUsage usage at UsageMergedRequirement{} - = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] -pprUsage usage at UsageHomeModuleInterface{} - = hsep [text "implementation", ppr (usg_mod_name usage) - , ppr (usg_unit_id usage) - , ppr (usg_iface_hash usage)] - -pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc -pprUsageImport mod hash safe - = hsep [ text "import", pp_safe, ppr mod - , ppr hash ] - where - pp_safe | safe = text "safe" - | otherwise = text " -/ " pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -88,13 +88,13 @@ import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModSummary import GHC.Unit.Module.Deps -import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign, emptyIfaceForeign) import Data.Function import Data.List ( sortBy ) import Data.Ord import Data.IORef - +import Data.Traversable {- ************************************************************************ @@ -143,11 +143,13 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos stubs foreign_files = updateDecl (mi_decls partial_iface) mb_stg_infos mb_cmm_infos -- See Note [Foreign stubs and TH bytecode linking] - foreign_ <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + mi_simplified_core <- for (mi_simplified_core partial_iface) $ \simpl_core -> do + fs <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + return $ (simpl_core { mi_sc_foreign = fs }) full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env $ set_mi_foreign foreign_ $ set_mi_decls decls partial_iface + addFingerprints hsc_env $ set_mi_simplified_core mi_simplified_core $ set_mi_decls decls partial_iface -- Debug printing let unit_state = hsc_units hsc_env @@ -289,7 +291,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode - -> Maybe ModIfaceSelfRecomp + -> Maybe IfaceSelfRecomp -> Maybe Docs -> ModDetails -> PartialModIface @@ -316,8 +318,8 @@ mkIface_ hsc_env entities = typeEnvElts type_env show_linear_types = xopt LangExt.LinearTypes (hsc_dflags hsc_env) - extra_decls = if gopt Opt_WriteIfSimplifiedCore dflags then Just [ toIfaceTopBind b | b <- core_prog ] - else Nothing + simplified_core = if gopt Opt_WriteIfSimplifiedCore dflags then Just (IfaceSimplifiedCore [ toIfaceTopBind b | b <- core_prog ] emptyIfaceForeign) + else Nothing decls = [ tyThingToIfaceDecl show_linear_types entity | entity <- entities, let name = getName entity, @@ -370,12 +372,12 @@ mkIface_ hsc_env & set_mi_anns annotations & set_mi_top_env rdrs & set_mi_decls decls - & set_mi_extra_decls extra_decls + & set_mi_simplified_core simplified_core & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) & set_mi_docs docs - & set_mi_final_exts () + & set_mi_abi_hashes () & set_mi_ext_fields emptyExtensibleFields & set_mi_hi_bytes PartialIfaceBinHandle ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -88,6 +88,7 @@ import Data.Ord import Data.Containers.ListUtils import Data.Bifunctor import GHC.Iface.Errors.Ppr +import Data.Functor {- ----------------------------------------------- @@ -325,8 +326,8 @@ check_old_iface hsc_env mod_summary maybe_iface maybe_dyn_iface <- liftIO $ loadIface (setDynamicNow dflags) (msDynHiFilePath mod_summary) case maybe_dyn_iface of Nothing -> return $ outOfDateItemBecause MissingDynHiFile Nothing - Just dyn_iface | mi_iface_hash (mi_final_exts dyn_iface) - /= mi_iface_hash (mi_final_exts normal_iface) + Just dyn_iface | mi_iface_hash dyn_iface + /= mi_iface_hash normal_iface -> return $ outOfDateItemBecause MismatchedDynHiFile Nothing Just {} -> return res _ -> return res @@ -382,7 +383,7 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface - -> ModIfaceSelfRecomp + -> IfaceSelfRecomp -> IfG (MaybeValidated ModIface) checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger @@ -435,7 +436,7 @@ checkVersions hsc_env mod_summary iface self_recomp -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins :: Plugins -> IfaceSelfRecomp -> IfG RecompileRequired checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp @@ -528,10 +529,10 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash :: HscEnv -> Module -> IfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + let FingerprintWithValue old_fp old_flags = mi_sr_flag_hash self_recomp (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally if old_fp == new_fp then up_to_date logger (text "Module flags unchanged") @@ -573,7 +574,7 @@ checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkOptimHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env let old_hash = mi_sr_opt_hash iface @@ -589,7 +590,7 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env let old_hash = mi_sr_hpc_hash self_recomp @@ -606,7 +607,7 @@ checkHpcHash hsc_env self_recomp = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures :: HscEnv -> ModSummary -> IfaceSelfRecomp -> IO RecompileRequired checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env @@ -748,7 +749,7 @@ checkModUsage _ UsagePackageModule{ logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChanged (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) -- We only track the ABI hash of package modules, rather than -- individual entity usages, so if the ABI hash changes we must -- recompile. This is safe but may entail more recompilation when @@ -758,7 +759,7 @@ checkModUsage _ UsageMergedRequirement{ usg_mod = mod, usg_mod_hash = old_mod_ha logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedRaw (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name , usg_unit_id = uid , usg_iface_hash = old_mod_hash } = do @@ -766,7 +767,7 @@ checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedIface mod_name - checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash (mi_final_exts iface)) + checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash iface) checkModUsage _ UsageHomeModule{ usg_mod_name = mod_name, @@ -779,9 +780,9 @@ checkModUsage _ UsageHomeModule{ logger <- getLogger needInterface mod $ \iface -> do let - new_mod_hash = mi_mod_hash (mi_final_exts iface) - new_decl_hash = mi_hash_fn (mi_final_exts iface) - new_export_hash = mi_exp_hash (mi_final_exts iface) + new_mod_hash = mi_mod_hash iface + new_decl_hash = mi_hash_fn iface + new_export_hash = mi_exp_hash iface reason = ModuleChanged (moduleName mod) @@ -986,7 +987,7 @@ we use is: -- | Compute the information needed for self-recompilation checking. This -- information can be computed before the backend phase. -mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO IfaceSelfRecomp mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env @@ -1000,10 +1001,10 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do let include_detailed_flags (flag_hash, flags) = if gopt Opt_WriteSelfRecompFlags dflags - then (flag_hash, Just flags) - else (flag_hash, Nothing) + then FingerprintWithValue flag_hash (Just flags) + else FingerprintWithValue flag_hash Nothing - return (ModIfaceSelfRecomp + return (IfaceSelfRecomp { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash @@ -1018,28 +1019,92 @@ addFingerprints :: HscEnv -> PartialModIface -> IO ModIface -addFingerprints hsc_env iface0 - = do - eps <- hscEPS hsc_env - let - decls = mi_decls iface0 - decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings $ mi_warns iface0) - export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ mi_warns iface0) - fix_fn = mkIfaceFixCache (mi_fixities iface0) +addFingerprints hsc_env iface0 = do + (abiHashes, caches, decls_w_hashes) <- addAbiHashes hsc_env (mi_mod_info iface0) (mi_public iface0) (mi_deps iface0) + + -- put the declarations in a canonical order, sorted by OccName + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ + [(getOccName d, e) | e@(_, d) <- decls_w_hashes] + + -- This key is safe because mi_extra_decls contains tidied things. + getOcc (IfGblTopBndr b) = getOccName b + getOcc (IfLclTopBndr fs _ _ details) = + case details of + IfRecSelId { ifRecSelFirstCon = first_con } + -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) + _ -> mkVarOccFS (ifLclNameFS fs) + + binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () + binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) + + sorted_extra_decls :: Maybe IfaceSimplifiedCore + sorted_extra_decls = mi_simplified_core iface0 <&> \simpl_core -> + IfaceSimplifiedCore (sortOn binding_key (mi_sc_extra_decls simpl_core)) (mi_sc_foreign simpl_core) + + -- The interface hash depends on: + -- - the ABI hash, plus + -- - the things which can affect whether a module is recompiled + -- - the module level annotations, + -- - deps (home and external packages, dependent files) + iface_hash <- computeFingerprint putNameLiterally + (mi_abi_mod_hash abiHashes, + mi_self_recomp_info iface0, + mi_deps iface0) + + let final_iface = completePartialModIface iface0 iface_hash + sorted_decls sorted_extra_decls abiHashes caches + -- + return final_iface + + + +-- The ABI hash should depend on everything in IfacePublic +-- This is however computed in a very convoluted way, so be careful your +-- addition ends up in the right place. In essence all this function does is +-- compute a hash of the arguments. +-- +-- Why the convoluted way? Hashing individual declarations allows us to do fine-grained +-- recompilation checking for home package modules, which record precisely what they use +-- from each module. +addAbiHashes :: HscEnv -> IfaceModInfo -> PartialIfacePublic -> Dependencies -> IO (IfaceAbiHashes, IfaceCache, [(Fingerprint, IfaceDecl)]) +addAbiHashes hsc_env info iface_public deps = do + eps <- hscEPS hsc_env + let + -- If you have arrived here by accident then congratulations, + -- you have discovered the ABI hash. Your reward is to update the ABI hash to + -- account for your change to the interface file. Omitting your field using a + -- wildcard may lead to some unfortunate consequences. + + -- MP: TODO: Existing bug where defaults, trust_pkg and complete are not taken into account + -- when computing the ABI hash. + IfacePublic exports fixities warns anns decls _defaults insts fam_insts rules trust _trust_pkg _complete _cache () = iface_public + -- And these fields of deps should be in IfacePublic, but in good time. + Dependencies _ _ _ sig_mods trusted_pkgs boot_mods orph_mods fis_mods = deps + decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings warns) + export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ warns) + fix_fn = mkIfaceFixCache fixities + + this_mod = mi_mod_info_module info + semantic_mod = mi_mod_info_semantic_module info + (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph insts + (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph rules + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph fam_insts + ann_fn = mkIfaceAnnCache anns -- The ABI of a declaration represents everything that is made -- visible about the declaration that a client can depend on. -- see IfaceDeclABI below. - declABI :: IfaceDecl -> IfaceDeclABI + declABI :: IfaceDecl -> IfaceDeclABI -- TODO: I'm not sure if this should be semantic_mod or this_mod. -- See also Note [Identity versus semantic module] - declABI decl = (this_mod, decl, extras) + declABI decl = (this_mod, decl, extras) where extras = declExtras fix_fn ann_fn non_orph_rules non_orph_insts non_orph_fis top_lvl_name_env decl -- This is used for looking up the Name of a default method -- from its OccName. See Note [default method Name] - top_lvl_name_env = + top_lvl_name_env = mkOccEnv [ (nameOccName nm, nm) | IfaceId { ifName = nm } <- decls ] @@ -1047,15 +1112,15 @@ addFingerprints hsc_env iface0 -- This is computed by finding the free external names of each -- declaration, including IfaceDeclExtras (things that a -- declaration implicitly depends on). - edges :: [ Node OccName IfaceDeclABI ] - edges = [ DigraphNode abi (getOccName decl) out + edges :: [ Node OccName IfaceDeclABI ] + edges = [ DigraphNode abi (getOccName decl) out | decl <- decls , let abi = declABI decl , let out = localOccs $ freeNamesDeclABI abi ] - name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) - localOccs = + name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) + localOccs = map (getParent . getOccName) -- NB: names always use semantic module, so -- filtering must be on the semantic module! @@ -1073,17 +1138,17 @@ addFingerprints hsc_env iface0 -- maps OccNames to their parents in the current module. -- e.g. a reference to a constructor must be turned into a reference -- to the TyCon for the purposes of calculating dependencies. - parent_map :: OccEnv OccName - parent_map = foldl' extend emptyOccEnv decls + parent_map :: OccEnv OccName + parent_map = foldl' extend emptyOccEnv decls where extend env d = extendOccEnvList env [ (b,n) | b <- ifaceDeclImplicitBndrs d ] where n = getOccName d -- Strongly-connected groups of declarations, in dependency order - groups :: [SCC IfaceDeclABI] - groups = stronglyConnCompFromEdgedVerticesOrd edges + groups :: [SCC IfaceDeclABI] + groups = stronglyConnCompFromEdgedVerticesOrd edges - global_hash_fn = mkHashFun hsc_env eps + global_hash_fn = mkHashFun hsc_env eps -- How to output Names when generating the data to fingerprint. -- Here we want to output the fingerprint for each top-level @@ -1091,9 +1156,9 @@ addFingerprints hsc_env iface0 -- module. In this way, the fingerprint for a declaration will -- change if the fingerprint for anything it refers to (transitively) -- changes. - mk_put_name :: OccEnv (OccName,Fingerprint) + mk_put_name :: OccEnv (OccName,Fingerprint) -> WriteBinHandle -> Name -> IO () - mk_put_name local_env bh name + mk_put_name local_env bh name | isWiredInName name = putNameLiterally bh name -- wired-in names don't have fingerprints | otherwise @@ -1120,21 +1185,21 @@ addFingerprints hsc_env iface0 -- take a strongly-connected group of declarations and compute -- its fingerprint. - fingerprint_group :: (OccEnv (OccName,Fingerprint), + fingerprint_group :: (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) -> SCC IfaceDeclABI -> IO (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) - fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) - = do let hash_fn = mk_put_name local_env - decl = abiDecl abi + fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) + = do let hash_fn = mk_put_name local_env + decl = abiDecl abi --pprTrace "fingerprinting" (ppr (ifName decl) ) $ do - hash <- computeFingerprint hash_fn abi - env' <- extend_hash_env local_env (hash,decl) - return (env', (hash,decl) : decls_w_hashes) + hash <- computeFingerprint hash_fn abi + env' <- extend_hash_env local_env (hash,decl) + return (env', (hash,decl) : decls_w_hashes) - fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) + fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) = do let stable_abis = sortBy cmp_abiNames abis stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env @@ -1150,33 +1215,27 @@ addFingerprints hsc_env iface0 return (local_env2, pairs ++ decls_w_hashes) -- Make a fingerprint from the ordinal position of a binding in its group. - mkRecFingerprint :: Word64 -> Fingerprint - mkRecFingerprint i = Fingerprint 0 i + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i - bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint - bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. -- - extend_hash_env :: OccEnv (OccName,Fingerprint) + extend_hash_env :: OccEnv (OccName,Fingerprint) -> (Fingerprint,IfaceDecl) -> IO (OccEnv (OccName,Fingerprint)) - extend_hash_env env0 (hash,d) = + extend_hash_env env0 (hash,d) = return (foldr (\(b,fp) env -> extendOccEnv env b (b,fp)) env0 (ifaceDeclFingerprints hash d)) -- - (local_env, decls_w_hashes) <- + (local_env, decls_w_hashes) <- foldM fingerprint_group (emptyOccEnv, []) groups - -- when calculating fingerprints, we always need to use canonical ordering - -- for lists of things. The mi_deps has various lists of modules and - -- suchlike, which are stored in canonical order: - let sorted_deps :: Dependencies - sorted_deps = mi_deps iface0 - -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way -- that changes in orphans get propagated all the way up the @@ -1202,10 +1261,11 @@ addFingerprints hsc_env iface0 -- External. It's true that Home1 will get rebuilt if the orphans -- of External, but we also need to make sure Home2 gets rebuilt -- as well. See #12733 for more details. - let orph_mods - = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] - $ dep_orphs sorted_deps - dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods + let orph_mods_no_self + = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] + $ orph_mods + dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods_no_self + -- Note [Do not update EPS with your own hi-boot] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1216,26 +1276,26 @@ addFingerprints hsc_env iface0 -- instances yourself, no need to consult hs-boot; if you do load the -- interface into EPS, you will see a duplicate orphan instance. - orphan_hash <- computeFingerprint (mk_put_name local_env) + orphan_hash <- computeFingerprint (mk_put_name local_env) (map ifDFun orph_insts, orph_rules, orph_fis) - -- Hash of the transitive things in dependencies - dep_hash <- computeFingerprint putNameLiterally - (dep_sig_mods (mi_deps iface0), - dep_boot_mods (mi_deps iface0), - -- Trusted packages are like orphans - dep_trusted_pkgs (mi_deps iface0), + -- Hash of the transitive things in dependencies + dep_hash <- computeFingerprint putNameLiterally + (sig_mods, + boot_mods, + -- Trusted packages are like orphans + trusted_pkgs, -- See Note [Export hash depends on non-orphan family instances] - dep_finsts (mi_deps iface0) ) + fis_mods ) - -- the export list hash doesn't depend on the fingerprints of - -- the Names it mentions, only the Names themselves, hence putNameLiterally. - export_hash <- computeFingerprint putNameLiterally - (mi_exports iface0, + -- the export list hash doesn't depend on the fingerprints of + -- the Names it mentions, only the Names themselves, hence putNameLiterally. + export_hash <- computeFingerprint putNameLiterally + (exports, orphan_hash, dep_hash, dep_orphan_hashes, - mi_trust iface0) + trust) -- Make sure change of Safe Haskell mode causes recomp. -- Note [Export hash depends on non-orphan family instances] @@ -1266,79 +1326,44 @@ addFingerprints hsc_env iface0 -- (also we didn't store it anywhere!) -- - -- put the declarations in a canonical order, sorted by OccName - let sorted_decls :: [(Fingerprint, IfaceDecl)] - sorted_decls = Map.elems $ Map.fromList $ - [(getOccName d, e) | e@(_, d) <- decls_w_hashes] - -- This key is safe because mi_extra_decls contains tidied things. - getOcc (IfGblTopBndr b) = getOccName b - getOcc (IfLclTopBndr fs _ _ details) = - case details of - IfRecSelId { ifRecSelFirstCon = first_con } - -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) - _ -> mkVarOccFS (ifLclNameFS fs) - - binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () - binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) - - sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - - -- the ABI hash depends on: - -- - decls - -- - export list - -- - orphans - -- - deprecations - -- - flag abi hash - -- - foreign stubs and files - mod_hash <- computeFingerprint putNameLiterally - (map fst sorted_decls, + -- the ABI hash depends on: + -- - decls + -- - export list + -- - orphans + -- - deprecations + -- - flag abi hash + mod_hash <- computeFingerprint putNameLiterally + (sort (map fst decls_w_hashes), export_hash, -- includes orphan_hash - mi_warns iface0, - mi_foreign iface0) - - - -- The interface hash depends on: - -- - the ABI hash, plus - -- - the things which can affect whether a module is recompiled - -- - the module level annotations, - -- - deps (home and external packages, dependent files) - iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_self_recomp_info iface0, - sorted_deps ) + ann_fn AnnModule, + warns) - let - final_iface_exts = ModIfaceBackend - { mi_mod_hash = mod_hash - , mi_iface_hash = iface_hash - , mi_orphan = not ( all ifRuleAuto orph_rules + -- Surely the ABI depends on "module" annotations? + -- Also named defaults + + + + let + final_iface_exts = IfaceAbiHashes + { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts && null orph_fis) - , mi_finsts = not (null (mi_fam_insts iface0)) - , mi_exp_hash = export_hash - , mi_orphan_hash = orphan_hash - , mi_decl_warn_fn = decl_warn_fn - , mi_export_warn_fn = export_warn_fn - , mi_fix_fn = fix_fn - , mi_hash_fn = lookupOccEnv local_env + , mi_abi_finsts = not (null fam_insts) + , mi_abi_exp_hash = export_hash + , mi_abi_orphan_hash = orphan_hash } - final_iface = completePartialModIface iface0 - sorted_decls sorted_extra_decls final_iface_exts - -- - return final_iface + caches = IfaceCache + { mi_cache_decl_warn_fn = decl_warn_fn + , mi_cache_export_warn_fn = export_warn_fn + , mi_cache_fix_fn = fix_fn + , mi_cache_hash_fn = lookupOccEnv local_env + } + return (final_iface_exts, caches, decls_w_hashes) where - this_mod = mi_module iface0 - semantic_mod = mi_semantic_module iface0 - (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) - (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) - (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - ann_fn = mkIfaceAnnCache (mi_anns iface0) - -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the @@ -1378,7 +1403,7 @@ getOrphanHashes hsc_env mods = do get_orph_hash mod = do iface <- initIfaceLoad hsc_env . withIfaceErr ctx $ loadInterface (text "getOrphanHashes") mod ImportBySystem - return (mi_orphan_hash (mi_final_exts iface)) + return (mi_orphan_hash iface) mapM get_orph_hash mods @@ -1531,7 +1556,7 @@ instance Binary IfaceIdExtras where put_ bh (IdExtras fix rules anns)= do { put_ bh fix; put_ bh rules; put_ bh anns } declExtras :: (OccName -> Maybe Fixity) - -> (OccName -> [AnnPayload]) + -> (AnnCacheKey -> [AnnPayload]) -> OccEnv [IfaceRule] -> OccEnv [IfaceClsInst] -> OccEnv [IfaceFamInst] @@ -1546,10 +1571,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl IfaceDataExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n) ++ map ifDFun (lookupOccEnvL inst_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) (map (id_extras . occName . ifConName) (visibleIfConDecls cons)) IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} -> - IfaceClassExtras (fix_fn n) insts (ann_fn n) meths defms + IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms where insts = (map ifDFun $ (concatMap at_extras ats) ++ lookupOccEnvL inst_env n) @@ -1562,17 +1587,16 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl , let dmOcc = mkDefaultMethodOcc (nameOccName bndr) , Just dmName <- [lookupOccEnv dm_env dmOcc] ] IfaceSynonym{} -> IfaceSynonymExtras (fix_fn n) - (ann_fn n) + (ann_fn (AnnOccName n)) IfaceFamily{} -> IfaceFamilyExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) _other -> IfaceOtherDeclExtras where n = getOccName decl - id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn occ) + id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl) - {- Note [default method Name] (see also #15970) ~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1685,20 +1709,25 @@ mkHashFun hsc_env eps name -- just one of the many horrible hacks in the backpack -- implementation. $ loadInterface (text "lookupVers2") mod ImportBySystem - return $ snd (mi_hash_fn (mi_final_exts iface) occ `orElse` + return $ snd (mi_hash_fn iface occ `orElse` pprPanic "lookupVers1" (ppr mod <+> ppr occ)) +data AnnCacheKey = AnnModule | AnnOccName OccName + -- | Creates cached lookup for the 'mi_anns' field of ModIface -- Hackily, we use "module" as the OccName for any module-level annotations -mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload] +mkIfaceAnnCache :: [IfaceAnnotation] -> AnnCacheKey -> [AnnPayload] mkIfaceAnnCache anns - = \n -> lookupOccEnv env n `orElse` [] + = \n -> case n of + AnnModule -> module_anns + AnnOccName occn -> lookupOccEnv env occn `orElse` [] where - pair (IfaceAnnotation target value) = - (case target of - NamedTarget occn -> occn - ModuleTarget _ -> mkVarOccFS (fsLit "module") - , [value]) + (module_anns, occ_anns) = partitionEithers $ map classify anns + classify (IfaceAnnotation target value) = + case target of + NamedTarget occn -> Right (occn, [value]) + ModuleTarget _ -> Left value + -- flipping (++), so the first argument is always short - env = mkOccEnv_C (flip (++)) (map pair anns) + env = mkOccEnv_C (flip (++)) occ_anns ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,5 +1,5 @@ module GHC.Iface.Recomp.Types ( - ModIfaceSelfRecomp(..), + IfaceSelfRecomp(..), IfaceDynFlags(..), pprIfaceDynFlags, missingExtraFlagInfo, @@ -9,7 +9,9 @@ import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable import GHC.Iface.Flags +import GHC.Types.SafeHaskell import GHC.Unit.Module.Deps +import GHC.Unit.Module import GHC.Utils.Binary @@ -59,8 +61,8 @@ proper way. -- itself. -- -- See Note [Self recompilation information in interface files] -data ModIfaceSelfRecomp = - ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint +data IfaceSelfRecomp = + IfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint -- ^ Hash of the .hs source, used for recompilation checking. , mi_sr_usages :: [Usage] -- ^ Usages; kept sorted so that it's easy to decide @@ -69,7 +71,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) + , mi_sr_flag_hash :: !(FingerprintWithValue IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -81,8 +83,8 @@ data ModIfaceSelfRecomp = } -instance Binary ModIfaceSelfRecomp where - put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do +instance Binary IfaceSelfRecomp where + put_ bh (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do put_ bh mi_sr_src_hash lazyPut bh mi_sr_usages put_ bh mi_sr_flag_hash @@ -97,19 +99,58 @@ instance Binary ModIfaceSelfRecomp where opt_hash <- get bh hpc_hash <- get bh plugin_hash <- get bh - return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + return $ IfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } -instance Outputable ModIfaceSelfRecomp where - ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) +instance Outputable IfaceSelfRecomp where + ppr (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash - , text "usages:" <+> ppr (length mi_sr_usages) - , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash + , text "flags:" <+> pprFingerprintWithValue missingExtraFlagInfo (fmap pprIfaceDynFlags mi_sr_flag_hash) , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash + , text "usages:" <+> ppr (map pprUsage mi_sr_usages) ])] -instance NFData ModIfaceSelfRecomp where - rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file +instance NFData IfaceSelfRecomp where + rnf (IfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () + +pprFingerprintWithValue :: SDoc -> FingerprintWithValue SDoc -> SDoc +pprFingerprintWithValue missingInfo (FingerprintWithValue fp mflags) + = vcat $ + [ text "fingerprint:" <+> (ppr fp) + ] + ++ case mflags of + Nothing -> [missingInfo] + Just doc -> [doc] + +pprUsage :: Usage -> SDoc +pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } + = pprUsageImport mod hash safe +pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name + , usg_mod_hash = hash, usg_safe = safe + , usg_exports = exports, usg_entities = entities } + = pprUsageImport (mkModule unit_id mod_name) hash safe $$ + nest 2 ( + maybe empty (\v -> text "exports: " <> ppr v) exports $$ + vcat [ ppr n <+> ppr v | (n,v) <- entities ] + ) +pprUsage usage at UsageFile{} + = hsep [text "addDependentFile", + doubleQuotes (ftext (usg_file_path usage)), + ppr (usg_file_hash usage)] +pprUsage usage at UsageMergedRequirement{} + = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] +pprUsage usage at UsageHomeModuleInterface{} + = hsep [text "implementation", ppr (usg_mod_name usage) + , ppr (usg_unit_id usage) + , ppr (usg_iface_hash usage)] + +pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc +pprUsageImport mod hash safe + = hsep [ text "import", pp_safe, ppr mod + , ppr hash ] + where + pp_safe | safe = text "safe" + | otherwise = text " -/ " \ No newline at end of file ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -183,7 +183,7 @@ lookupFixityRn_help name -- loadInterfaceForName will find B.hi even if B is a hidden module, -- and that's what we want. = do { iface <- loadInterfaceForName doc name - ; let mb_fix = mi_fix_fn (mi_final_exts iface) occ + ; let mb_fix = mi_fix_fn iface occ ; let msg = case mb_fix of Nothing -> text "looking up name" <+> ppr name ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -485,8 +485,8 @@ calculateAvails :: HomeUnit calculateAvails home_unit other_home_units iface mod_safe' want_boot imported_by = let imp_mod = mi_module iface imp_sem_mod= mi_semantic_module iface - orph_iface = mi_orphan (mi_final_exts iface) - has_finsts = mi_finsts (mi_final_exts iface) + orph_iface = mi_orphan iface + has_finsts = mi_finsts iface deps = mi_deps iface trust = getSafeMode $ mi_trust iface trust_pkg = mi_trust_pkg iface @@ -1397,7 +1397,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) _ -> failLookupWith err mk_depr_export_warning gre - = DeprecatedExport name <$> mi_export_warn_fn (mi_final_exts iface) name + = DeprecatedExport name <$> mi_export_warn_fn iface name where name = greName gre ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -539,9 +539,9 @@ warnIfDeclDeprecated gre@(GRE { gre_imp = iss }) lookupImpDeclDeprec :: ModIface -> GlobalRdrElt -> Maybe (WarningTxt GhcRn) lookupImpDeclDeprec iface gre -- Bleat if the thing, or its parent, is warn'd - = mi_decl_warn_fn (mi_final_exts iface) (greOccName gre) `mplus` + = mi_decl_warn_fn iface (greOccName gre) `mplus` case greParent gre of - ParentIs p -> mi_decl_warn_fn (mi_final_exts iface) (nameOccName p) + ParentIs p -> mi_decl_warn_fn iface (nameOccName p) NoParent -> Nothing warnIfExportDeprecated :: GlobalRdrElt -> RnM () @@ -562,7 +562,7 @@ warnIfExportDeprecated gre@(GRE { gre_imp = iss }) process_import_spec is = do let mod = is_mod $ is_decl is iface <- loadInterfaceForModule doc mod - let mb_warn_txt = mi_export_warn_fn (mi_final_exts iface) name + let mb_warn_txt = mi_export_warn_fn iface name return $ (moduleName mod, ) <$> mb_warn_txt ------------------------- ===================================== compiler/GHC/Tc/Instance/Family.hs ===================================== @@ -308,7 +308,7 @@ checkFamInstConsistency directlyImpMods ifc <- modIface mod deps <- dep_finsts . mi_deps <$> modIface mod pure $ - if mi_finsts (mi_final_exts ifc) + if mi_finsts ifc then mod:deps else deps ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -97,7 +97,7 @@ checkHsigDeclM sig_iface sig_thing real_thing = do -- implementation cases. checkBootDeclM Hsig sig_thing real_thing real_fixity <- lookupFixityRn name - let sig_fixity = case mi_fix_fn (mi_final_exts sig_iface) (occName name) of + let sig_fixity = case mi_fix_fn sig_iface (occName name) of Nothing -> defaultFixity Just f -> f when (real_fixity /= sig_fixity) $ @@ -850,7 +850,7 @@ mergeSignatures if outer_mod == mi_module iface -- Don't add ourselves! then tcg_merged tcg_env - else (mi_module iface, mi_mod_hash (mi_final_exts iface)) : tcg_merged tcg_env + else (mi_module iface, mi_mod_hash iface) : tcg_merged tcg_env } -- Note [Signature merging DFuns] ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -1,18 +1,20 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ExplicitNamespaces #-} -- | Dependencies and Usage of a module module GHC.Unit.Module.Deps - ( Dependencies - , mkDependencies - , noDependencies - , dep_direct_mods - , dep_direct_pkgs - , dep_sig_mods - , dep_trusted_pkgs - , dep_orphs - , dep_plugin_pkgs - , dep_finsts - , dep_boot_mods + ( Dependencies(dep_direct_mods + , dep_direct_pkgs + , dep_sig_mods + , dep_trusted_pkgs + , dep_orphs + , dep_plugin_pkgs + , dep_finsts + , dep_boot_mods + , Dependencies) , dep_orphs_update , dep_finsts_update + , mkDependencies + , noDependencies , pprDeps , Usage (..) , ImportAvails (..) @@ -52,38 +54,38 @@ import Control.DeepSeq -- -- See Note [Transitive Information in Dependencies] data Dependencies = Deps - { dep_direct_mods :: Set (UnitId, ModuleNameWithIsBoot) + { dep_direct_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All home-package modules which are directly imported by this one. -- This may include modules from other units when using multiple home units - , dep_direct_pkgs :: Set UnitId + , dep_direct_pkgs_ :: Set UnitId -- ^ All packages directly imported by this module -- I.e. packages to which this module's direct imports belong. -- Does not include other home units when using multiple home units. -- Modules from these units will go in `dep_direct_mods` - , dep_plugin_pkgs :: Set UnitId + , dep_plugin_pkgs_ :: Set UnitId -- ^ All units needed for plugins ------------------------------------ -- Transitive information below here - , dep_sig_mods :: ![ModuleName] + , dep_sig_mods_ :: ![ModuleName] -- ^ Transitive closure of hsig files in the home package - , dep_trusted_pkgs :: Set UnitId + , dep_trusted_pkgs_ :: Set UnitId -- Packages which we are required to trust -- when the module is imported as a safe import -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names - , dep_boot_mods :: Set (UnitId, ModuleNameWithIsBoot) + , dep_boot_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All modules which have boot files below this one, and whether we -- should use the boot file or not. -- This information is only used to populate the eps_is_boot field. -- See Note [Structure of dep_boot_mods] - , dep_orphs :: [Module] + , dep_orphs_ :: [Module] -- ^ Transitive closure of orphan modules (whether -- home or external pkg). -- @@ -93,7 +95,7 @@ data Dependencies = Deps -- which relies on dep_orphs having the complete list!) -- This does NOT include us, unlike 'imp_orphs'. - , dep_finsts :: [Module] + , dep_finsts_ :: [Module] -- ^ Transitive closure of depended upon modules which -- contain family instances (whether home or external). -- This is used by 'checkFamInstConsistency'. This @@ -105,6 +107,26 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +pattern Dependencies :: Set (UnitId, ModuleNameWithIsBoot) + -> Set UnitId + -> Set UnitId + -> [ModuleName] + -> Set UnitId + -> Set (UnitId, ModuleNameWithIsBoot) + -> [Module] + -> [Module] + -> Dependencies +pattern Dependencies {dep_direct_mods, dep_direct_pkgs, dep_plugin_pkgs, dep_sig_mods, dep_trusted_pkgs, dep_boot_mods, dep_orphs, dep_finsts} + <- Deps {dep_direct_mods_ = dep_direct_mods + , dep_direct_pkgs_ = dep_direct_pkgs + , dep_plugin_pkgs_ = dep_plugin_pkgs + , dep_sig_mods_ = dep_sig_mods + , dep_trusted_pkgs_ = dep_trusted_pkgs + , dep_boot_mods_ = dep_boot_mods + , dep_orphs_ = dep_orphs + , dep_finsts_ = dep_finsts} +{-# COMPLETE Dependencies #-} + instance NFData Dependencies where rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) = rnf dmods @@ -158,14 +180,14 @@ mkDependencies home_unit mod imports plugin_mods = sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports - in Deps { dep_direct_mods = direct_mods - , dep_direct_pkgs = direct_pkgs - , dep_plugin_pkgs = plugin_units - , dep_sig_mods = sort sig_mods - , dep_trusted_pkgs = trust_pkgs - , dep_boot_mods = source_mods - , dep_orphs = sortBy stableModuleCmp dep_orphs - , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) + in Deps { dep_direct_mods_ = direct_mods + , dep_direct_pkgs_ = direct_pkgs + , dep_plugin_pkgs_ = plugin_units + , dep_sig_mods_ = sort sig_mods + , dep_trusted_pkgs_ = trust_pkgs + , dep_boot_mods_ = source_mods + , dep_orphs_ = sortBy stableModuleCmp dep_orphs + , dep_finsts_ = sortBy stableModuleCmp (imp_finsts imports) -- sort to get into canonical order -- NB. remember to use lexicographic ordering } @@ -174,14 +196,13 @@ mkDependencies home_unit mod imports plugin_mods = dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_orphs_update deps f = do r <- f (dep_orphs deps) - pure (deps { dep_orphs = sortBy stableModuleCmp r }) + pure (deps { dep_orphs_ = sortBy stableModuleCmp r }) -- | Update module dependencies containing family instances (used by Backpack) dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_finsts_update deps f = do r <- f (dep_finsts deps) - pure (deps { dep_finsts = sortBy stableModuleCmp r }) - + pure (deps { dep_finsts_ = sortBy stableModuleCmp r }) instance Binary Dependencies where put_ bh deps = do put_ bh (dep_direct_mods deps) @@ -201,36 +222,36 @@ instance Binary Dependencies where sms <- get bh os <- get bh fis <- get bh - return (Deps { dep_direct_mods = dms - , dep_direct_pkgs = dps - , dep_plugin_pkgs = plugin_pkgs - , dep_sig_mods = hsigms - , dep_boot_mods = sms - , dep_trusted_pkgs = tps - , dep_orphs = os, - dep_finsts = fis }) + return (Deps { dep_direct_mods_ = dms + , dep_direct_pkgs_ = dps + , dep_plugin_pkgs_ = plugin_pkgs + , dep_sig_mods_ = hsigms + , dep_boot_mods_ = sms + , dep_trusted_pkgs_ = tps + , dep_orphs_ = os, + dep_finsts_ = fis }) noDependencies :: Dependencies noDependencies = Deps - { dep_direct_mods = Set.empty - , dep_direct_pkgs = Set.empty - , dep_plugin_pkgs = Set.empty - , dep_sig_mods = [] - , dep_boot_mods = Set.empty - , dep_trusted_pkgs = Set.empty - , dep_orphs = [] - , dep_finsts = [] + { dep_direct_mods_ = Set.empty + , dep_direct_pkgs_ = Set.empty + , dep_plugin_pkgs_ = Set.empty + , dep_sig_mods_ = [] + , dep_boot_mods_ = Set.empty + , dep_trusted_pkgs_ = Set.empty + , dep_orphs_ = [] + , dep_finsts_ = [] } -- | Pretty-print unit dependencies pprDeps :: UnitState -> Dependencies -> SDoc -pprDeps unit_state (Deps { dep_direct_mods = dmods - , dep_boot_mods = bmods - , dep_plugin_pkgs = plgns - , dep_orphs = orphs - , dep_direct_pkgs = pkgs - , dep_trusted_pkgs = tps - , dep_finsts = finsts +pprDeps unit_state (Deps { dep_direct_mods_ = dmods + , dep_boot_mods_ = bmods + , dep_plugin_pkgs_ = plgns + , dep_orphs_ = orphs + , dep_direct_pkgs_ = pkgs + , dep_trusted_pkgs_ = tps + , dep_finsts_ = finsts }) = pprWithUnitState unit_state $ vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -11,18 +11,20 @@ module GHC.Unit.Module.ModIface ( ModIface , ModIface_ - ( mi_module + ( mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls , mi_defaults - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_top_env , mi_insts , mi_fam_insts @@ -31,12 +33,17 @@ module GHC.Unit.Module.ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn ) , pattern ModIface + , set_mi_mod_info , set_mi_module , set_mi_sig_of , set_mi_hsc_src @@ -52,24 +59,34 @@ module GHC.Unit.Module.ModIface , set_mi_rules , set_mi_decls , set_mi_defaults - , set_mi_extra_decls - , set_mi_foreign + , set_mi_simplified_core , set_mi_top_env , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches , set_mi_docs - , set_mi_final_exts + , set_mi_abi_hashes , set_mi_ext_fields + , set_mi_caches + , set_mi_decl_warn_fn + , set_mi_export_warn_fn + , set_mi_fix_fn + , set_mi_hash_fn , completePartialModIface , IfaceBinHandle(..) , PartialModIface - , ModIfaceBackend (..) - , ModIfaceSelfRecomp (..) + , IfaceAbiHashes (..) + , IfaceSelfRecomp (..) + , IfaceCache (..) + , IfaceSimplifiedCore (..) , withSelfRecomp , IfaceDeclExts - , IfaceBackendExts + , IfaceAbiHashesExts , IfaceExport + , IfacePublic_(..) + , IfacePublic + , PartialIfacePublic + , IfaceModInfo(..) , WhetherHasOrphans , WhetherHasFamInst , IfaceTopEnv (..) @@ -77,6 +94,7 @@ module GHC.Unit.Module.ModIface , mi_boot , mi_fix , mi_semantic_module + , mi_mod_info_semantic_module , mi_free_holes , mi_mnwib , mi_flag_hash @@ -85,6 +103,11 @@ module GHC.Unit.Module.ModIface , mi_plugin_hash , mi_src_hash , mi_usages + , mi_mod_hash + , mi_orphan + , mi_finsts + , mi_exp_hash + , mi_orphan_hash , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,7 +129,7 @@ import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings -import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..)) import GHC.Types.Avail @@ -147,36 +170,36 @@ We can build a full interface file two ways: type PartialModIface = ModIface_ 'ModIfaceCore type ModIface = ModIface_ 'ModIfaceFinal --- | Extends a PartialModIface with information which is either: --- * Computed after codegen --- * Or computed just before writing the iface to disk. (Hashes) --- In order to fully instantiate it. -data ModIfaceBackend = ModIfaceBackend - { mi_mod_hash :: !Fingerprint +type PartialIfacePublic = IfacePublic_ 'ModIfaceCore +type IfacePublic = IfacePublic_ 'ModIfaceFinal + +-- | Extends a PartialModIface with hashes of the ABI. +-- +-- * The mi_mod_hash is the hash of the entire ABI +-- * THe other fields are more specific hashes of parts of the ABI +data IfaceAbiHashes = IfaceAbiHashes + { mi_abi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_orphan :: !WhetherHasOrphans + , mi_abi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans - , mi_finsts :: !WhetherHasFamInst + , mi_abi_finsts :: !WhetherHasFamInst -- ^ Whether this module has family instances. See Note [The type family -- instance consistency story]. - , mi_exp_hash :: !Fingerprint + , mi_abi_exp_hash :: !Fingerprint -- ^ Hash of export list - , mi_orphan_hash :: !Fingerprint + , mi_abi_orphan_hash :: !Fingerprint -- ^ Hash for orphan rules, class and family instances combined + -- NOT transitive + } - -- Cached environments for easy lookup. These are computed (lazily) from - -- other fields and are not put into the interface file. - -- Not really produced by the backend but there is no need to create them - -- any earlier. - , mi_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) +data IfaceCache = IfaceCache + { mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for declaration deprecations - , mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) + , mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for export deprecations - , mi_fix_fn :: !(OccName -> Maybe Fixity) + , mi_cache_fix_fn :: !(OccName -> Maybe Fixity) -- ^ Cached lookup for 'mi_fixities' - , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) + , mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that -- the thing isn't in decls. It's useful to know that when seeing if we are -- up to date wrt. the old interface. The 'OccName' is the parent of the @@ -195,9 +218,9 @@ type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where IfaceDeclExts 'ModIfaceCore = IfaceDecl IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) -type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where - IfaceBackendExts 'ModIfaceCore = () - IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend +type family IfaceAbiHashesExts (phase :: ModIfacePhase) = bk | bk -> phase where + IfaceAbiHashesExts 'ModIfaceCore = () + IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes -- | In-memory byte array representation of a 'ModIface'. -- @@ -212,7 +235,7 @@ data IfaceBinHandle (phase :: ModIfacePhase) where FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp :: ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r withSelfRecomp iface nk jk = case mi_self_recomp_info iface of Nothing -> nk @@ -220,34 +243,80 @@ withSelfRecomp iface nk jk = --- | A 'ModIface' plus a 'ModDetails' summarises everything we know --- about a compiled module. The 'ModIface' is the stuff *before* linking, --- and can be written out to an interface file. The 'ModDetails is after --- linking and can be completely recovered from just the 'ModIface'. +-- | A 'ModIface' summarises everything we know +-- about a compiled module. -- --- When we read an interface file, we also construct a 'ModIface' from it, --- except that we explicitly make the 'mi_decls' and a few other fields empty; --- as when reading we consolidate the declarations etc. into a number of indexed --- maps and environments in the 'ExternalPackageState'. +-- See Note [Structure of ModIface] for information about what belongs in each field. -- --- See Note [Strictness in ModIface] to learn about why some fields are --- strict and others are not. +-- See Note [Strictness in ModIface] to learn about why all the fields are lazy. -- -- See Note [Private fields in ModIface] to learn why we don't export any of the -- fields. data ModIface_ (phase :: ModIfacePhase) = PrivateModIface { - mi_module_ :: !Module, -- ^ Name of the module we are for - mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? + mi_hi_bytes_ :: !(IfaceBinHandle phase), + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. + mi_iface_hash_ :: Fingerprint, -- A hash of the whole interface - mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? + mi_mod_info_ :: IfaceModInfo, + -- ^ Meta information about the module the interface file is for mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) + -- MP: Needs to be refactored (#25844) + + mi_public_ :: IfacePublic_ phase, + -- ^ The parts of interface which are used by other modules when + -- importing this module. The main, original part of an interface. - mi_exports_ :: ![IfaceExport], + + mi_self_recomp_ :: Maybe IfaceSelfRecomp, + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] + + mi_simplified_core_ :: Maybe IfaceSimplifiedCore, + -- ^ The part of the interface written when `-fwrite-if-simplified-core` is enabled. + -- These parts are used to restart bytecode generation. + + mi_docs_ :: Maybe Docs, + -- ^ Docstrings and related data for use by haddock, the ghci + -- @:doc@ command, and other tools. + -- + -- @Just _@ @<=>@ the module was built with @-haddock at . + + mi_top_env_ :: IfaceTopEnv, + -- ^ Just enough information to reconstruct the top level environment in + -- the /original source/ code for this module. which + -- is NOT the same as mi_exports, nor mi_decls (which + -- may contains declarations for things not actually + -- defined by the user). Used for GHCi and for inspecting + -- the contents of modules via the GHC API only. + + mi_ext_fields_ :: ExtensibleFields + -- ^ Additional optional fields, where the Map key represents + -- the field name, resulting in a (size, serialized data) pair. + -- Because the data is intended to be serialized through the + -- internal `Binary` class (increasing compatibility with types + -- using `Name` and `FastString`, such as HIE), this format is + -- chosen over `ByteString`s. + } + +-- | Meta information about the module the interface file is for +data IfaceModInfo = IfaceModInfo { + mi_mod_info_module :: Module, -- ^ Name of the module we are for + mi_mod_info_sig_of :: Maybe Module, -- ^ Are we a sig of another mod? + mi_mod_info_hsc_src :: HscSource -- ^ Boot? Signature? +} + +-- | The public interface of a module which are used by other modules when importing this module. +-- The ABI of a module. +data IfacePublic_ phase = IfacePublic { + mi_exports_ :: [IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things @@ -273,25 +342,10 @@ data ModIface_ (phase :: ModIfacePhase) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], - -- ^ Extra variable definitions which are **NOT** exposed but when - -- combined with mi_decls allows us to restart code generation. - -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - - mi_foreign_ :: !IfaceForeign, - -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. - -- See Note [Foreign stubs and TH bytecode linking] mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: IfaceTopEnv, - -- ^ Just enough information to reconstruct the top level environment in - -- the /original source/ code for this module. which - -- is NOT the same as mi_exports, nor mi_decls (which - -- may contains declarations for things not actually - -- defined by the user). Used for GHCi and for inspecting - -- the contents of modules via the GHC API only. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -299,53 +353,81 @@ data ModIface_ (phase :: ModIfacePhase) mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_trust_ :: !IfaceTrustInfo, + mi_trust_ :: IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg_ :: !Bool, + mi_trust_pkg_ :: Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches_ :: ![IfaceCompleteMatch], + mi_complete_matches_ :: [IfaceCompleteMatch], + -- ^ {-# COMPLETE #-} declarations - mi_docs_ :: !(Maybe Docs), - -- ^ Docstrings and related data for use by haddock, the ghci - -- @:doc@ command, and other tools. - -- - -- @Just _@ @<=>@ the module was built with @-haddock at . + mi_caches_ :: IfaceCache, + -- ^ Cached lookups of some parts of mi_public - mi_final_exts_ :: !(IfaceBackendExts phase), - -- ^ Either `()` or `ModIfaceBackend` for + mi_abi_hashes_ :: (IfaceAbiHashesExts phase) + -- ^ Either `()` or `IfaceAbiHashes` for -- a fully instantiated interface. - - mi_ext_fields_ :: !ExtensibleFields, - -- ^ Additional optional fields, where the Map key represents - -- the field name, resulting in a (size, serialized data) pair. - -- Because the data is intended to be serialized through the - -- internal `Binary` class (increasing compatibility with types - -- using `Name` and `FastString`, such as HIE), this format is - -- chosen over `ByteString`s. - -- - - mi_hi_bytes_ :: !(IfaceBinHandle phase), - -- ^ A serialised in-memory buffer of this 'ModIface'. - -- If this handle is given, we can avoid serialising the 'ModIface' - -- when writing this 'ModIface' to disk, and write this buffer to disk instead. - -- See Note [Sharing of ModIface]. - - mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) - -- ^ Information needed for checking self-recompilation. - -- See Note [Self recompilation information in interface files] - } + -- These fields are hashes of different parts of the public interface. +} + +mkIfacePublic :: [IfaceExport] + -> [IfaceDeclExts 'ModIfaceFinal] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDefault] + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> IfaceAbiHashes + -> IfacePublic +mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes = IfacePublic { + mi_exports_ = exports, + mi_decls_ = decls, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_defaults_ = defaults, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, + mi_cache_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, + mi_cache_fix_fn = mkIfaceFixCache fixities, + mi_cache_hash_fn = mkIfaceHashCache decls + }, + mi_abi_hashes_ = abi_hashes +} + +-- | The information needed to restart bytecode generation. +-- Enabled by `-fwrite-if-simplified-core`. +data IfaceSimplifiedCore = IfaceSimplifiedCore { + mi_sc_extra_decls :: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -- ^ Extra variable definitions which are **NOT** exposed but when + -- combined with mi_decls allows us to restart code generation. + -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] + , mi_sc_foreign :: IfaceForeign + -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. + -- See Note [Foreign stubs and TH bytecode linking] +} -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff - , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module + { ifaceTopExports :: DetOrdAvails -- ^ all top level things in this module, including unexported stuff + , ifaceImports :: [IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where @@ -362,6 +444,35 @@ instance Binary IfaceTopEnv where {- +Note [Structure of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The ModIface structure is divided into several logical parts: + +1. mi_mod_info: Basic module metadata (name, version, etc.) + +2. mi_public: The public interface of the module, which includes: + - Exports, declarations, fixities, warnings, annotations + - Class and type family instances + - Rewrite rules and COMPLETE pragmas + - Safe Haskell and package trust information + - ABI hashes for recompilation checking + +4. mi_self_recomp: Information needed for self-recompilation checking + (see Note [Self recompilation information in interface files]) + +5. mi_simplified_core: Optional simplified Core for bytecode generation + (only present when -fwrite-if-simplified-core is enabled) + +6. mi_docs: Optional documentation (only present when -haddock is enabled) + +7. mi_top_env: Information about the top-level environment of the original source + +8. mi_ext_fields: Additional fields for extensibility + +This structure helps organize the interface data according to its purpose and usage +patterns. Different parts of the compiler use different fields. By separating them +logically in the interface we can arrange to only deserialize the fields that are needed. + Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -371,7 +482,7 @@ The ModIface is the Haskell representation of an interface (.hi) file. that we have just compiled * For packages that we depend on we load the ModIface from disk. -Some fields in the ModIface are deliberately lazy because when we read +All fields in the ModIface are deliberately lazy because when we read an interface file we don't always need all the parts. For example, an interface file contains information about documentation which is often not needed during compilation. This is achieved using the lazyPut/lazyGet pair. @@ -384,23 +495,43 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) -mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ +mi_flag_hash :: ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags) +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint -mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_ mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint -mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_ mi_src_hash :: ModIface_ phase -> Maybe Fingerprint -mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_ mi_usages :: ModIface_ phase -> Maybe [Usage] -mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ +mi_usages = fmap mi_sr_usages . mi_self_recomp_ mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint -mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_ + +-- | Accessor for the module hash of the ABI from a ModIface. +mi_mod_hash :: ModIface -> Fingerprint +mi_mod_hash iface = mi_abi_mod_hash (mi_abi_hashes iface) + +-- | Accessor for whether this module has orphans from a ModIface. +mi_orphan :: ModIface -> WhetherHasOrphans +mi_orphan iface = mi_abi_orphan (mi_abi_hashes iface) + +-- | Accessor for whether this module has family instances from a ModIface. +mi_finsts :: ModIface -> WhetherHasFamInst +mi_finsts iface = mi_abi_finsts (mi_abi_hashes iface) + +-- | Accessor for the hash of the export list from a ModIface. +mi_exp_hash :: ModIface -> Fingerprint +mi_exp_hash iface = mi_abi_exp_hash (mi_abi_hashes iface) + +-- | Accessor for the hash of orphan rules, class and family instances combined from a ModIface. +mi_orphan_hash :: ModIface -> Fingerprint +mi_orphan_hash iface = mi_abi_orphan_hash (mi_abi_hashes iface) -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. @@ -415,16 +546,19 @@ mi_mnwib iface = GWIB (moduleName $ mi_module iface) (mi_boot iface) -- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be -- found, 'defaultFixity' is returned instead. mi_fix :: ModIface -> OccName -> Fixity -mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity +mi_fix iface name = mi_fix_fn iface name `orElse` defaultFixity -- | The semantic module for this interface; e.g., if it's a interface -- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module' -- will be @<A>@. -mi_semantic_module :: ModIface_ a -> Module -mi_semantic_module iface = case mi_sig_of iface of - Nothing -> mi_module iface +mi_mod_info_semantic_module :: IfaceModInfo -> Module +mi_mod_info_semantic_module iface = case mi_mod_info_sig_of iface of + Nothing -> mi_mod_info_module iface Just mod -> mod +mi_semantic_module :: ModIface_ a -> Module +mi_semantic_module iface = mi_mod_info_semantic_module (mi_mod_info iface) + -- | The "precise" free holes, e.g., the signatures that this -- 'ModIface' depends on. mi_free_holes :: ModIface -> UniqDSet ModuleName @@ -455,191 +589,229 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + put_ bh (PrivateModIface + { mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then -- we likely have a good reason, and do not want to reuse -- the byte array. -- See Note [Private fields in ModIface] + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_anns_ = anns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - mi_complete_matches_ = complete_matches, + mi_public_ = public, mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_self_recomp_info_ = self_recomp, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash - }}) = do - put_ bh mod - put_ bh sig_of - put_ bh hsc_src - put_ bh self_recomp - put_ bh mod_hash + mi_self_recomp_ = self_recomp, + mi_simplified_core_ = simplified_core + }) = do + put_ bh mod_info put_ bh iface_hash - put_ bh orphan - put_ bh hasFamInsts lazyPut bh deps - put_ bh exports - put_ bh exp_hash - put_ bh fixities - lazyPut bh warns - lazyPut bh anns - put_ bh decls - put_ bh extra_decls - put_ bh defaults - put_ bh foreign_ - put_ bh insts - put_ bh fam_insts - lazyPut bh rules - put_ bh orphan_hash - put_ bh trust - put_ bh trust_pkg - put_ bh complete_matches + lazyPut bh public lazyPut bh top_env lazyPutMaybe bh docs + lazyPutMaybe bh self_recomp + lazyPutMaybe bh simplified_core get bh = do - mod <- get bh - sig_of <- get bh - hsc_src <- get bh - self_recomp_info <- get bh - mod_hash <- get bh + mod_info <- get bh iface_hash <- get bh - orphan <- get bh - hasFamInsts <- get bh deps <- lazyGet bh - exports <- {-# SCC "bin_exports" #-} get bh - exp_hash <- get bh - fixities <- {-# SCC "bin_fixities" #-} get bh - warns <- {-# SCC "bin_warns" #-} lazyGet bh - anns <- {-# SCC "bin_anns" #-} lazyGet bh - decls <- {-# SCC "bin_tycldecls" #-} get bh - extra_decls <- get bh - defaults <- get bh - foreign_ <- get bh - insts <- {-# SCC "bin_insts" #-} get bh - fam_insts <- {-# SCC "bin_fam_insts" #-} get bh - rules <- {-# SCC "bin_rules" #-} lazyGet bh - orphan_hash <- get bh - trust <- get bh - trust_pkg <- get bh - complete_matches <- get bh + public <- lazyGet bh top_env <- lazyGet bh docs <- lazyGetMaybe bh + self_recomp <- lazyGetMaybe bh + simplified_core <- lazyGetMaybe bh + return (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = - -- We can't populate this field here, as we are - -- missing the 'mi_ext_fields_' field, which is - -- handled in 'getIfaceWithExtFields'. - FullIfaceBinHandle Strict.Nothing, + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_anns_ = anns, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - -- And build the cached values - mi_complete_matches_ = complete_matches, + mi_public_ = public, + mi_simplified_core_ = simplified_core, mi_docs_ = docs, mi_top_env_ = top_env, - mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt - -- with specially when the file is read - mi_self_recomp_info_ = self_recomp_info, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash, - mi_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, - mi_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, - mi_fix_fn = mkIfaceFixCache fixities, - mi_hash_fn = mkIfaceHashCache decls - }}) + mi_self_recomp_ = self_recomp, + -- placeholder because this is dealt + -- with specially when the file is read + mi_ext_fields_ = emptyExtensibleFields, + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + }) + +instance Binary IfaceModInfo where + put_ bh (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) = do + put_ bh mod + put_ bh sig_of + put_ bh hsc_src + get bh = do + mod <- get bh + sig_of <- get bh + hsc_src <- get bh + return (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) + + +instance Binary (IfacePublic_ 'ModIfaceFinal) where + put_ bh (IfacePublic { mi_exports_ = exports + , mi_decls_ = decls + , mi_fixities_ = fixities + , mi_warns_ = warns + , mi_anns_ = anns + , mi_defaults_ = defaults + , mi_insts_ = insts + , mi_fam_insts_ = fam_insts + , mi_rules_ = rules + , mi_trust_ = trust + , mi_trust_pkg_ = trust_pkg + , mi_complete_matches_ = complete_matches + , mi_abi_hashes_ = abi_hashes + }) = do + + lazyPut bh exports + lazyPut bh decls + lazyPut bh fixities + lazyPut bh warns + lazyPut bh anns + lazyPut bh defaults + lazyPut bh insts + lazyPut bh fam_insts + lazyPut bh rules + lazyPut bh trust + lazyPut bh trust_pkg + lazyPut bh complete_matches + lazyPut bh abi_hashes + + get bh = do + exports <- lazyGet bh + decls <- lazyGet bh + fixities <- lazyGet bh + warns <- lazyGet bh + anns <- lazyGet bh + defaults <- lazyGet bh + insts <- lazyGet bh + fam_insts <- lazyGet bh + rules <- lazyGet bh + trust <- lazyGet bh + trust_pkg <- lazyGet bh + complete_matches <- lazyGet bh + abi_hashes <- lazyGet bh + return (mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes) + +instance Binary IfaceAbiHashes where + put_ bh (IfaceAbiHashes { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = orphan + , mi_abi_finsts = hasFamInsts + , mi_abi_exp_hash = exp_hash + , mi_abi_orphan_hash = orphan_hash + }) = do + put_ bh mod_hash + put_ bh orphan + put_ bh hasFamInsts + put_ bh exp_hash + put_ bh orphan_hash + get bh = do + mod_hash <- get bh + orphan <- get bh + hasFamInsts <- get bh + exp_hash <- get bh + orphan_hash <- get bh + return $ IfaceAbiHashes { + mi_abi_mod_hash = mod_hash, + mi_abi_orphan = orphan, + mi_abi_finsts = hasFamInsts, + mi_abi_exp_hash = exp_hash, + mi_abi_orphan_hash = orphan_hash + } + +instance Binary IfaceSimplifiedCore where + put_ bh (IfaceSimplifiedCore eds fs) = do + put_ bh eds + put_ bh fs + + get bh = do + eds <- get bh + fs <- get bh + return (IfaceSimplifiedCore eds fs) emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface - { mi_module_ = mod, - mi_sig_of_ = Nothing, - mi_hsc_src_ = HsSrcFile, + { mi_mod_info_ = emptyIfaceModInfo mod, + mi_iface_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_exports_ = [], - mi_fixities_ = [], - mi_warns_ = IfWarnSome [] [], - mi_anns_ = [], - mi_defaults_ = [], - mi_insts_ = [], - mi_fam_insts_ = [], - mi_rules_ = [], - mi_decls_ = [], - mi_extra_decls_ = Nothing, - mi_foreign_ = emptyIfaceForeign, + mi_public_ = emptyPublicModIface (), + mi_simplified_core_ = Nothing, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_trust_ = noIfaceTrustInfo, - mi_trust_pkg_ = False, - mi_complete_matches_ = [], mi_docs_ = Nothing, - mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields, - mi_self_recomp_info_ = Nothing + mi_self_recomp_ = Nothing, + mi_ext_fields_ = emptyExtensibleFields + } +emptyIfaceModInfo :: Module -> IfaceModInfo +emptyIfaceModInfo mod = IfaceModInfo + { mi_mod_info_module = mod + , mi_mod_info_sig_of = Nothing + , mi_mod_info_hsc_src = HsSrcFile + } + + +emptyPublicModIface :: IfaceAbiHashesExts phase -> IfacePublic_ phase +emptyPublicModIface abi_hashes = IfacePublic + { mi_exports_ = [] + , mi_decls_ = [] + , mi_fixities_ = [] + , mi_warns_ = IfWarnSome [] [] + , mi_anns_ = [] + , mi_defaults_ = [] + , mi_insts_ = [] + , mi_fam_insts_ = [] + , mi_rules_ = [] + , mi_abi_hashes_ = abi_hashes + , mi_trust_ = noIfaceTrustInfo + , mi_trust_pkg_ = False + , mi_caches_ = emptyModIfaceCache + , mi_complete_matches_ = [] + } + +emptyModIfaceCache :: IfaceCache +emptyModIfaceCache = IfaceCache { + mi_cache_decl_warn_fn = emptyIfaceWarnCache, + mi_cache_export_warn_fn = emptyIfaceWarnCache, + mi_cache_fix_fn = emptyIfaceFixCache, + mi_cache_hash_fn = emptyIfaceHashCache +} + +emptyIfaceBackend :: IfaceAbiHashes +emptyIfaceBackend = IfaceAbiHashes + { mi_abi_mod_hash = fingerprint0, + mi_abi_orphan = False, + mi_abi_finsts = False, + mi_abi_exp_hash = fingerprint0, + mi_abi_orphan_hash = fingerprint0 + } + emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls_ = [] - , mi_self_recomp_info_ = Nothing + { mi_public_ = emptyPublicModIface emptyIfaceBackend , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing - , mi_final_exts_ = ModIfaceBackend - { mi_mod_hash = fingerprint0, - mi_iface_hash = fingerprint0, - mi_orphan = False, - mi_finsts = False, - mi_exp_hash = fingerprint0, - mi_orphan_hash = fingerprint0, - mi_decl_warn_fn = emptyIfaceWarnCache, - mi_export_warn_fn = emptyIfaceWarnCache, - mi_fix_fn = emptyIfaceFixCache, - mi_hash_fn = emptyIfaceHashCache } } + } + -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface' mkIfaceHashCache :: [(Fingerprint,IfaceDecl)] @@ -657,11 +829,11 @@ emptyIfaceHashCache _occ = Nothing -- ModIface is completely forced since it will live in memory for a long time. -- If forcing it uses a lot of memory, then store less things in ModIface. -instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) +instance ( NFData (IfaceAbiHashesExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) - = rnf a1 + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = (a1 :: IfaceBinHandle phase) `seq` rnf a2 `seq` rnf a3 `seq` rnf a4 @@ -671,24 +843,27 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 - `seq` rnf a11 - `seq` rnf a12 - `seq` rnf a13 - `seq` rnf a14 - `seq` rnf a15 - `seq` rnf a16 - `seq` rnf a17 - `seq` rnf a18 - `seq` rnf a19 - `seq` rnf a20 - `seq` rnf a21 - `seq` rnf a22 - -- IfaceBinHandle - `seq` (a23 :: IfaceBinHandle phase) - `seq` rnf a24 - -instance NFData ModIfaceBackend where - rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + +instance NFData IfaceModInfo where + rnf (IfaceModInfo a1 a2 a3) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + + +instance NFData IfaceSimplifiedCore where + rnf (IfaceSimplifiedCore eds fs) = rnf eds `seq` rnf fs + +instance NFData IfaceAbiHashes where + rnf (IfaceAbiHashes a1 a2 a3 a4 a5) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + +instance (NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) where + rnf (IfacePublic a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = rnf a1 `seq` rnf a2 `seq` rnf a3 @@ -699,6 +874,18 @@ instance NFData ModIfaceBackend where `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +instance NFData IfaceCache where + rnf (IfaceCache a1 a2 a3 a4) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + forceModIface :: ModIface -> IO () @@ -745,28 +932,38 @@ to serialise the 'ModIface' to disk again. -- | Given a 'PartialModIface', turn it into a 'ModIface' by completing -- missing fields. completePartialModIface :: PartialModIface + -> Fingerprint -> [(Fingerprint, IfaceDecl)] - -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - -> ModIfaceBackend + -> Maybe IfaceSimplifiedCore + -> IfaceAbiHashes + -> IfaceCache -> ModIface -completePartialModIface partial decls extra_decls final_exts = partial - { mi_decls_ = decls - , mi_extra_decls_ = extra_decls - , mi_final_exts_ = final_exts +completePartialModIface partial iface_hash decls extra_decls final_exts cache = partial + { mi_public_ = completePublicModIface decls final_exts cache (mi_public_ partial) + , mi_simplified_core_ = extra_decls , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_iface_hash_ = iface_hash } + where -set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase -set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } - -set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase -set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } +-- | Given a 'PartialIfacePublic', turn it into an 'IfacePublic' by completing +-- missing fields. +completePublicModIface :: [(Fingerprint, IfaceDecl)] + -> IfaceAbiHashes + -> IfaceCache + -> PartialIfacePublic + -> IfacePublic +completePublicModIface decls abi_hashes cache partial = partial + { mi_decls_ = decls + , mi_abi_hashes_ = abi_hashes + , mi_caches_ = cache + } -set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase -set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } +set_mi_mod_info :: IfaceModInfo -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info val iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = val } -set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase -set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } +set_mi_self_recomp :: Maybe IfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -774,59 +971,100 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } +set_mi_public :: (IfacePublic_ phase -> IfacePublic_ phase) -> ModIface_ phase -> ModIface_ phase +set_mi_public f iface = clear_mi_hi_bytes $ iface { mi_public_ = f (mi_public_ iface) } + +set_mi_simplified_core :: Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase +set_mi_simplified_core val iface = clear_mi_hi_bytes $ iface { mi_simplified_core_ = val } + +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +{- Settings for mi_public interface fields -} + set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase -set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } +set_mi_exports val = set_mi_public (\iface -> iface { mi_exports_ = val }) set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase -set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } +set_mi_fixities val = set_mi_public (\iface -> iface { mi_fixities_ = val }) set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase -set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } +set_mi_warns val = set_mi_public (\iface -> iface { mi_warns_ = val }) set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase -set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } +set_mi_anns val = set_mi_public (\iface -> iface { mi_anns_ = val }) set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase -set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } +set_mi_insts val = set_mi_public (\iface -> iface { mi_insts_ = val }) set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase -set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } +set_mi_fam_insts val = set_mi_public (\iface -> iface { mi_fam_insts_ = val }) set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase -set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } +set_mi_rules val = set_mi_public (\iface -> iface { mi_rules_ = val }) set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase -set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } +set_mi_decls val = set_mi_public (\iface -> iface { mi_decls_ = val }) set_mi_defaults :: [IfaceDefault] -> ModIface_ phase -> ModIface_ phase -set_mi_defaults val iface = clear_mi_hi_bytes $ iface { mi_defaults_ = val } - -set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase -set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } - -set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase -set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } - -set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase -set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } +set_mi_defaults val = set_mi_public (\iface -> iface { mi_defaults_ = val }) set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase -set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } +set_mi_trust val = set_mi_public (\iface -> iface { mi_trust_ = val }) set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase -set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } +set_mi_trust_pkg val = set_mi_public (\iface -> iface { mi_trust_pkg_ = val }) set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase -set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } +set_mi_complete_matches val = set_mi_public (\iface -> iface { mi_complete_matches_ = val }) + +set_mi_abi_hashes :: IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_abi_hashes val = set_mi_public (\iface -> iface { mi_abi_hashes_ = val }) + +{- Setters for mi_caches interface fields -} + +set_mi_decl_warn_fn :: (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_decl_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_decl_warn_fn = val } }) + +set_mi_export_warn_fn :: (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_export_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_export_warn_fn = val } }) + +set_mi_fix_fn :: (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase +set_mi_fix_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_fix_fn = val } }) + +set_mi_hash_fn :: (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase +set_mi_hash_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_hash_fn = val } }) + +set_mi_caches :: IfaceCache -> ModIface_ phase -> ModIface_ phase +set_mi_caches val = set_mi_public (\iface -> iface { mi_caches_ = val }) + +{- + +-} + +{- Setters for mi_mod_info interface fields -} + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val = set_mi_mod_info_field (\info -> info { mi_mod_info_module = val }) + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val = set_mi_mod_info_field (\info -> info { mi_mod_info_sig_of = val }) + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val = set_mi_mod_info_field (\info -> info { mi_mod_info_hsc_src = val }) + +-- | Helper function for setting fields in mi_mod_info_ +set_mi_mod_info_field :: (IfaceModInfo -> IfaceModInfo) -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info_field f iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = f (mi_mod_info_ iface) } -set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase -set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } -set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase -set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } -set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase -set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } -- | Invalidate any byte array buffer we might have. clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase @@ -887,18 +1125,20 @@ However, with the pragma, the correct core is generated: -- See Note [Inline Pattern synonym of ModIface] for why we have all these -- inline pragmas. -{-# INLINE ModIface #-} +{-# INLINE mi_mod_info #-} +{-# INLINE mi_iface_hash #-} {-# INLINE mi_module #-} {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} +{-# INLINE mi_public #-} {-# INLINE mi_exports #-} {-# INLINE mi_fixities #-} {-# INLINE mi_warns #-} {-# INLINE mi_anns #-} {-# INLINE mi_decls #-} -{-# INLINE mi_extra_decls #-} -{-# INLINE mi_foreign #-} +{-# INLINE mi_simplified_core #-} +{-# INLINE mi_defaults #-} {-# INLINE mi_top_env #-} {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} @@ -907,32 +1147,63 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} {-# INLINE mi_docs #-} -{-# INLINE mi_final_exts #-} +{-# INLINE mi_abi_hashes #-} {-# INLINE mi_ext_fields #-} {-# INLINE mi_hi_bytes #-} +{-# INLINE mi_self_recomp_info #-} +{-# INLINE mi_fix_fn #-} +{-# INLINE mi_hash_fn #-} +{-# INLINE mi_decl_warn_fn #-} +{-# INLINE mi_export_warn_fn #-} +{-# INLINE ModIface #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> - [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> - [IfaceAnnotation] -> [IfaceDeclExts phase] -> - Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> + IfaceModInfo + -> Module + -> Maybe Module + -> HscSource + -> Fingerprint + -> Dependencies + -> IfacePublic_ phase + -> [IfaceExport] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDeclExts phase] + -> Maybe IfaceSimplifiedCore + -> [IfaceDefault] + -> IfaceTopEnv + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> Maybe Docs + -> IfaceAbiHashesExts phase + -> ExtensibleFields + -> IfaceBinHandle phase + -> Maybe IfaceSelfRecomp + -> (OccName -> Maybe Fixity) + -> (OccName -> Maybe (OccName, Fingerprint)) + -> (OccName -> Maybe (WarningTxt GhcRn)) + -> (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase pattern ModIface - { mi_module + { mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_defaults , mi_top_env , mi_insts @@ -942,33 +1213,45 @@ pattern ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_hash_fn + , mi_decl_warn_fn + , mi_export_warn_fn } <- PrivateModIface - { mi_module_ = mi_module - , mi_sig_of_ = mi_sig_of - , mi_hsc_src_ = mi_hsc_src + { mi_mod_info_ = mi_mod_info at IfaceModInfo { mi_mod_info_module = mi_module + , mi_mod_info_sig_of = mi_sig_of + , mi_mod_info_hsc_src = mi_hsc_src } + , mi_iface_hash_ = mi_iface_hash , mi_deps_ = mi_deps - , mi_exports_ = mi_exports - , mi_fixities_ = mi_fixities - , mi_warns_ = mi_warns - , mi_anns_ = mi_anns - , mi_decls_ = mi_decls - , mi_extra_decls_ = mi_extra_decls - , mi_foreign_ = mi_foreign - , mi_defaults_ = mi_defaults - , mi_top_env_ = mi_top_env - , mi_insts_ = mi_insts - , mi_fam_insts_ = mi_fam_insts - , mi_rules_ = mi_rules - , mi_trust_ = mi_trust - , mi_trust_pkg_ = mi_trust_pkg - , mi_complete_matches_ = mi_complete_matches + , mi_public_ = mi_public at IfacePublic { + mi_exports_ = mi_exports + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_defaults_ = mi_defaults + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mi_decl_warn_fn, + mi_cache_export_warn_fn = mi_export_warn_fn, + mi_cache_fix_fn = mi_fix_fn, + mi_cache_hash_fn = mi_hash_fn + } + , mi_abi_hashes_ = mi_abi_hashes + } , mi_docs_ = mi_docs - , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields , mi_hi_bytes_ = mi_hi_bytes - , mi_self_recomp_info_ = mi_self_recomp_info + , mi_self_recomp_ = mi_self_recomp_info + , mi_simplified_core_ = mi_simplified_core + , mi_top_env_ = mi_top_env } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -107,6 +107,9 @@ module GHC.Utils.Binary simpleBindingNameReader, FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, BinArray, + + -- * FingerprintWithValue + FingerprintWithValue(..) ) where import GHC.Prelude @@ -2088,3 +2091,39 @@ source location as part of a larger structure. instance (Binary v) => Binary (IntMap v) where put_ bh m = put_ bh (IntMap.toAscList m) get bh = IntMap.fromAscList <$> get bh + + +{- +Note [FingerprintWithValue] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +FingerprintWithValue is a wrapper which allows us to store a fingerprint and +optionally the value which was used to create the fingerprint. + +This is useful for storing information in interface files, where we want to +store the fingerprint of the interface file, but also the value which was used +to create the fingerprint (e.g. the DynFlags). + +The wrapper is useful to ensure that the fingerprint can be read quickly without +having to deserialise the value itself. + +-} + +-- | A wrapper which allows us to store a fingerprint and optionally the value which +-- was used to create the fingerprint. +data FingerprintWithValue a = FingerprintWithValue !Fingerprint (Maybe a) + deriving Functor + +instance Binary a => Binary (FingerprintWithValue a) where + put_ bh (FingerprintWithValue fp val) = do + put_ bh fp + lazyPutMaybe bh val + + get bh = do + fp <- get bh + val <- lazyGetMaybe bh + return $ FingerprintWithValue fp val + +instance NFData a => NFData (FingerprintWithValue a) where + rnf (FingerprintWithValue fp mflags) + = rnf fp `seq` rnf mflags `seq` () \ No newline at end of file ===================================== ghc/Main.hs ===================================== @@ -1133,6 +1133,8 @@ abiHash strs = do mods <- mapM find_it strs + -- MP: loadUserInterface is inefficient here since we will never find a cached + -- interface. computeInterface is probably better. let get_iface modl = loadUserInterface NotBoot (text "abiHash") modl ifaces <- initIfaceCheck (text "abiHash") hsc_env $ mapM get_iface mods @@ -1140,7 +1142,7 @@ abiHash strs = do put_ bh hiVersion -- package hashes change when the compiler version changes (for now) -- see #5328 - mapM_ (put_ bh . mi_mod_hash . mi_final_exts) ifaces + mapM_ (put_ bh . mi_mod_hash) ifaces f <- fingerprintBinMem bh putStrLn (showPpr dflags f) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0203403cb4ce73d86206b633c3dffb997f8061f6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0203403cb4ce73d86206b633c3dffb997f8061f6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/19634ee8/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 11:18:10 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 14 Mar 2025 07:18:10 -0400 Subject: [Git][ghc/ghc][wip/romes/better-main] driver: Move DynFlags consistency fixes off Main Message-ID: <67d41072a78_1f51beb5c764503d0@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/better-main at Glasgow Haskell Compiler / GHC Commits: 4ec85a8f by Rodrigo Mesquita at 2025-03-14T11:17:53+00:00 driver: Move DynFlags consistency fixes off Main These consistency fixes found in Main.hs are required for the proper functioning of the compiler and should live together with all remaining fixes in `makeDynFlagsConsistent`. This is especially relevant to GHC applications that shouldn't have to copy/fix themselves possibly inconsistent DynFlags. Additionally, outputs information when verbosity is high about these consistency fixes that were previously quiet, adds information to the Note on consistency of DynFlags, and improves one of the fixes that incorrectly used `dynNow`. - - - - - 8 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - ghc/GHCi/UI.hs - ghc/Main.hs - utils/check-exact/Parsers.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -918,7 +918,7 @@ parseDynamicFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) parseDynamicFlags logger dflags cmdline = do - (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine dflags cmdline + (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine logger dflags cmdline -- flags that have just been read are used by the logger when loading package -- env (this is checked by T16318) let logger1 = setLogFlags logger (initLogFlags dflags1) @@ -1015,11 +1015,13 @@ normalise_hyp fp checkNewDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags checkNewDynFlags logger dflags = do -- See Note [DynFlags consistency] - let (dflags', warnings) = makeDynFlagsConsistent dflags + let (dflags', warnings, infoverb) = makeDynFlagsConsistent dflags let diag_opts = initDiagOpts dflags print_config = initPrintConfig dflags liftIO $ printOrThrowDiagnostics logger print_config diag_opts $ fmap GhcDriverMessage $ warnsToMessages diag_opts warnings + when (logVerbAtLeast logger 3) $ + mapM_ (\(L _loc m) -> liftIO $ logInfo logger m) infoverb return dflags' checkNewInteractiveDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -100,8 +100,9 @@ doBackpack [src_filename] = do dflags0 <- getDynFlags let dflags1 = dflags0 let parser_opts1 = initParserOpts dflags1 + logger0 <- getLogger (p_warns, src_opts) <- liftIO $ getOptionsFromFile parser_opts1 (supportedLanguagePragmas dflags1) src_filename - (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma dflags1 src_opts + (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma logger0 dflags1 src_opts modifySession (hscSetFlags dflags) logger <- getLogger -- Get the logger after having set the session flags, -- so that logger options are correctly set. ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -1962,6 +1962,8 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do mgMapM enable_code_gen mg where defaultBackendOf ms = platformDefaultBackend (targetPlatform $ ue_unitFlags (ms_unitid ms) unit_env) + -- FIXME: Strong resemblance and some duplication between this and `makeDynFlagsConsistent`. + -- It would be good to consider how to make these checks more uniform and not duplicated. enable_code_gen :: ModSummary -> IO ModSummary enable_code_gen ms | ModSummary ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -655,10 +655,11 @@ runUnlitPhase hsc_env input_fn output_fn = do getFileArgs :: HscEnv -> FilePath -> IO ((DynFlags, Messages PsMessage, Messages DriverMessage)) getFileArgs hsc_env input_fn = do let dflags0 = hsc_dflags hsc_env + logger = hsc_logger hsc_env parser_opts = initParserOpts dflags0 (warns0, src_opts) <- getOptionsFromFile parser_opts (supportedLanguagePragmas dflags0) input_fn (dflags1, unhandled_flags, warns) - <- parseDynamicFilePragma dflags0 src_opts + <- parseDynamicFilePragma logger dflags0 src_opts checkProcessArgsResult unhandled_flags return (dflags1, warns0, warns) ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -247,6 +247,7 @@ import GHC.Driver.Plugins.External import GHC.Settings.Config import GHC.Core.Unfold import GHC.Driver.CmdLine +import GHC.Utils.Logger import GHC.Utils.Panic import GHC.Utils.Misc import GHC.Utils.Constants (debugIsOn) @@ -265,7 +266,7 @@ import GHC.Data.FastString import GHC.Utils.TmpFs import GHC.Utils.Fingerprint import GHC.Utils.Outputable -import GHC.Utils.Error (emptyDiagOpts) +import GHC.Utils.Error (emptyDiagOpts, logInfo) import GHC.Settings import GHC.CmmToAsm.CFG.Weight import GHC.Core.Opt.CallerCC @@ -806,7 +807,7 @@ updOptLevel n = fst . updOptLevelChanged n -- the parsed 'DynFlags', the left-over arguments, and a list of warnings. -- Throws a 'UsageError' if errors occurred during parsing (such as unknown -- flags or missing arguments). -parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] +parseDynamicFlagsCmdLine :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -816,7 +817,7 @@ parseDynamicFlagsCmdLine = parseDynamicFlagsFull flagsAll True -- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags -- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db). -- Used to parse flags set in a modules pragma. -parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] +parseDynamicFilePragma :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -865,10 +866,11 @@ parseDynamicFlagsFull :: forall m. MonadIO m => [Flag (CmdLineP DynFlags)] -- ^ valid flags to match against -> Bool -- ^ are the arguments from the command line? + -> Logger -- ^ logger -> DynFlags -- ^ current dynamic flags -> [Located String] -- ^ arguments to parse -> m (DynFlags, [Located String], Messages DriverMessage) -parseDynamicFlagsFull activeFlags cmdline dflags0 args = do +parseDynamicFlagsFull activeFlags cmdline logger dflags0 args = do ((leftover, errs, cli_warns), dflags1) <- processCmdLineP activeFlags dflags0 args -- See Note [Handling errors when parsing command-line flags] @@ -884,7 +886,7 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do throwGhcExceptionIO (CmdLineError ("combination not supported: " ++ intercalate "/" (map wayDesc (Set.toAscList theWays)))) - let (dflags3, consistency_warnings) = makeDynFlagsConsistent dflags2 + let (dflags3, consistency_warnings, infoverb) = makeDynFlagsConsistent dflags2 -- Set timer stats & heap size when (enableTimeStats dflags3) $ liftIO enableTimingStats @@ -898,6 +900,9 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do let diag_opts = initDiagOpts dflags3 warns = warnsToMessages diag_opts $ mconcat [consistency_warnings, sh_warns, cli_warns] + when (logVerbAtLeast logger 3) $ + mapM_ (\(L _loc m) -> liftIO $ logInfo logger m) infoverb + return (dflags3, leftover, warns) -- | Check (and potentially disable) any extensions that aren't allowed @@ -3491,12 +3496,35 @@ combination when parsing flags, we also need to check when we update the flags; this is because API clients may parse flags but update the DynFlags afterwords, before finally running code inside a session (see T10052 and #10052). + +Host ways vs Build ways mismatch +-------------------------------- +Many consistency checks aim to fix the situation where the wanted build ways +are not compatible with the ways the compiler is built in. This happens when +using the interpreter, TH, and the runtime linker, where the compiler cannot +load objects compiled for ways not matching its own. + +For instance, a profiled-dynamic object can only be loaded by a +profiled-dynamic compiler (and not any other kind of compiler). + +This incompatibility is traditionally solved in either of two ways: + +(1) Force the "wanted" build ways to match the compiler ways exactly, + guaranteeing they match. + +(2) Force the use of the external interpreter. When interpreting is offloaded + to the external interpreter it no longer matters what are the host compiler ways. + +In the checks and fixes performed by `makeDynFlagsConsistent`, the choice +between the two does not seem uniform. TODO: Make this choice more evident and uniform. -} -- | Resolve any internal inconsistencies in a set of 'DynFlags'. -- Returns the consistent 'DynFlags' as well as a list of warnings --- to report to the user. -makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn]) +-- to report to the user, and a list of verbose info msgs. +-- +-- See Note [DynFlags consistency] +makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn], [Located SDoc]) -- Whenever makeDynFlagsConsistent does anything, it starts over, to -- ensure that a later change doesn't invalidate an earlier check. -- Be careful not to introduce potential loops! @@ -3587,13 +3615,41 @@ makeDynFlagsConsistent dflags | LinkMergedObj <- ghcLink dflags , Nothing <- outputFile dflags - = pgmError "--output must be specified when using --merge-objs" + = pgmError "--output must be specified when using --merge-objs" - | otherwise = (dflags, mempty) + -- When we do ghci, force using dyn ways if the target RTS linker + -- only supports dynamic code + | LinkInMemory <- ghcLink dflags + , sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags + , not (ways dflags `hasWay` WayDyn && gopt Opt_ExternalInterpreter dflags) + = flip loopNoWarn "Forcing dynamic way because target RTS linker only supports dynamic code" $ + -- See checkOptions, -fexternal-interpreter is + -- required when using --interactive with a non-standard + -- way (-prof, -static, or -dynamic). + setGeneralFlag' Opt_ExternalInterpreter $ + addWay' WayDyn dflags + + | ghcLink dflags `elem` [LinkInMemory, NoLink] + , not (gopt Opt_ExternalInterpreter dflags) + , targetWays_ dflags /= hostFullWays + = flip loopNoWarn "Forcing build ways to match the compiler ways because we're using the internal interpreter" $ + let dflags_a = dflags { targetWays_ = hostFullWays } + dflags_b = foldl gopt_set dflags_a + $ concatMap (wayGeneralFlags platform) + hostFullWays + dflags_c = foldl gopt_unset dflags_b + $ concatMap (wayUnsetGeneralFlags platform) + hostFullWays + in dflags_c + + | otherwise = (dflags, mempty, mempty) where loc = mkGeneralSrcSpan (fsLit "when making flags consistent") loop updated_dflags warning = case makeDynFlagsConsistent updated_dflags of - (dflags', ws) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws) + (dflags', ws, is) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws, is) + loopNoWarn updated_dflags doc + = case makeDynFlagsConsistent updated_dflags of + (dflags', ws, is) -> (dflags', ws, L loc (text doc):is) platform = targetPlatform dflags arch = platformArch platform os = platformOS platform ===================================== ghc/GHCi/UI.hs ===================================== @@ -3148,7 +3148,7 @@ newDynFlags interactive_only minus_opts = do logger <- getLogger idflags0 <- GHC.getInteractiveDynFlags - (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine idflags0 lopts + (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine logger idflags0 lopts liftIO $ printOrThrowDiagnostics logger (initPrintConfig idflags1) (initDiagOpts idflags1) (GhcDriverMessage <$> warns) when (not $ null leftovers) (unknownFlagsErr $ map unLoc leftovers) @@ -3161,7 +3161,7 @@ newDynFlags interactive_only minus_opts = do dflags0 <- getDynFlags when (not interactive_only) $ do - (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine dflags0 lopts + (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine logger dflags0 lopts must_reload <- GHC.setProgramDynFlags dflags1 -- if the package flags changed, reset the context and link ===================================== ghc/Main.hs ===================================== @@ -224,41 +224,9 @@ main' postLoadMode units dflags0 args flagWarnings = do -- The rest of the arguments are "dynamic" -- Leftover ones are presumably files - (dflags3', fileish_args, dynamicFlagWarnings) <- + (dflags4, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags logger2 dflags2 args' - -- When we do ghci, force using dyn ways if the target RTS linker - -- only supports dynamic code - let dflags3 - | LinkInMemory <- link, - sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags3' - = setDynamicNow $ - -- See checkOptions below, -fexternal-interpreter is - -- required when using --interactive with a non-standard - -- way (-prof, -static, or -dynamic). - setGeneralFlag' Opt_ExternalInterpreter $ - -- Use .o for dynamic object, otherwise it gets dropped - -- with "Warning: ignoring unrecognised input", see - -- objish_suffixes - dflags3' { dynObjectSuf_ = objectSuf dflags3' } - | otherwise - = dflags3' - - let dflags4 = if backendNeedsFullWays bcknd && - not (gopt Opt_ExternalInterpreter dflags3) - then - let platform = targetPlatform dflags3 - dflags3a = dflags3 { targetWays_ = hostFullWays } - dflags3b = foldl gopt_set dflags3a - $ concatMap (wayGeneralFlags platform) - hostFullWays - dflags3c = foldl gopt_unset dflags3b - $ concatMap (wayUnsetGeneralFlags platform) - hostFullWays - in dflags3c - else - dflags3 - let logger4 = setLogFlags logger2 (initLogFlags dflags4) GHC.prettyPrintGhcErrors logger4 $ do @@ -804,7 +772,7 @@ initMulti unitArgsFiles = do dynFlagsAndSrcs <- forM unitArgsFiles $ \f -> do when (verbosity initial_dflags > 2) (liftIO $ print f) args <- liftIO $ expandResponse [f] - (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine initial_dflags (map (mkGeneralLocated f) (removeRTS args)) + (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine logger initial_dflags (map (mkGeneralLocated f) (removeRTS args)) handleSourceError (\e -> do GHC.printException e liftIO $ exitWith (ExitFailure 1)) $ do ===================================== utils/check-exact/Parsers.hs ===================================== @@ -348,12 +348,14 @@ initDynFlags file = do -- Based on GHC backpack driver doBackPack dflags0 <- GHC.getSessionDynFlags let parser_opts0 = GHC.initParserOpts dflags0 + logger <- GHC.getLogger (_, src_opts) <- GHC.liftIO $ GHC.getOptionsFromFile parser_opts0 (GHC.supportedLanguagePragmas dflags0) file - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 src_opts + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 src_opts -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 @@ -375,13 +377,15 @@ initDynFlagsPure fp s = do -- as long as `parseDynamicFilePragma` is impure there seems to be -- no reason to use it. dflags0 <- GHC.getSessionDynFlags + logger <- GHC.getLogger let parser_opts0 = GHC.initParserOpts dflags0 let (_, pragmaInfo) = GHC.getOptions parser_opts0 (GHC.supportedLanguagePragmas dflags0) (GHC.stringToStringBuffer $ s) fp - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 pragmaInfo + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 pragmaInfo -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4ec85a8fd2e0b2a62844cc1d90db06e9dc1e197c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4ec85a8fd2e0b2a62844cc1d90db06e9dc1e197c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/54317d98/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 11:18:48 2025 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 14 Mar 2025 07:18:48 -0400 Subject: [Git][ghc/ghc][wip/romes/better-main-2] 4 commits: driver: Move DynFlags consistency fixes off Main Message-ID: <67d41097c7ec2_1f51beb68f145091b@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/better-main-2 at Glasgow Haskell Compiler / GHC Commits: 4ec85a8f by Rodrigo Mesquita at 2025-03-14T11:17:53+00:00 driver: Move DynFlags consistency fixes off Main These consistency fixes found in Main.hs are required for the proper functioning of the compiler and should live together with all remaining fixes in `makeDynFlagsConsistent`. This is especially relevant to GHC applications that shouldn't have to copy/fix themselves possibly inconsistent DynFlags. Additionally, outputs information when verbosity is high about these consistency fixes that were previously quiet, adds information to the Note on consistency of DynFlags, and improves one of the fixes that incorrectly used `dynNow`. - - - - - 93d2d600 by Rodrigo Mesquita at 2025-03-14T11:18:13+00:00 driver: Split Session functions out of Main This commit moves out functions that help in creating and validating a GHC session from Main into the ghc library where they can be used by other GHC applications. In particular: - Move `Mode` types and functions (referring to the mode GHC is running on) to `GHC.Driver.Session.Mode` - Move `checkOptions` and aux functions, which validates GHC DynFlags based on the mode, to `GHC.Driver.Session.Lint` - Moves `initMulti` and aux functions, which initializes a multi-unit session, into `GHC.Driver.Session.Units`. - - - - - cc3af792 by Rodrigo Mesquita at 2025-03-14T11:18:14+00:00 Add docs to obtainTermFromId - - - - - 710ba89f by Rodrigo Mesquita at 2025-03-14T11:18:14+00:00 Move logic to find and set Breakpoint to GHC Breakpoints are uniquely identified by a module and an index unique within that module. `ModBreaks` of a Module contains arrays mapping from this unique breakpoint index to information about each breakpoint. For instance, `modBreaks_locs` stores the `SrcSpan` for each breakpoint. To find a breakpoint using the line number you need to go through all breakpoints in the array for a given module and look at the line and column stored in the `SrcSpan`s. Similarly for columns and finding breakpoints by name. This logic previously lived within the `GHCi` application sources, however, it is common to any GHC applications wanting to set breakpoints, like the upcoming `ghc-debugger`. This commit moves this logic for finding and setting breakpoints to the GHC library so it can be used by both `ghci` and `ghc-debugger`. - - - - - 16 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - + compiler/GHC/Driver/Session/Lint.hs - + compiler/GHC/Driver/Session/Mode.hs - + compiler/GHC/Driver/Session/Units.hs - + compiler/GHC/Runtime/Debugger/Breakpoints.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/ghc.cabal.in - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - ghc/Main.hs - utils/check-exact/Parsers.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -918,7 +918,7 @@ parseDynamicFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) parseDynamicFlags logger dflags cmdline = do - (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine dflags cmdline + (dflags1, leftovers, warns) <- parseDynamicFlagsCmdLine logger dflags cmdline -- flags that have just been read are used by the logger when loading package -- env (this is checked by T16318) let logger1 = setLogFlags logger (initLogFlags dflags1) @@ -1015,11 +1015,13 @@ normalise_hyp fp checkNewDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags checkNewDynFlags logger dflags = do -- See Note [DynFlags consistency] - let (dflags', warnings) = makeDynFlagsConsistent dflags + let (dflags', warnings, infoverb) = makeDynFlagsConsistent dflags let diag_opts = initDiagOpts dflags print_config = initPrintConfig dflags liftIO $ printOrThrowDiagnostics logger print_config diag_opts $ fmap GhcDriverMessage $ warnsToMessages diag_opts warnings + when (logVerbAtLeast logger 3) $ + mapM_ (\(L _loc m) -> liftIO $ logInfo logger m) infoverb return dflags' checkNewInteractiveDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags @@ -1846,7 +1848,11 @@ obtainTermFromVal :: GhcMonad m => Int -> Bool -> Type -> a -> m Term obtainTermFromVal bound force ty a = withSession $ \hsc_env -> liftIO $ GHC.Runtime.Eval.obtainTermFromVal hsc_env bound force ty a -obtainTermFromId :: GhcMonad m => Int -> Bool -> Id -> m Term +obtainTermFromId :: GhcMonad m + => Int -- ^ How many times to recurse for subterms + -> Bool -- ^ Whether to force the expression + -> Id + -> m Term obtainTermFromId bound force id = withSession $ \hsc_env -> liftIO $ GHC.Runtime.Eval.obtainTermFromId hsc_env bound force id ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -100,8 +100,9 @@ doBackpack [src_filename] = do dflags0 <- getDynFlags let dflags1 = dflags0 let parser_opts1 = initParserOpts dflags1 + logger0 <- getLogger (p_warns, src_opts) <- liftIO $ getOptionsFromFile parser_opts1 (supportedLanguagePragmas dflags1) src_filename - (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma dflags1 src_opts + (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma logger0 dflags1 src_opts modifySession (hscSetFlags dflags) logger <- getLogger -- Get the logger after having set the session flags, -- so that logger options are correctly set. ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -1962,6 +1962,8 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do mgMapM enable_code_gen mg where defaultBackendOf ms = platformDefaultBackend (targetPlatform $ ue_unitFlags (ms_unitid ms) unit_env) + -- FIXME: Strong resemblance and some duplication between this and `makeDynFlagsConsistent`. + -- It would be good to consider how to make these checks more uniform and not duplicated. enable_code_gen :: ModSummary -> IO ModSummary enable_code_gen ms | ModSummary ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -655,10 +655,11 @@ runUnlitPhase hsc_env input_fn output_fn = do getFileArgs :: HscEnv -> FilePath -> IO ((DynFlags, Messages PsMessage, Messages DriverMessage)) getFileArgs hsc_env input_fn = do let dflags0 = hsc_dflags hsc_env + logger = hsc_logger hsc_env parser_opts = initParserOpts dflags0 (warns0, src_opts) <- getOptionsFromFile parser_opts (supportedLanguagePragmas dflags0) input_fn (dflags1, unhandled_flags, warns) - <- parseDynamicFilePragma dflags0 src_opts + <- parseDynamicFilePragma logger dflags0 src_opts checkProcessArgsResult unhandled_flags return (dflags1, warns0, warns) ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -247,6 +247,7 @@ import GHC.Driver.Plugins.External import GHC.Settings.Config import GHC.Core.Unfold import GHC.Driver.CmdLine +import GHC.Utils.Logger import GHC.Utils.Panic import GHC.Utils.Misc import GHC.Utils.Constants (debugIsOn) @@ -265,7 +266,7 @@ import GHC.Data.FastString import GHC.Utils.TmpFs import GHC.Utils.Fingerprint import GHC.Utils.Outputable -import GHC.Utils.Error (emptyDiagOpts) +import GHC.Utils.Error (emptyDiagOpts, logInfo) import GHC.Settings import GHC.CmmToAsm.CFG.Weight import GHC.Core.Opt.CallerCC @@ -806,7 +807,7 @@ updOptLevel n = fst . updOptLevelChanged n -- the parsed 'DynFlags', the left-over arguments, and a list of warnings. -- Throws a 'UsageError' if errors occurred during parsing (such as unknown -- flags or missing arguments). -parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] +parseDynamicFlagsCmdLine :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -816,7 +817,7 @@ parseDynamicFlagsCmdLine = parseDynamicFlagsFull flagsAll True -- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags -- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db). -- Used to parse flags set in a modules pragma. -parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] +parseDynamicFilePragma :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], Messages DriverMessage) -- ^ Updated 'DynFlags', left-over arguments, and -- list of warnings. @@ -865,10 +866,11 @@ parseDynamicFlagsFull :: forall m. MonadIO m => [Flag (CmdLineP DynFlags)] -- ^ valid flags to match against -> Bool -- ^ are the arguments from the command line? + -> Logger -- ^ logger -> DynFlags -- ^ current dynamic flags -> [Located String] -- ^ arguments to parse -> m (DynFlags, [Located String], Messages DriverMessage) -parseDynamicFlagsFull activeFlags cmdline dflags0 args = do +parseDynamicFlagsFull activeFlags cmdline logger dflags0 args = do ((leftover, errs, cli_warns), dflags1) <- processCmdLineP activeFlags dflags0 args -- See Note [Handling errors when parsing command-line flags] @@ -884,7 +886,7 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do throwGhcExceptionIO (CmdLineError ("combination not supported: " ++ intercalate "/" (map wayDesc (Set.toAscList theWays)))) - let (dflags3, consistency_warnings) = makeDynFlagsConsistent dflags2 + let (dflags3, consistency_warnings, infoverb) = makeDynFlagsConsistent dflags2 -- Set timer stats & heap size when (enableTimeStats dflags3) $ liftIO enableTimingStats @@ -898,6 +900,9 @@ parseDynamicFlagsFull activeFlags cmdline dflags0 args = do let diag_opts = initDiagOpts dflags3 warns = warnsToMessages diag_opts $ mconcat [consistency_warnings, sh_warns, cli_warns] + when (logVerbAtLeast logger 3) $ + mapM_ (\(L _loc m) -> liftIO $ logInfo logger m) infoverb + return (dflags3, leftover, warns) -- | Check (and potentially disable) any extensions that aren't allowed @@ -3491,12 +3496,35 @@ combination when parsing flags, we also need to check when we update the flags; this is because API clients may parse flags but update the DynFlags afterwords, before finally running code inside a session (see T10052 and #10052). + +Host ways vs Build ways mismatch +-------------------------------- +Many consistency checks aim to fix the situation where the wanted build ways +are not compatible with the ways the compiler is built in. This happens when +using the interpreter, TH, and the runtime linker, where the compiler cannot +load objects compiled for ways not matching its own. + +For instance, a profiled-dynamic object can only be loaded by a +profiled-dynamic compiler (and not any other kind of compiler). + +This incompatibility is traditionally solved in either of two ways: + +(1) Force the "wanted" build ways to match the compiler ways exactly, + guaranteeing they match. + +(2) Force the use of the external interpreter. When interpreting is offloaded + to the external interpreter it no longer matters what are the host compiler ways. + +In the checks and fixes performed by `makeDynFlagsConsistent`, the choice +between the two does not seem uniform. TODO: Make this choice more evident and uniform. -} -- | Resolve any internal inconsistencies in a set of 'DynFlags'. -- Returns the consistent 'DynFlags' as well as a list of warnings --- to report to the user. -makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn]) +-- to report to the user, and a list of verbose info msgs. +-- +-- See Note [DynFlags consistency] +makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Warn], [Located SDoc]) -- Whenever makeDynFlagsConsistent does anything, it starts over, to -- ensure that a later change doesn't invalidate an earlier check. -- Be careful not to introduce potential loops! @@ -3587,13 +3615,41 @@ makeDynFlagsConsistent dflags | LinkMergedObj <- ghcLink dflags , Nothing <- outputFile dflags - = pgmError "--output must be specified when using --merge-objs" + = pgmError "--output must be specified when using --merge-objs" - | otherwise = (dflags, mempty) + -- When we do ghci, force using dyn ways if the target RTS linker + -- only supports dynamic code + | LinkInMemory <- ghcLink dflags + , sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags + , not (ways dflags `hasWay` WayDyn && gopt Opt_ExternalInterpreter dflags) + = flip loopNoWarn "Forcing dynamic way because target RTS linker only supports dynamic code" $ + -- See checkOptions, -fexternal-interpreter is + -- required when using --interactive with a non-standard + -- way (-prof, -static, or -dynamic). + setGeneralFlag' Opt_ExternalInterpreter $ + addWay' WayDyn dflags + + | ghcLink dflags `elem` [LinkInMemory, NoLink] + , not (gopt Opt_ExternalInterpreter dflags) + , targetWays_ dflags /= hostFullWays + = flip loopNoWarn "Forcing build ways to match the compiler ways because we're using the internal interpreter" $ + let dflags_a = dflags { targetWays_ = hostFullWays } + dflags_b = foldl gopt_set dflags_a + $ concatMap (wayGeneralFlags platform) + hostFullWays + dflags_c = foldl gopt_unset dflags_b + $ concatMap (wayUnsetGeneralFlags platform) + hostFullWays + in dflags_c + + | otherwise = (dflags, mempty, mempty) where loc = mkGeneralSrcSpan (fsLit "when making flags consistent") loop updated_dflags warning = case makeDynFlagsConsistent updated_dflags of - (dflags', ws) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws) + (dflags', ws, is) -> (dflags', L loc (DriverInconsistentDynFlags warning) : ws, is) + loopNoWarn updated_dflags doc + = case makeDynFlagsConsistent updated_dflags of + (dflags', ws, is) -> (dflags', ws, L loc (text doc):is) platform = targetPlatform dflags arch = platformArch platform os = platformOS platform ===================================== compiler/GHC/Driver/Session/Lint.hs ===================================== @@ -0,0 +1,124 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NondecreasingIndentation #-} +{-# LANGUAGE TupleSections #-} +module GHC.Driver.Session.Lint (checkOptions) where + +import GHC.Driver.Backend +import GHC.Driver.Phases +import GHC.Driver.Session +import GHC.Platform.Ways + +import GHC.Utils.Misc +import GHC.Utils.Panic + +import GHC.Data.Maybe + +import System.IO +import Control.Monad +import qualified Data.Set as Set +import Prelude + +import GHC.Driver.Session.Mode + +-- ----------------------------------------------------------------------------- +-- Option sanity checks + +-- | Ensure sanity of options. +-- +-- Throws 'UsageError' or 'CmdLineError' if not. +checkOptions :: PostLoadMode -> DynFlags -> [(String,Maybe Phase)] -> [String] -> [String] -> IO () + -- Final sanity checking before kicking off a compilation (pipeline). +checkOptions mode dflags srcs objs units = do + -- Complain about any unknown flags + let unknown_opts = [ f | (f@('-':_), _) <- srcs ] + when (notNull unknown_opts) (unknownFlagsErr unknown_opts) + + when (not (Set.null (rtsWays (ways dflags))) + && isInterpretiveMode mode) $ + hPutStrLn stderr ("Warning: -debug, -threaded and -ticky are ignored by GHCi") + + -- -prof and --interactive are not a good combination + when ((fullWays (ways dflags) /= hostFullWays) + && isInterpretiveMode mode + && not (gopt Opt_ExternalInterpreter dflags)) $ + do throwGhcException (UsageError + "-fexternal-interpreter is required when using --interactive with a non-standard way (-prof, -static, or -dynamic).") + -- -ohi sanity check + if (isJust (outputHi dflags) && + (isCompManagerMode mode || srcs `lengthExceeds` 1)) + then throwGhcException (UsageError "-ohi can only be used when compiling a single source file") + else do + + if (isJust (dynOutputHi dflags) && + (isCompManagerMode mode || srcs `lengthExceeds` 1)) + then throwGhcException (UsageError "-dynohi can only be used when compiling a single source file") + else do + + -- -o sanity checking + if (srcs `lengthExceeds` 1 && isJust (outputFile dflags) + && not (isLinkMode mode)) + then throwGhcException (UsageError "can't apply -o to multiple source files") + else do + + let not_linking = not (isLinkMode mode) || isNoLink (ghcLink dflags) + + when (not_linking && not (null objs)) $ + hPutStrLn stderr ("Warning: the following files would be used as linker inputs, but linking is not being done: " ++ unwords objs) + + -- Check that there are some input files + -- (except in the interactive case) + if null srcs && (null objs || not_linking) && needsInputsMode mode && null units + then throwGhcException (UsageError "no input files" ) + else do + + case mode of + StopBefore StopC | not (backendGeneratesHc (backend dflags)) + -> throwGhcException $ UsageError $ + "the option -C is only available with an unregisterised GHC" + StopBefore StopAs | ghcLink dflags == NoLink + -> throwGhcException $ UsageError $ + "the options -S and -fno-code are incompatible. Please omit -S" + + _ -> return () + + -- Verify that output files point somewhere sensible. + verifyOutputFiles dflags + +-- Compiler output options + +-- Called to verify that the output files point somewhere valid. +-- +-- The assumption is that the directory portion of these output +-- options will have to exist by the time 'verifyOutputFiles' +-- is invoked. +-- +-- We create the directories for -odir, -hidir, -outputdir etc. ourselves if +-- they don't exist, so don't check for those here (#2278). +verifyOutputFiles :: DynFlags -> IO () +verifyOutputFiles dflags = do + let ofile = outputFile dflags + when (isJust ofile) $ do + let fn = fromJust ofile + flg <- doesDirNameExist fn + when (not flg) (nonExistentDir "-o" fn) + let ohi = outputHi dflags + when (isJust ohi) $ do + let hi = fromJust ohi + flg <- doesDirNameExist hi + when (not flg) (nonExistentDir "-ohi" hi) + where + nonExistentDir flg dir = + throwGhcException (CmdLineError ("error: directory portion of " ++ + show dir ++ " does not exist (used with " ++ + show flg ++ " option.)")) + +-- | Utility for reporting unknown flag error +unknownFlagsErr :: [String] -> a +unknownFlagsErr fs = throwGhcException $ UsageError $ concatMap oneError fs + where + oneError f = + "unrecognised flag: " ++ f ++ "\n" ++ + (case flagSuggestions (nubSort allNonDeprecatedFlags) f of + [] -> "" + suggs -> "did you mean one of:\n" ++ unlines (map (" " ++) suggs)) ===================================== compiler/GHC/Driver/Session/Mode.hs ===================================== @@ -0,0 +1,327 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NondecreasingIndentation #-} +{-# LANGUAGE TupleSections #-} +module GHC.Driver.Session.Mode where + +import GHC.Driver.CmdLine +import GHC.Driver.Phases +import GHC.Driver.Session +import GHC.Unit.Module ( ModuleName, mkModuleName ) + +import GHC.Types.SrcLoc + +import GHC.Utils.Panic + +import GHC.Data.Maybe + +-- Standard Haskell libraries +import System.IO +import Control.Monad +import Data.Char +import Prelude + +----------------------------------------------------------------------------- +-- GHC modes of operation + +type Mode = Either PreStartupMode PostStartupMode +type PostStartupMode = Either PreLoadMode PostLoadMode + +data PreStartupMode + = ShowVersion -- ghc -V/--version + | ShowNumVersion -- ghc --numeric-version + | ShowSupportedExtensions -- ghc --supported-extensions + | ShowOptions Bool {- isInteractive -} -- ghc --show-options + +showVersionMode, showNumVersionMode, showSupportedExtensionsMode, showOptionsMode :: Mode +showVersionMode = mkPreStartupMode ShowVersion +showNumVersionMode = mkPreStartupMode ShowNumVersion +showSupportedExtensionsMode = mkPreStartupMode ShowSupportedExtensions +showOptionsMode = mkPreStartupMode (ShowOptions False) + +mkPreStartupMode :: PreStartupMode -> Mode +mkPreStartupMode = Left + +isShowVersionMode :: Mode -> Bool +isShowVersionMode (Left ShowVersion) = True +isShowVersionMode _ = False + +isShowNumVersionMode :: Mode -> Bool +isShowNumVersionMode (Left ShowNumVersion) = True +isShowNumVersionMode _ = False + +data PreLoadMode + = ShowGhcUsage -- ghc -? + | ShowGhciUsage -- ghci -? + | ShowInfo -- ghc --info + | PrintWithDynFlags (DynFlags -> String) -- ghc --print-foo + +showGhcUsageMode, showGhciUsageMode, showInfoMode :: Mode +showGhcUsageMode = mkPreLoadMode ShowGhcUsage +showGhciUsageMode = mkPreLoadMode ShowGhciUsage +showInfoMode = mkPreLoadMode ShowInfo + +printSetting :: String -> Mode +printSetting k = mkPreLoadMode (PrintWithDynFlags f) + where f dflags = fromMaybe (panic ("Setting not found: " ++ show k)) + $ lookup k (compilerInfo dflags) + +mkPreLoadMode :: PreLoadMode -> Mode +mkPreLoadMode = Right . Left + +isShowGhcUsageMode :: Mode -> Bool +isShowGhcUsageMode (Right (Left ShowGhcUsage)) = True +isShowGhcUsageMode _ = False + +isShowGhciUsageMode :: Mode -> Bool +isShowGhciUsageMode (Right (Left ShowGhciUsage)) = True +isShowGhciUsageMode _ = False + +data PostLoadMode + = ShowInterface FilePath -- ghc --show-iface + | DoMkDependHS -- ghc -M + | StopBefore StopPhase -- ghc -E | -C | -S + -- StopBefore StopLn is the default + | DoMake -- ghc --make + | DoBackpack -- ghc --backpack foo.bkp + | DoInteractive -- ghc --interactive + | DoEval [String] -- ghc -e foo -e bar => DoEval ["bar", "foo"] + | DoRun -- ghc --run + | DoAbiHash -- ghc --abi-hash + | ShowPackages -- ghc --show-packages + | DoFrontend ModuleName -- ghc --frontend Plugin.Module + +doMkDependHSMode, doMakeMode, doInteractiveMode, doRunMode, + doAbiHashMode, showUnitsMode :: Mode +doMkDependHSMode = mkPostLoadMode DoMkDependHS +doMakeMode = mkPostLoadMode DoMake +doInteractiveMode = mkPostLoadMode DoInteractive +doRunMode = mkPostLoadMode DoRun +doAbiHashMode = mkPostLoadMode DoAbiHash +showUnitsMode = mkPostLoadMode ShowPackages + +showInterfaceMode :: FilePath -> Mode +showInterfaceMode fp = mkPostLoadMode (ShowInterface fp) + +stopBeforeMode :: StopPhase -> Mode +stopBeforeMode phase = mkPostLoadMode (StopBefore phase) + +doEvalMode :: String -> Mode +doEvalMode str = mkPostLoadMode (DoEval [str]) + +doFrontendMode :: String -> Mode +doFrontendMode str = mkPostLoadMode (DoFrontend (mkModuleName str)) + +doBackpackMode :: Mode +doBackpackMode = mkPostLoadMode DoBackpack + +mkPostLoadMode :: PostLoadMode -> Mode +mkPostLoadMode = Right . Right + +isDoInteractiveMode :: Mode -> Bool +isDoInteractiveMode (Right (Right DoInteractive)) = True +isDoInteractiveMode _ = False + +isStopLnMode :: Mode -> Bool +isStopLnMode (Right (Right (StopBefore NoStop))) = True +isStopLnMode _ = False + +isDoMakeMode :: Mode -> Bool +isDoMakeMode (Right (Right DoMake)) = True +isDoMakeMode _ = False + +isDoEvalMode :: Mode -> Bool +isDoEvalMode (Right (Right (DoEval _))) = True +isDoEvalMode _ = False + +#if defined(HAVE_INTERNAL_INTERPRETER) +isInteractiveMode :: PostLoadMode -> Bool +isInteractiveMode DoInteractive = True +isInteractiveMode _ = False +#endif + +-- isInterpretiveMode: byte-code compiler involved +isInterpretiveMode :: PostLoadMode -> Bool +isInterpretiveMode DoInteractive = True +isInterpretiveMode (DoEval _) = True +isInterpretiveMode _ = False + +needsInputsMode :: PostLoadMode -> Bool +needsInputsMode DoMkDependHS = True +needsInputsMode (StopBefore _) = True +needsInputsMode DoMake = True +needsInputsMode _ = False + +-- True if we are going to attempt to link in this mode. +-- (we might not actually link, depending on the GhcLink flag) +isLinkMode :: PostLoadMode -> Bool +isLinkMode (StopBefore NoStop) = True +isLinkMode DoMake = True +isLinkMode DoRun = True +isLinkMode DoInteractive = True +isLinkMode (DoEval _) = True +isLinkMode _ = False + +isCompManagerMode :: PostLoadMode -> Bool +isCompManagerMode DoRun = True +isCompManagerMode DoMake = True +isCompManagerMode DoInteractive = True +isCompManagerMode (DoEval _) = True +isCompManagerMode _ = False + +-- ----------------------------------------------------------------------------- +-- Parsing the mode flag + +parseModeFlags :: [Located String] + -> IO (Mode, [String], + [Located String], + [Warn]) +parseModeFlags args = do + ((leftover, errs1, warns), (mModeFlag, units, errs2, flags')) <- + processCmdLineP mode_flags (Nothing, [], [], []) args + let mode = case mModeFlag of + Nothing -> doMakeMode + Just (m, _) -> m + + -- See Note [Handling errors when parsing command-line flags] + unless (null errs1 && null errs2) $ throwGhcException $ errorsToGhcException $ + map (("on the commandline", )) $ map (unLoc . errMsg) errs1 ++ errs2 + + return (mode, units, flags' ++ leftover, warns) + +type ModeM = CmdLineP (Maybe (Mode, String), [String], [String], [Located String]) + -- mode flags sometimes give rise to new DynFlags (eg. -C, see below) + -- so we collect the new ones and return them. + +mode_flags :: [Flag ModeM] +mode_flags = + [ ------- help / version ---------------------------------------------- + defFlag "?" (PassFlag (setMode showGhcUsageMode)) + , defFlag "-help" (PassFlag (setMode showGhcUsageMode)) + , defFlag "V" (PassFlag (setMode showVersionMode)) + , defFlag "-version" (PassFlag (setMode showVersionMode)) + , defFlag "-numeric-version" (PassFlag (setMode showNumVersionMode)) + , defFlag "-info" (PassFlag (setMode showInfoMode)) + , defFlag "-show-options" (PassFlag (setMode showOptionsMode)) + , defFlag "-supported-languages" (PassFlag (setMode showSupportedExtensionsMode)) + , defFlag "-supported-extensions" (PassFlag (setMode showSupportedExtensionsMode)) + , defFlag "-show-packages" (PassFlag (setMode showUnitsMode)) + ] ++ + [ defFlag k' (PassFlag (setMode (printSetting k))) + | k <- ["Project version", + "Project Git commit id", + "Booter version", + "Stage", + "Build platform", + "Host platform", + "Target platform", + "Have interpreter", + "Object splitting supported", + "Have native code generator", + "Support SMP", + "Unregisterised", + "Tables next to code", + "RTS ways", + "Leading underscore", + "Debug on", + "LibDir", + "Global Package DB", + "C compiler flags", + "C compiler link flags" + ], + let k' = "-print-" ++ map (replaceSpace . toLower) k + replaceSpace ' ' = '-' + replaceSpace c = c + ] ++ + ------- interfaces ---------------------------------------------------- + [ defFlag "-show-iface" (HasArg (\f -> setMode (showInterfaceMode f) + "--show-iface")) + + ------- primary modes ------------------------------------------------ + , defFlag "c" (PassFlag (\f -> do setMode (stopBeforeMode NoStop) f + addFlag "-no-link" f)) + , defFlag "M" (PassFlag (setMode doMkDependHSMode)) + , defFlag "E" (PassFlag (setMode (stopBeforeMode StopPreprocess ))) + , defFlag "C" (PassFlag (setMode (stopBeforeMode StopC))) + , defFlag "S" (PassFlag (setMode (stopBeforeMode StopAs))) + , defFlag "-run" (PassFlag (setMode doRunMode)) + , defFlag "-make" (PassFlag (setMode doMakeMode)) + , defFlag "unit" (SepArg (\s -> addUnit s "-unit")) + , defFlag "-backpack" (PassFlag (setMode doBackpackMode)) + , defFlag "-interactive" (PassFlag (setMode doInteractiveMode)) + , defFlag "-abi-hash" (PassFlag (setMode doAbiHashMode)) + , defFlag "e" (SepArg (\s -> setMode (doEvalMode s) "-e")) + , defFlag "-frontend" (SepArg (\s -> setMode (doFrontendMode s) "-frontend")) + ] + +addUnit :: String -> String -> EwM ModeM () +addUnit unit_str _arg = liftEwM $ do + (mModeFlag, units, errs, flags') <- getCmdLineState + putCmdLineState (mModeFlag, unit_str:units, errs, flags') + +setMode :: Mode -> String -> EwM ModeM () +setMode newMode newFlag = liftEwM $ do + (mModeFlag, units, errs, flags') <- getCmdLineState + let (modeFlag', errs') = + case mModeFlag of + Nothing -> ((newMode, newFlag), errs) + Just (oldMode, oldFlag) -> + case (oldMode, newMode) of + -- -c/--make are allowed together, and mean --make -no-link + _ | isStopLnMode oldMode && isDoMakeMode newMode + || isStopLnMode newMode && isDoMakeMode oldMode -> + ((doMakeMode, "--make"), []) + + -- If we have both --help and --interactive then we + -- want showGhciUsage + _ | isShowGhcUsageMode oldMode && + isDoInteractiveMode newMode -> + ((showGhciUsageMode, oldFlag), []) + | isShowGhcUsageMode newMode && + isDoInteractiveMode oldMode -> + ((showGhciUsageMode, newFlag), []) + + -- If we have both -e and --interactive then -e always wins + _ | isDoEvalMode oldMode && + isDoInteractiveMode newMode -> + ((oldMode, oldFlag), []) + | isDoEvalMode newMode && + isDoInteractiveMode oldMode -> + ((newMode, newFlag), []) + + -- Otherwise, --help/--version/--numeric-version always win + | isDominantFlag oldMode -> ((oldMode, oldFlag), []) + | isDominantFlag newMode -> ((newMode, newFlag), []) + -- We need to accumulate eval flags like "-e foo -e bar" + (Right (Right (DoEval esOld)), + Right (Right (DoEval [eNew]))) -> + ((Right (Right (DoEval (eNew : esOld))), oldFlag), + errs) + -- Saying e.g. --interactive --interactive is OK + _ | oldFlag == newFlag -> ((oldMode, oldFlag), errs) + + -- --interactive and --show-options are used together + (Right (Right DoInteractive), Left (ShowOptions _)) -> + ((Left (ShowOptions True), + "--interactive --show-options"), errs) + (Left (ShowOptions _), (Right (Right DoInteractive))) -> + ((Left (ShowOptions True), + "--show-options --interactive"), errs) + -- Otherwise, complain + _ -> let err = flagMismatchErr oldFlag newFlag + in ((oldMode, oldFlag), err : errs) + putCmdLineState (Just modeFlag', units, errs', flags') + where isDominantFlag f = isShowGhcUsageMode f || + isShowGhciUsageMode f || + isShowVersionMode f || + isShowNumVersionMode f + +flagMismatchErr :: String -> String -> String +flagMismatchErr oldFlag newFlag + = "cannot use `" ++ oldFlag ++ "' with `" ++ newFlag ++ "'" + +addFlag :: String -> String -> EwM ModeM () +addFlag s flag = liftEwM $ do + (m, units, e, flags') <- getCmdLineState + putCmdLineState (m, units, e, mkGeneralLocated loc s : flags') + where loc = "addFlag by " ++ flag ++ " on the commandline" ===================================== compiler/GHC/Driver/Session/Units.hs ===================================== @@ -0,0 +1,226 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NondecreasingIndentation #-} +{-# LANGUAGE TupleSections #-} +module GHC.Driver.Session.Units (initMulti) where + +-- The official GHC API +import qualified GHC +import GHC (parseTargetFiles, Ghc, GhcMonad(..)) + +import GHC.Driver.Env +import GHC.Driver.Errors +import GHC.Driver.Errors.Types +import GHC.Driver.Phases +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Driver.Pipeline ( oneShot, compileFile ) +import GHC.Driver.Config.Diagnostic + +import GHC.Unit.Env +import GHC.Unit (UnitId) +import GHC.Unit.Home.PackageTable +import qualified GHC.Unit.Home.Graph as HUG +import GHC.Unit.State ( emptyUnitState ) +import qualified GHC.Unit.State as State + +import GHC.Types.SrcLoc +import GHC.Types.SourceError + +import GHC.Utils.Misc +import GHC.Utils.Panic +import GHC.Utils.Outputable as Outputable +import GHC.Utils.Monad ( liftIO, mapMaybeM ) +import GHC.Data.Maybe + +import System.IO +import System.Exit +import System.FilePath +import Control.Monad +import Data.List ( partition, (\\) ) +import qualified Data.Set as Set +import Prelude +import GHC.ResponseFile (expandResponse) +import Data.Bifunctor +import GHC.Data.Graph.Directed +import qualified Data.List.NonEmpty as NE + +import GHC.Driver.Session.Mode +import GHC.Driver.Session.Lint + +-- Strip out any ["+RTS", ..., "-RTS"] sequences in the command string list. +removeRTS :: [String] -> [String] +removeRTS ("+RTS" : xs) = + case dropWhile (/= "-RTS") xs of + [] -> [] + (_ : ys) -> removeRTS ys +removeRTS (y:ys) = y : removeRTS ys +removeRTS [] = [] + +initMulti :: NE.NonEmpty String -> Ghc ([(String, Maybe UnitId, Maybe Phase)]) +initMulti unitArgsFiles = do + hsc_env <- GHC.getSession + let logger = hsc_logger hsc_env + initial_dflags <- GHC.getSessionDynFlags + + dynFlagsAndSrcs <- forM unitArgsFiles $ \f -> do + when (verbosity initial_dflags > 2) (liftIO $ print f) + args <- liftIO $ expandResponse [f] + (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine logger initial_dflags (map (mkGeneralLocated f) (removeRTS args)) + handleSourceError (\e -> do + GHC.printException e + liftIO $ exitWith (ExitFailure 1)) $ do + liftIO $ printOrThrowDiagnostics logger (initPrintConfig dflags2) (initDiagOpts dflags2) (GhcDriverMessage <$> warns) + + let (dflags3, srcs, objs) = parseTargetFiles dflags2 (map unLoc fileish_args) + dflags4 = offsetDynFlags dflags3 + + let (hs_srcs, non_hs_srcs) = partition isHaskellishTarget srcs + + -- This is dubious as the whole unit environment won't be set-up correctly, but + -- that doesn't matter for what we use it for (linking and oneShot) + let dubious_hsc_env = hscSetFlags dflags4 hsc_env + -- if we have no haskell sources from which to do a dependency + -- analysis, then just do one-shot compilation and/or linking. + -- This means that "ghc Foo.o Bar.o -o baz" links the program as + -- we expect. + if (null hs_srcs) + then liftIO (oneShot dubious_hsc_env NoStop srcs) >> return (dflags4, []) + else do + + o_files <- mapMaybeM (\x -> liftIO $ compileFile dubious_hsc_env NoStop x) + non_hs_srcs + let dflags5 = dflags4 { ldInputs = map (FileOption "") o_files + ++ ldInputs dflags4 } + + liftIO $ checkOptions DoMake dflags5 srcs objs [] + + pure (dflags5, hs_srcs) + + let + unitDflags = NE.map fst dynFlagsAndSrcs + srcs = NE.map (\(dflags, lsrcs) -> map (uncurry (,Just $ homeUnitId_ dflags,)) lsrcs) dynFlagsAndSrcs + (hs_srcs, _non_hs_srcs) = unzip (map (partition (\(file, _uid, phase) -> isHaskellishTarget (file, phase))) (NE.toList srcs)) + + checkDuplicateUnits initial_dflags (NE.toList (NE.zip unitArgsFiles unitDflags)) + + (initial_home_graph, mainUnitId) <- liftIO $ createUnitEnvFromFlags unitDflags + let home_units = HUG.allUnits initial_home_graph + + home_unit_graph <- forM initial_home_graph $ \homeUnitEnv -> do + let cached_unit_dbs = homeUnitEnv_unit_dbs homeUnitEnv + hue_flags = homeUnitEnv_dflags homeUnitEnv + dflags = homeUnitEnv_dflags homeUnitEnv + (dbs,unit_state,home_unit,mconstants) <- liftIO $ State.initUnits logger hue_flags cached_unit_dbs home_units + + updated_dflags <- liftIO $ updatePlatformConstants dflags mconstants + emptyHpt <- liftIO $ emptyHomePackageTable + pure $ HomeUnitEnv + { homeUnitEnv_units = unit_state + , homeUnitEnv_unit_dbs = Just dbs + , homeUnitEnv_dflags = updated_dflags + , homeUnitEnv_hpt = emptyHpt + , homeUnitEnv_home_unit = Just home_unit + } + + checkUnitCycles initial_dflags home_unit_graph + + let dflags = homeUnitEnv_dflags $ HUG.unitEnv_lookup mainUnitId home_unit_graph + unitEnv <- assertUnitEnvInvariant <$> (liftIO $ initUnitEnv mainUnitId home_unit_graph (ghcNameVersion dflags) (targetPlatform dflags)) + let final_hsc_env = hsc_env { hsc_unit_env = unitEnv } + + GHC.setSession final_hsc_env + + -- if we have no haskell sources from which to do a dependency + -- analysis, then just do one-shot compilation and/or linking. + -- This means that "ghc Foo.o Bar.o -o baz" links the program as + -- we expect. + if (null hs_srcs) + then do + liftIO $ hPutStrLn stderr $ "Multi Mode can not be used for one-shot mode." + liftIO $ exitWith (ExitFailure 1) + else do + +{- + o_files <- liftIO $ mapMaybeM + (\(src, uid, mphase) -> + compileFile (hscSetActiveHomeUnit (ue_unitHomeUnit (fromJust uid) unitEnv) final_hsc_env) NoStop (src, mphase) + ) + (concat non_hs_srcs) + -} + + -- MP: This should probably modify dflags for each unit? + --let dflags' = dflags { ldInputs = map (FileOption "") o_files + -- ++ ldInputs dflags } + return $ concat hs_srcs + +checkUnitCycles :: DynFlags -> HUG.HomeUnitGraph -> Ghc () +checkUnitCycles dflags graph = processSCCs (HUG.hugSCCs graph) + where + + processSCCs [] = return () + processSCCs (AcyclicSCC _: other_sccs) = processSCCs other_sccs + processSCCs (CyclicSCC uids: _) = throwGhcException $ CmdLineError $ showSDoc dflags (cycle_err uids) + + + cycle_err uids = + hang (text "Units form a dependency cycle:") + 2 + (one_err uids) + + one_err uids = vcat $ + (map (\uid -> text "-" <+> ppr uid <+> text "depends on") start) + ++ [text "-" <+> ppr final] + where + start = init uids + final = last uids + +-- | Check that we don't have multiple units with the same UnitId. +checkDuplicateUnits :: DynFlags -> [(FilePath, DynFlags)] -> Ghc () +checkDuplicateUnits dflags flags = + unless (null duplicate_ids) + (throwGhcException $ CmdLineError $ showSDoc dflags multi_err) + + where + uids = map (second homeUnitId_) flags + deduplicated_uids = ordNubOn snd uids + duplicate_ids = Set.fromList (map snd uids \\ map snd deduplicated_uids) + + duplicate_flags = filter (flip Set.member duplicate_ids . snd) uids + + one_err (fp, home_uid) = text "-" <+> ppr home_uid <+> text "defined in" <+> text fp + + multi_err = + hang (text "Multiple units with the same unit-id:") + 2 + (vcat (map one_err duplicate_flags)) + + +offsetDynFlags :: DynFlags -> DynFlags +offsetDynFlags dflags = + dflags { hiDir = c hiDir + , objectDir = c objectDir + , stubDir = c stubDir + , hieDir = c hieDir + , dumpDir = c dumpDir } + + where + c f = augment_maybe (f dflags) + + augment_maybe Nothing = Nothing + augment_maybe (Just f) = Just (augment f) + augment f | isRelative f, Just offset <- workingDirectory dflags = offset </> f + | otherwise = f + + +createUnitEnvFromFlags :: NE.NonEmpty DynFlags -> IO (HomeUnitGraph, UnitId) +createUnitEnvFromFlags unitDflags = do + unitEnvList <- forM unitDflags $ \dflags -> do + emptyHpt <- emptyHomePackageTable + let newInternalUnitEnv = + HUG.mkHomeUnitEnv emptyUnitState Nothing dflags emptyHpt Nothing + return (homeUnitId_ dflags, newInternalUnitEnv) + let activeUnit = fst $ NE.head unitEnvList + return (HUG.hugFromList (NE.toList unitEnvList), activeUnit) + + ===================================== compiler/GHC/Runtime/Debugger/Breakpoints.hs ===================================== @@ -0,0 +1,106 @@ +-- | GHC API debugger module for finding and setting breakpoints. +-- +-- This module is user facing and is at least used by `GHCi` and `ghc-debugger` +-- to find and set breakpoints. +module GHC.Runtime.Debugger.Breakpoints where + +import GHC.Prelude +import GHC.Types.SrcLoc +import qualified GHC.Data.Strict as Strict +import qualified Data.Semigroup as S +import Data.List +import Data.Maybe +import Data.Function +import Control.Monad +import GHC +import Data.Array + +-------------------------------------------------------------------------------- +-- Finding breakpoints +-------------------------------------------------------------------------------- + +-- | Find a breakpoint given a Module's 'TickArray' and the line number. +-- +-- When a line number is specified, the current policy for choosing +-- the best breakpoint is this: +-- - the leftmost complete subexpression on the specified line, or +-- - the leftmost subexpression starting on the specified line, or +-- - the rightmost subexpression enclosing the specified line +-- +findBreakByLine :: Int {-^ Line number -} -> TickArray -> Maybe (BreakIndex, RealSrcSpan) +findBreakByLine line arr + | not (inRange (bounds arr) line) = Nothing + | otherwise = + listToMaybe (sortBy (leftmostLargestRealSrcSpan `on` snd) comp) `mplus` + listToMaybe (sortBy (compare `on` snd) incomp) `mplus` + listToMaybe (sortBy (flip compare `on` snd) ticks) + where + ticks = arr ! line + + starts_here = [ (ix,pan) | (ix, pan) <- ticks, + GHC.srcSpanStartLine pan == line ] + + (comp, incomp) = partition ends_here starts_here + where ends_here (_,pan) = GHC.srcSpanEndLine pan == line + +-- | The aim of this function is to find the breakpoints for all the RHSs of +-- the equations corresponding to a binding. So we find all breakpoints +-- for +-- (a) this binder only (it maybe a top-level or a nested declaration) +-- (b) that do not have an enclosing breakpoint +findBreakForBind :: String {-^ Name of bind to break at -} -> GHC.ModBreaks -> [(BreakIndex, RealSrcSpan)] +findBreakForBind str_name modbreaks = filter (not . enclosed) ticks + where + ticks = [ (index, span) + | (index, decls) <- assocs (GHC.modBreaks_decls modbreaks), + str_name == intercalate "." decls, + RealSrcSpan span _ <- [GHC.modBreaks_locs modbreaks ! index] ] + enclosed (_,sp0) = any subspan ticks + where subspan (_,sp) = sp /= sp0 && + realSrcSpanStart sp <= realSrcSpanStart sp0 && + realSrcSpanEnd sp0 <= realSrcSpanEnd sp + +-- | Find a breakpoint in the 'TickArray' of a module, given a line number and a column coordinate. +findBreakByCoord :: (Int, Int) -> TickArray -> Maybe (BreakIndex, RealSrcSpan) +findBreakByCoord (line, col) arr + | not (inRange (bounds arr) line) = Nothing + | otherwise = + listToMaybe (sortBy (flip compare `on` snd) contains ++ + sortBy (compare `on` snd) after_here) + where + ticks = arr ! line + + -- the ticks that span this coordinate + contains = [ tick | tick@(_,pan) <- ticks, RealSrcSpan pan Strict.Nothing `spans` (line,col) ] + + after_here = [ tick | tick@(_,pan) <- ticks, + GHC.srcSpanStartLine pan == line, + GHC.srcSpanStartCol pan >= col ] + +leftmostLargestRealSrcSpan :: RealSrcSpan -> RealSrcSpan -> Ordering +leftmostLargestRealSrcSpan = on compare realSrcSpanStart S.<> on (flip compare) realSrcSpanEnd + +-------------------------------------------------------------------------------- +-- Mapping line numbers to ticks +-------------------------------------------------------------------------------- + +-- | Maps line numbers to the breakpoint ticks existing at that line for a module. +type TickArray = Array Int [(GHC.BreakIndex,RealSrcSpan)] + +-- | Construct the 'TickArray' for the given module. +makeModuleLineMap :: GhcMonad m => Module -> m (Maybe TickArray) +makeModuleLineMap m = do + mi <- GHC.getModuleInfo m + return $ + mkTickArray . assocs . GHC.modBreaks_locs . GHC.modInfoModBreaks <$> mi + where + mkTickArray :: [(BreakIndex, SrcSpan)] -> TickArray + mkTickArray ticks + = accumArray (flip (:)) [] (1, max_line) + [ (line, (nm,pan)) | (nm,RealSrcSpan pan _) <- ticks, line <- srcSpanLines pan ] + where + max_line = foldr max 0 [ GHC.srcSpanEndLine sp | (_, RealSrcSpan sp _) <- ticks ] + srcSpanLines pan = [ GHC.srcSpanStartLine pan .. GHC.srcSpanEndLine pan ] + + + ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -1266,7 +1266,7 @@ dynCompileExpr expr = do return (unsafeCoerce hval :: Dynamic) ----------------------------------------------------------------------------- --- show a module and it's source/object filenames +-- show a module and its source/object filenames showModule :: GhcMonad m => ModSummary -> m String showModule mod_summary = ===================================== compiler/GHC/Runtime/Eval/Types.hs ===================================== @@ -76,7 +76,8 @@ breakHere step break_span = case step of data ExecResult - -- | Execution is complete + -- | Execution is complete with either an exception or the list of + -- user-visible names that were brought into scope. = ExecComplete { execResult :: Either SomeException [Name] , execAllocation :: Word64 ===================================== compiler/ghc.cabal.in ===================================== @@ -536,6 +536,9 @@ Library GHC.Driver.Plugins.External GHC.Driver.Ppr GHC.Driver.Session + GHC.Driver.Session.Lint + GHC.Driver.Session.Mode + GHC.Driver.Session.Units GHC.Hs GHC.Hs.Basic GHC.Hs.Binds @@ -694,6 +697,7 @@ Library GHC.Rename.Utils GHC.Runtime.Context GHC.Runtime.Debugger + GHC.Runtime.Debugger.Breakpoints GHC.Runtime.Eval GHC.Runtime.Eval.Types GHC.Runtime.Heap.Inspect ===================================== ghc/GHCi/UI.hs ===================================== @@ -40,6 +40,7 @@ import GHCi.Leak import GHCi.UI.Print import GHC.Runtime.Debugger +import GHC.Runtime.Debugger.Breakpoints import GHC.Runtime.Eval (mkTopLevEnv) -- The GHC interface @@ -3148,7 +3149,7 @@ newDynFlags interactive_only minus_opts = do logger <- getLogger idflags0 <- GHC.getInteractiveDynFlags - (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine idflags0 lopts + (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine logger idflags0 lopts liftIO $ printOrThrowDiagnostics logger (initPrintConfig idflags1) (initDiagOpts idflags1) (GhcDriverMessage <$> warns) when (not $ null leftovers) (unknownFlagsErr $ map unLoc leftovers) @@ -3161,7 +3162,7 @@ newDynFlags interactive_only minus_opts = do dflags0 <- getDynFlags when (not interactive_only) $ do - (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine dflags0 lopts + (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine logger dflags0 lopts must_reload <- GHC.setProgramDynFlags dflags1 -- if the package flags changed, reset the context and link @@ -3853,9 +3854,6 @@ enclosingTickSpan md (RealSrcSpan src _) = do return . minimumBy leftmostLargestRealSrcSpan $ enclosing_spans where -leftmostLargestRealSrcSpan :: RealSrcSpan -> RealSrcSpan -> Ordering -leftmostLargestRealSrcSpan = on compare realSrcSpanStart S.<> on (flip compare) realSrcSpanEnd - traceCmd :: GhciMonad m => String -> m () traceCmd arg = withSandboxOnly ":trace" $ tr arg @@ -4089,7 +4087,7 @@ breakByModuleLine :: GhciMonad m => Module -> Int -> [String] -> m () breakByModuleLine md line args | [] <- args = findBreakAndSet md $ maybeToList . findBreakByLine line | [col] <- args, all isDigit col = - findBreakAndSet md $ maybeToList . findBreakByCoord Nothing (line, read col) + findBreakAndSet md $ maybeToList . findBreakByCoord (line, read col) | otherwise = breakSyntax -- Set a breakpoint for an identifier @@ -4113,7 +4111,7 @@ breakById inp = do let modBreaks = case mb_mod_info of (Just mod_info) -> GHC.modInfoModBreaks mod_info Nothing -> emptyModBreaks - findBreakAndSet (fromJust mb_mod) $ findBreakForBind fun_str modBreaks + findBreakAndSet (fromJust mb_mod) $ \_ -> findBreakForBind fun_str modBreaks where -- Try to lookup the module for an identifier that is in scope. -- `parseName` throws an exception, if the identifier is not in scope @@ -4181,68 +4179,6 @@ findBreakAndSet md lookupTickTree = do then text " was already set at " <> ppr pan else text " activated at " <> ppr pan --- When a line number is specified, the current policy for choosing --- the best breakpoint is this: --- - the leftmost complete subexpression on the specified line, or --- - the leftmost subexpression starting on the specified line, or --- - the rightmost subexpression enclosing the specified line --- -findBreakByLine :: Int -> TickArray -> Maybe (BreakIndex,RealSrcSpan) -findBreakByLine line arr - | not (inRange (bounds arr) line) = Nothing - | otherwise = - listToMaybe (sortBy (leftmostLargestRealSrcSpan `on` snd) comp) `mplus` - listToMaybe (sortBy (compare `on` snd) incomp) `mplus` - listToMaybe (sortBy (flip compare `on` snd) ticks) - where - ticks = arr ! line - - starts_here = [ (ix,pan) | (ix, pan) <- ticks, - GHC.srcSpanStartLine pan == line ] - - (comp, incomp) = partition ends_here starts_here - where ends_here (_,pan) = GHC.srcSpanEndLine pan == line - --- The aim is to find the breakpoints for all the RHSs of the --- equations corresponding to a binding. So we find all breakpoints --- for --- (a) this binder only (it maybe a top-level or a nested declaration) --- (b) that do not have an enclosing breakpoint -findBreakForBind :: String -> GHC.ModBreaks -> TickArray - -> [(BreakIndex,RealSrcSpan)] -findBreakForBind str_name modbreaks _ = filter (not . enclosed) ticks - where - ticks = [ (index, span) - | (index, decls) <- assocs (GHC.modBreaks_decls modbreaks), - str_name == declPath decls, - RealSrcSpan span _ <- [GHC.modBreaks_locs modbreaks ! index] ] - enclosed (_,sp0) = any subspan ticks - where subspan (_,sp) = sp /= sp0 && - realSrcSpanStart sp <= realSrcSpanStart sp0 && - realSrcSpanEnd sp0 <= realSrcSpanEnd sp - -findBreakByCoord :: Maybe FastString -> (Int,Int) -> TickArray - -> Maybe (BreakIndex,RealSrcSpan) -findBreakByCoord mb_file (line, col) arr - | not (inRange (bounds arr) line) = Nothing - | otherwise = - listToMaybe (sortBy (flip compare `on` snd) contains ++ - sortBy (compare `on` snd) after_here) - where - ticks = arr ! line - - -- the ticks that span this coordinate - contains = [ tick | tick@(_,pan) <- ticks, RealSrcSpan pan Strict.Nothing `spans` (line,col), - is_correct_file pan ] - - is_correct_file pan - | Just f <- mb_file = GHC.srcSpanFile pan == f - | otherwise = True - - after_here = [ tick | tick@(_,pan) <- ticks, - GHC.srcSpanStartLine pan == line, - GHC.srcSpanStartCol pan >= col ] - -- For now, use ANSI bold on terminals that we know support it. -- Otherwise, we add a line of carets under the active expression instead. -- In particular, on Windows and when running the testsuite (which sets @@ -4327,7 +4263,7 @@ list2 [arg] = do RealSrcLoc l _ -> do tickArray <- assert (isExternalName name) $ getTickArray (GHC.nameModule name) - let mb_span = findBreakByCoord (Just (GHC.srcLocFile l)) + let mb_span = findBreakByCoord (GHC.srcLocLine l, GHC.srcLocCol l) tickArray case mb_span of @@ -4435,22 +4371,13 @@ getTickArray modl = do case lookupModuleEnv arrmap modl of Just arr -> return arr Nothing -> do - (ticks, _) <- getModBreak modl - let arr = mkTickArray (assocs ticks) + arr <- fromMaybe (panic "getTickArray") <$> makeModuleLineMap modl setGHCiState st{tickarrays = extendModuleEnv arrmap modl arr} return arr discardTickArrays :: GhciMonad m => m () discardTickArrays = modifyGHCiState (\st -> st {tickarrays = emptyModuleEnv}) -mkTickArray :: [(BreakIndex,SrcSpan)] -> TickArray -mkTickArray ticks - = accumArray (flip (:)) [] (1, max_line) - [ (line, (nm,pan)) | (nm,RealSrcSpan pan _) <- ticks, line <- srcSpanLines pan ] - where - max_line = foldr max 0 [ GHC.srcSpanEndLine sp | (_, RealSrcSpan sp _) <- ticks ] - srcSpanLines pan = [ GHC.srcSpanStartLine pan .. GHC.srcSpanEndLine pan ] - -- don't reset the counter back to zero? discardActiveBreakPoints :: GhciMonad m => m () discardActiveBreakPoints = do ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -56,10 +56,10 @@ import GHC.Hs (ImportDecl, GhcPs, GhciLStmt, LHsDecl) import GHC.Hs.Utils import GHC.Utils.Misc import GHC.Utils.Logger +import GHC.Runtime.Debugger.Breakpoints import GHC.Utils.Exception hiding (uninterruptibleMask, mask, catch) import Numeric -import Data.Array import Data.IORef import Data.Time import System.Environment @@ -164,8 +164,6 @@ data GHCiState = GHCiState ifaceCache :: ModIfaceCache } -type TickArray = Array Int [(GHC.BreakIndex,RealSrcSpan)] - -- | A GHCi command data Command = Command ===================================== ghc/Main.hs ===================================== @@ -35,7 +35,6 @@ import GHC.Driver.Config.Logger (initLogFlags) import GHC.Driver.Config.Diagnostic import GHC.Platform -import GHC.Platform.Ways import GHC.Platform.Host #if defined(HAVE_INTERNAL_INTERPRETER) @@ -44,15 +43,10 @@ import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings import GHC.Runtime.Loader ( loadFrontendPlugin, initializeSessionPlugins ) -import GHC.Unit.Env -import GHC.Unit (UnitId) -import GHC.Unit.Home.PackageTable -import qualified GHC.Unit.Home.Graph as HUG import GHC.Unit.Module ( ModuleName, mkModuleName ) import GHC.Unit.Module.ModIface -import GHC.Unit.State ( pprUnits, pprUnitsSimple, emptyUnitState ) +import GHC.Unit.State ( pprUnits, pprUnitsSimple ) import GHC.Unit.Finder ( findImportedModule, FindResult(..) ) -import qualified GHC.Unit.State as State import GHC.Unit.Types ( IsBootInterface(..) ) import GHC.Types.Basic ( failed ) @@ -62,7 +56,6 @@ import GHC.Types.Unique.Supply import GHC.Types.PkgQual import GHC.Utils.Error -import GHC.Utils.Misc import GHC.Utils.Panic import GHC.Utils.Outputable as Outputable import GHC.Utils.Monad ( liftIO, mapMaybeM ) @@ -84,21 +77,19 @@ import GHC.Iface.Recomp.Binary ( fingerprintBinMem ) import GHC.Tc.Utils.Monad ( initIfaceCheck ) import GHC.Iface.Errors.Ppr +import GHC.Driver.Session.Mode +import GHC.Driver.Session.Lint +import GHC.Driver.Session.Units + -- Standard Haskell libraries import System.IO import System.Environment import System.Exit -import System.FilePath import Control.Monad import Control.Monad.Trans.Class import Control.Monad.Trans.Except (throwE, runExceptT) -import Data.Char -import Data.List ( isPrefixOf, partition, intercalate, (\\) ) -import qualified Data.Set as Set +import Data.List ( isPrefixOf, partition, intercalate ) import Prelude -import GHC.ResponseFile (expandResponse) -import Data.Bifunctor -import GHC.Data.Graph.Directed import qualified Data.List.NonEmpty as NE ----------------------------------------------------------------------------- @@ -224,41 +215,9 @@ main' postLoadMode units dflags0 args flagWarnings = do -- The rest of the arguments are "dynamic" -- Leftover ones are presumably files - (dflags3', fileish_args, dynamicFlagWarnings) <- + (dflags4, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags logger2 dflags2 args' - -- When we do ghci, force using dyn ways if the target RTS linker - -- only supports dynamic code - let dflags3 - | LinkInMemory <- link, - sTargetRTSLinkerOnlySupportsSharedLibs $ settings dflags3' - = setDynamicNow $ - -- See checkOptions below, -fexternal-interpreter is - -- required when using --interactive with a non-standard - -- way (-prof, -static, or -dynamic). - setGeneralFlag' Opt_ExternalInterpreter $ - -- Use .o for dynamic object, otherwise it gets dropped - -- with "Warning: ignoring unrecognised input", see - -- objish_suffixes - dflags3' { dynObjectSuf_ = objectSuf dflags3' } - | otherwise - = dflags3' - - let dflags4 = if backendNeedsFullWays bcknd && - not (gopt Opt_ExternalInterpreter dflags3) - then - let platform = targetPlatform dflags3 - dflags3a = dflags3 { targetWays_ = hostFullWays } - dflags3b = foldl gopt_set dflags3a - $ concatMap (wayGeneralFlags platform) - hostFullWays - dflags3c = foldl gopt_unset dflags3b - $ concatMap (wayUnsetGeneralFlags platform) - hostFullWays - in dflags3c - else - dflags3 - let logger4 = setLogFlags logger2 (initLogFlags dflags4) GHC.prettyPrintGhcErrors logger4 $ do @@ -347,404 +306,6 @@ ghciUI units srcs maybe_expr = do interactiveUI defaultGhciSettings hs_srcs maybe_expr #endif - --- ----------------------------------------------------------------------------- --- Option sanity checks - --- | Ensure sanity of options. --- --- Throws 'UsageError' or 'CmdLineError' if not. -checkOptions :: PostLoadMode -> DynFlags -> [(String,Maybe Phase)] -> [String] -> [String] -> IO () - -- Final sanity checking before kicking off a compilation (pipeline). -checkOptions mode dflags srcs objs units = do - -- Complain about any unknown flags - let unknown_opts = [ f | (f@('-':_), _) <- srcs ] - when (notNull unknown_opts) (unknownFlagsErr unknown_opts) - - when (not (Set.null (rtsWays (ways dflags))) - && isInterpretiveMode mode) $ - hPutStrLn stderr ("Warning: -debug, -threaded and -ticky are ignored by GHCi") - - -- -prof and --interactive are not a good combination - when ((fullWays (ways dflags) /= hostFullWays) - && isInterpretiveMode mode - && not (gopt Opt_ExternalInterpreter dflags)) $ - do throwGhcException (UsageError - "-fexternal-interpreter is required when using --interactive with a non-standard way (-prof, -static, or -dynamic).") - -- -ohi sanity check - if (isJust (outputHi dflags) && - (isCompManagerMode mode || srcs `lengthExceeds` 1)) - then throwGhcException (UsageError "-ohi can only be used when compiling a single source file") - else do - - if (isJust (dynOutputHi dflags) && - (isCompManagerMode mode || srcs `lengthExceeds` 1)) - then throwGhcException (UsageError "-dynohi can only be used when compiling a single source file") - else do - - -- -o sanity checking - if (srcs `lengthExceeds` 1 && isJust (outputFile dflags) - && not (isLinkMode mode)) - then throwGhcException (UsageError "can't apply -o to multiple source files") - else do - - let not_linking = not (isLinkMode mode) || isNoLink (ghcLink dflags) - - when (not_linking && not (null objs)) $ - hPutStrLn stderr ("Warning: the following files would be used as linker inputs, but linking is not being done: " ++ unwords objs) - - -- Check that there are some input files - -- (except in the interactive case) - if null srcs && (null objs || not_linking) && needsInputsMode mode && null units - then throwGhcException (UsageError "no input files" ) - else do - - case mode of - StopBefore StopC | not (backendGeneratesHc (backend dflags)) - -> throwGhcException $ UsageError $ - "the option -C is only available with an unregisterised GHC" - StopBefore StopAs | ghcLink dflags == NoLink - -> throwGhcException $ UsageError $ - "the options -S and -fno-code are incompatible. Please omit -S" - - _ -> return () - - -- Verify that output files point somewhere sensible. - verifyOutputFiles dflags - --- Compiler output options - --- Called to verify that the output files point somewhere valid. --- --- The assumption is that the directory portion of these output --- options will have to exist by the time 'verifyOutputFiles' --- is invoked. --- --- We create the directories for -odir, -hidir, -outputdir etc. ourselves if --- they don't exist, so don't check for those here (#2278). -verifyOutputFiles :: DynFlags -> IO () -verifyOutputFiles dflags = do - let ofile = outputFile dflags - when (isJust ofile) $ do - let fn = fromJust ofile - flg <- doesDirNameExist fn - when (not flg) (nonExistentDir "-o" fn) - let ohi = outputHi dflags - when (isJust ohi) $ do - let hi = fromJust ohi - flg <- doesDirNameExist hi - when (not flg) (nonExistentDir "-ohi" hi) - where - nonExistentDir flg dir = - throwGhcException (CmdLineError ("error: directory portion of " ++ - show dir ++ " does not exist (used with " ++ - show flg ++ " option.)")) - ------------------------------------------------------------------------------ --- GHC modes of operation - -type Mode = Either PreStartupMode PostStartupMode -type PostStartupMode = Either PreLoadMode PostLoadMode - -data PreStartupMode - = ShowVersion -- ghc -V/--version - | ShowNumVersion -- ghc --numeric-version - | ShowSupportedExtensions -- ghc --supported-extensions - | ShowOptions Bool {- isInteractive -} -- ghc --show-options - -showVersionMode, showNumVersionMode, showSupportedExtensionsMode, showOptionsMode :: Mode -showVersionMode = mkPreStartupMode ShowVersion -showNumVersionMode = mkPreStartupMode ShowNumVersion -showSupportedExtensionsMode = mkPreStartupMode ShowSupportedExtensions -showOptionsMode = mkPreStartupMode (ShowOptions False) - -mkPreStartupMode :: PreStartupMode -> Mode -mkPreStartupMode = Left - -isShowVersionMode :: Mode -> Bool -isShowVersionMode (Left ShowVersion) = True -isShowVersionMode _ = False - -isShowNumVersionMode :: Mode -> Bool -isShowNumVersionMode (Left ShowNumVersion) = True -isShowNumVersionMode _ = False - -data PreLoadMode - = ShowGhcUsage -- ghc -? - | ShowGhciUsage -- ghci -? - | ShowInfo -- ghc --info - | PrintWithDynFlags (DynFlags -> String) -- ghc --print-foo - -showGhcUsageMode, showGhciUsageMode, showInfoMode :: Mode -showGhcUsageMode = mkPreLoadMode ShowGhcUsage -showGhciUsageMode = mkPreLoadMode ShowGhciUsage -showInfoMode = mkPreLoadMode ShowInfo - -printSetting :: String -> Mode -printSetting k = mkPreLoadMode (PrintWithDynFlags f) - where f dflags = fromMaybe (panic ("Setting not found: " ++ show k)) - $ lookup k (compilerInfo dflags) - -mkPreLoadMode :: PreLoadMode -> Mode -mkPreLoadMode = Right . Left - -isShowGhcUsageMode :: Mode -> Bool -isShowGhcUsageMode (Right (Left ShowGhcUsage)) = True -isShowGhcUsageMode _ = False - -isShowGhciUsageMode :: Mode -> Bool -isShowGhciUsageMode (Right (Left ShowGhciUsage)) = True -isShowGhciUsageMode _ = False - -data PostLoadMode - = ShowInterface FilePath -- ghc --show-iface - | DoMkDependHS -- ghc -M - | StopBefore StopPhase -- ghc -E | -C | -S - -- StopBefore StopLn is the default - | DoMake -- ghc --make - | DoBackpack -- ghc --backpack foo.bkp - | DoInteractive -- ghc --interactive - | DoEval [String] -- ghc -e foo -e bar => DoEval ["bar", "foo"] - | DoRun -- ghc --run - | DoAbiHash -- ghc --abi-hash - | ShowPackages -- ghc --show-packages - | DoFrontend ModuleName -- ghc --frontend Plugin.Module - -doMkDependHSMode, doMakeMode, doInteractiveMode, doRunMode, - doAbiHashMode, showUnitsMode :: Mode -doMkDependHSMode = mkPostLoadMode DoMkDependHS -doMakeMode = mkPostLoadMode DoMake -doInteractiveMode = mkPostLoadMode DoInteractive -doRunMode = mkPostLoadMode DoRun -doAbiHashMode = mkPostLoadMode DoAbiHash -showUnitsMode = mkPostLoadMode ShowPackages - -showInterfaceMode :: FilePath -> Mode -showInterfaceMode fp = mkPostLoadMode (ShowInterface fp) - -stopBeforeMode :: StopPhase -> Mode -stopBeforeMode phase = mkPostLoadMode (StopBefore phase) - -doEvalMode :: String -> Mode -doEvalMode str = mkPostLoadMode (DoEval [str]) - -doFrontendMode :: String -> Mode -doFrontendMode str = mkPostLoadMode (DoFrontend (mkModuleName str)) - -doBackpackMode :: Mode -doBackpackMode = mkPostLoadMode DoBackpack - -mkPostLoadMode :: PostLoadMode -> Mode -mkPostLoadMode = Right . Right - -isDoInteractiveMode :: Mode -> Bool -isDoInteractiveMode (Right (Right DoInteractive)) = True -isDoInteractiveMode _ = False - -isStopLnMode :: Mode -> Bool -isStopLnMode (Right (Right (StopBefore NoStop))) = True -isStopLnMode _ = False - -isDoMakeMode :: Mode -> Bool -isDoMakeMode (Right (Right DoMake)) = True -isDoMakeMode _ = False - -isDoEvalMode :: Mode -> Bool -isDoEvalMode (Right (Right (DoEval _))) = True -isDoEvalMode _ = False - -#if defined(HAVE_INTERNAL_INTERPRETER) -isInteractiveMode :: PostLoadMode -> Bool -isInteractiveMode DoInteractive = True -isInteractiveMode _ = False -#endif - --- isInterpretiveMode: byte-code compiler involved -isInterpretiveMode :: PostLoadMode -> Bool -isInterpretiveMode DoInteractive = True -isInterpretiveMode (DoEval _) = True -isInterpretiveMode _ = False - -needsInputsMode :: PostLoadMode -> Bool -needsInputsMode DoMkDependHS = True -needsInputsMode (StopBefore _) = True -needsInputsMode DoMake = True -needsInputsMode _ = False - --- True if we are going to attempt to link in this mode. --- (we might not actually link, depending on the GhcLink flag) -isLinkMode :: PostLoadMode -> Bool -isLinkMode (StopBefore NoStop) = True -isLinkMode DoMake = True -isLinkMode DoRun = True -isLinkMode DoInteractive = True -isLinkMode (DoEval _) = True -isLinkMode _ = False - -isCompManagerMode :: PostLoadMode -> Bool -isCompManagerMode DoRun = True -isCompManagerMode DoMake = True -isCompManagerMode DoInteractive = True -isCompManagerMode (DoEval _) = True -isCompManagerMode _ = False - --- ----------------------------------------------------------------------------- --- Parsing the mode flag - -parseModeFlags :: [Located String] - -> IO (Mode, [String], - [Located String], - [Warn]) -parseModeFlags args = do - ((leftover, errs1, warns), (mModeFlag, units, errs2, flags')) <- - processCmdLineP mode_flags (Nothing, [], [], []) args - let mode = case mModeFlag of - Nothing -> doMakeMode - Just (m, _) -> m - - -- See Note [Handling errors when parsing command-line flags] - unless (null errs1 && null errs2) $ throwGhcException $ errorsToGhcException $ - map (("on the commandline", )) $ map (unLoc . errMsg) errs1 ++ errs2 - - return (mode, units, flags' ++ leftover, warns) - -type ModeM = CmdLineP (Maybe (Mode, String), [String], [String], [Located String]) - -- mode flags sometimes give rise to new DynFlags (eg. -C, see below) - -- so we collect the new ones and return them. - -mode_flags :: [Flag ModeM] -mode_flags = - [ ------- help / version ---------------------------------------------- - defFlag "?" (PassFlag (setMode showGhcUsageMode)) - , defFlag "-help" (PassFlag (setMode showGhcUsageMode)) - , defFlag "V" (PassFlag (setMode showVersionMode)) - , defFlag "-version" (PassFlag (setMode showVersionMode)) - , defFlag "-numeric-version" (PassFlag (setMode showNumVersionMode)) - , defFlag "-info" (PassFlag (setMode showInfoMode)) - , defFlag "-show-options" (PassFlag (setMode showOptionsMode)) - , defFlag "-supported-languages" (PassFlag (setMode showSupportedExtensionsMode)) - , defFlag "-supported-extensions" (PassFlag (setMode showSupportedExtensionsMode)) - , defFlag "-show-packages" (PassFlag (setMode showUnitsMode)) - ] ++ - [ defFlag k' (PassFlag (setMode (printSetting k))) - | k <- ["Project version", - "Project Git commit id", - "Booter version", - "Stage", - "Build platform", - "Host platform", - "Target platform", - "Have interpreter", - "Object splitting supported", - "Have native code generator", - "Support SMP", - "Unregisterised", - "Tables next to code", - "RTS ways", - "Leading underscore", - "Debug on", - "LibDir", - "Global Package DB", - "C compiler flags", - "C compiler link flags" - ], - let k' = "-print-" ++ map (replaceSpace . toLower) k - replaceSpace ' ' = '-' - replaceSpace c = c - ] ++ - ------- interfaces ---------------------------------------------------- - [ defFlag "-show-iface" (HasArg (\f -> setMode (showInterfaceMode f) - "--show-iface")) - - ------- primary modes ------------------------------------------------ - , defFlag "c" (PassFlag (\f -> do setMode (stopBeforeMode NoStop) f - addFlag "-no-link" f)) - , defFlag "M" (PassFlag (setMode doMkDependHSMode)) - , defFlag "E" (PassFlag (setMode (stopBeforeMode StopPreprocess ))) - , defFlag "C" (PassFlag (setMode (stopBeforeMode StopC))) - , defFlag "S" (PassFlag (setMode (stopBeforeMode StopAs))) - , defFlag "-run" (PassFlag (setMode doRunMode)) - , defFlag "-make" (PassFlag (setMode doMakeMode)) - , defFlag "unit" (SepArg (\s -> addUnit s "-unit")) - , defFlag "-backpack" (PassFlag (setMode doBackpackMode)) - , defFlag "-interactive" (PassFlag (setMode doInteractiveMode)) - , defFlag "-abi-hash" (PassFlag (setMode doAbiHashMode)) - , defFlag "e" (SepArg (\s -> setMode (doEvalMode s) "-e")) - , defFlag "-frontend" (SepArg (\s -> setMode (doFrontendMode s) "-frontend")) - ] - -addUnit :: String -> String -> EwM ModeM () -addUnit unit_str _arg = liftEwM $ do - (mModeFlag, units, errs, flags') <- getCmdLineState - putCmdLineState (mModeFlag, unit_str:units, errs, flags') - -setMode :: Mode -> String -> EwM ModeM () -setMode newMode newFlag = liftEwM $ do - (mModeFlag, units, errs, flags') <- getCmdLineState - let (modeFlag', errs') = - case mModeFlag of - Nothing -> ((newMode, newFlag), errs) - Just (oldMode, oldFlag) -> - case (oldMode, newMode) of - -- -c/--make are allowed together, and mean --make -no-link - _ | isStopLnMode oldMode && isDoMakeMode newMode - || isStopLnMode newMode && isDoMakeMode oldMode -> - ((doMakeMode, "--make"), []) - - -- If we have both --help and --interactive then we - -- want showGhciUsage - _ | isShowGhcUsageMode oldMode && - isDoInteractiveMode newMode -> - ((showGhciUsageMode, oldFlag), []) - | isShowGhcUsageMode newMode && - isDoInteractiveMode oldMode -> - ((showGhciUsageMode, newFlag), []) - - -- If we have both -e and --interactive then -e always wins - _ | isDoEvalMode oldMode && - isDoInteractiveMode newMode -> - ((oldMode, oldFlag), []) - | isDoEvalMode newMode && - isDoInteractiveMode oldMode -> - ((newMode, newFlag), []) - - -- Otherwise, --help/--version/--numeric-version always win - | isDominantFlag oldMode -> ((oldMode, oldFlag), []) - | isDominantFlag newMode -> ((newMode, newFlag), []) - -- We need to accumulate eval flags like "-e foo -e bar" - (Right (Right (DoEval esOld)), - Right (Right (DoEval [eNew]))) -> - ((Right (Right (DoEval (eNew : esOld))), oldFlag), - errs) - -- Saying e.g. --interactive --interactive is OK - _ | oldFlag == newFlag -> ((oldMode, oldFlag), errs) - - -- --interactive and --show-options are used together - (Right (Right DoInteractive), Left (ShowOptions _)) -> - ((Left (ShowOptions True), - "--interactive --show-options"), errs) - (Left (ShowOptions _), (Right (Right DoInteractive))) -> - ((Left (ShowOptions True), - "--show-options --interactive"), errs) - -- Otherwise, complain - _ -> let err = flagMismatchErr oldFlag newFlag - in ((oldMode, oldFlag), err : errs) - putCmdLineState (Just modeFlag', units, errs', flags') - where isDominantFlag f = isShowGhcUsageMode f || - isShowGhciUsageMode f || - isShowVersionMode f || - isShowNumVersionMode f - -flagMismatchErr :: String -> String -> String -flagMismatchErr oldFlag newFlag - = "cannot use `" ++ oldFlag ++ "' with `" ++ newFlag ++ "'" - -addFlag :: String -> String -> EwM ModeM () -addFlag s flag = liftEwM $ do - (m, units, e, flags') <- getCmdLineState - putCmdLineState (m, units, e, mkGeneralLocated loc s : flags') - where loc = "addFlag by " ++ flag ++ " on the commandline" - -- ---------------------------------------------------------------------------- -- Run --make mode @@ -786,181 +347,6 @@ initMake srcs = do _ <- GHC.setSessionDynFlags dflags' return hs_srcs --- Strip out any ["+RTS", ..., "-RTS"] sequences in the command string list. -removeRTS :: [String] -> [String] -removeRTS ("+RTS" : xs) = - case dropWhile (/= "-RTS") xs of - [] -> [] - (_ : ys) -> removeRTS ys -removeRTS (y:ys) = y : removeRTS ys -removeRTS [] = [] - -initMulti :: NE.NonEmpty String -> Ghc ([(String, Maybe UnitId, Maybe Phase)]) -initMulti unitArgsFiles = do - hsc_env <- GHC.getSession - let logger = hsc_logger hsc_env - initial_dflags <- GHC.getSessionDynFlags - - dynFlagsAndSrcs <- forM unitArgsFiles $ \f -> do - when (verbosity initial_dflags > 2) (liftIO $ print f) - args <- liftIO $ expandResponse [f] - (dflags2, fileish_args, warns) <- parseDynamicFlagsCmdLine initial_dflags (map (mkGeneralLocated f) (removeRTS args)) - handleSourceError (\e -> do - GHC.printException e - liftIO $ exitWith (ExitFailure 1)) $ do - liftIO $ printOrThrowDiagnostics logger (initPrintConfig dflags2) (initDiagOpts dflags2) (GhcDriverMessage <$> warns) - - let (dflags3, srcs, objs) = parseTargetFiles dflags2 (map unLoc fileish_args) - dflags4 = offsetDynFlags dflags3 - - let (hs_srcs, non_hs_srcs) = partition isHaskellishTarget srcs - - -- This is dubious as the whole unit environment won't be set-up correctly, but - -- that doesn't matter for what we use it for (linking and oneShot) - let dubious_hsc_env = hscSetFlags dflags4 hsc_env - -- if we have no haskell sources from which to do a dependency - -- analysis, then just do one-shot compilation and/or linking. - -- This means that "ghc Foo.o Bar.o -o baz" links the program as - -- we expect. - if (null hs_srcs) - then liftIO (oneShot dubious_hsc_env NoStop srcs) >> return (dflags4, []) - else do - - o_files <- mapMaybeM (\x -> liftIO $ compileFile dubious_hsc_env NoStop x) - non_hs_srcs - let dflags5 = dflags4 { ldInputs = map (FileOption "") o_files - ++ ldInputs dflags4 } - - liftIO $ checkOptions DoMake dflags5 srcs objs [] - - pure (dflags5, hs_srcs) - - let - unitDflags = NE.map fst dynFlagsAndSrcs - srcs = NE.map (\(dflags, lsrcs) -> map (uncurry (,Just $ homeUnitId_ dflags,)) lsrcs) dynFlagsAndSrcs - (hs_srcs, _non_hs_srcs) = unzip (map (partition (\(file, _uid, phase) -> isHaskellishTarget (file, phase))) (NE.toList srcs)) - - checkDuplicateUnits initial_dflags (NE.toList (NE.zip unitArgsFiles unitDflags)) - - (initial_home_graph, mainUnitId) <- liftIO $ createUnitEnvFromFlags unitDflags - let home_units = HUG.allUnits initial_home_graph - - home_unit_graph <- forM initial_home_graph $ \homeUnitEnv -> do - let cached_unit_dbs = homeUnitEnv_unit_dbs homeUnitEnv - hue_flags = homeUnitEnv_dflags homeUnitEnv - dflags = homeUnitEnv_dflags homeUnitEnv - (dbs,unit_state,home_unit,mconstants) <- liftIO $ State.initUnits logger hue_flags cached_unit_dbs home_units - - updated_dflags <- liftIO $ updatePlatformConstants dflags mconstants - emptyHpt <- liftIO $ emptyHomePackageTable - pure $ HomeUnitEnv - { homeUnitEnv_units = unit_state - , homeUnitEnv_unit_dbs = Just dbs - , homeUnitEnv_dflags = updated_dflags - , homeUnitEnv_hpt = emptyHpt - , homeUnitEnv_home_unit = Just home_unit - } - - checkUnitCycles initial_dflags home_unit_graph - - let dflags = homeUnitEnv_dflags $ HUG.unitEnv_lookup mainUnitId home_unit_graph - unitEnv <- assertUnitEnvInvariant <$> (liftIO $ initUnitEnv mainUnitId home_unit_graph (ghcNameVersion dflags) (targetPlatform dflags)) - let final_hsc_env = hsc_env { hsc_unit_env = unitEnv } - - GHC.setSession final_hsc_env - - -- if we have no haskell sources from which to do a dependency - -- analysis, then just do one-shot compilation and/or linking. - -- This means that "ghc Foo.o Bar.o -o baz" links the program as - -- we expect. - if (null hs_srcs) - then do - liftIO $ hPutStrLn stderr $ "Multi Mode can not be used for one-shot mode." - liftIO $ exitWith (ExitFailure 1) - else do - -{- - o_files <- liftIO $ mapMaybeM - (\(src, uid, mphase) -> - compileFile (hscSetActiveHomeUnit (ue_unitHomeUnit (fromJust uid) unitEnv) final_hsc_env) NoStop (src, mphase) - ) - (concat non_hs_srcs) - -} - - -- MP: This should probably modify dflags for each unit? - --let dflags' = dflags { ldInputs = map (FileOption "") o_files - -- ++ ldInputs dflags } - return $ concat hs_srcs - -checkUnitCycles :: DynFlags -> HUG.HomeUnitGraph -> Ghc () -checkUnitCycles dflags graph = processSCCs (HUG.hugSCCs graph) - where - - processSCCs [] = return () - processSCCs (AcyclicSCC _: other_sccs) = processSCCs other_sccs - processSCCs (CyclicSCC uids: _) = throwGhcException $ CmdLineError $ showSDoc dflags (cycle_err uids) - - - cycle_err uids = - hang (text "Units form a dependency cycle:") - 2 - (one_err uids) - - one_err uids = vcat $ - (map (\uid -> text "-" <+> ppr uid <+> text "depends on") start) - ++ [text "-" <+> ppr final] - where - start = init uids - final = last uids - --- | Check that we don't have multiple units with the same UnitId. -checkDuplicateUnits :: DynFlags -> [(FilePath, DynFlags)] -> Ghc () -checkDuplicateUnits dflags flags = - unless (null duplicate_ids) - (throwGhcException $ CmdLineError $ showSDoc dflags multi_err) - - where - uids = map (second homeUnitId_) flags - deduplicated_uids = ordNubOn snd uids - duplicate_ids = Set.fromList (map snd uids \\ map snd deduplicated_uids) - - duplicate_flags = filter (flip Set.member duplicate_ids . snd) uids - - one_err (fp, home_uid) = text "-" <+> ppr home_uid <+> text "defined in" <+> text fp - - multi_err = - hang (text "Multiple units with the same unit-id:") - 2 - (vcat (map one_err duplicate_flags)) - - -offsetDynFlags :: DynFlags -> DynFlags -offsetDynFlags dflags = - dflags { hiDir = c hiDir - , objectDir = c objectDir - , stubDir = c stubDir - , hieDir = c hieDir - , dumpDir = c dumpDir } - - where - c f = augment_maybe (f dflags) - - augment_maybe Nothing = Nothing - augment_maybe (Just f) = Just (augment f) - augment f | isRelative f, Just offset <- workingDirectory dflags = offset </> f - | otherwise = f - - -createUnitEnvFromFlags :: NE.NonEmpty DynFlags -> IO (HomeUnitGraph, UnitId) -createUnitEnvFromFlags unitDflags = do - unitEnvList <- forM unitDflags $ \dflags -> do - emptyHpt <- emptyHomePackageTable - let newInternalUnitEnv = - HUG.mkHomeUnitEnv emptyUnitState Nothing dflags emptyHpt Nothing - return (homeUnitId_ dflags, newInternalUnitEnv) - let activeUnit = fst $ NE.head unitEnvList - return (HUG.hugFromList (NE.toList unitEnvList), activeUnit) - -- --------------------------------------------------------------------------- -- Various banners and verbosity output. @@ -1145,14 +531,3 @@ abiHash strs = do putStrLn (showPpr dflags f) --- ----------------------------------------------------------------------------- --- Util - -unknownFlagsErr :: [String] -> a -unknownFlagsErr fs = throwGhcException $ UsageError $ concatMap oneError fs - where - oneError f = - "unrecognised flag: " ++ f ++ "\n" ++ - (case flagSuggestions (nubSort allNonDeprecatedFlags) f of - [] -> "" - suggs -> "did you mean one of:\n" ++ unlines (map (" " ++) suggs)) ===================================== utils/check-exact/Parsers.hs ===================================== @@ -348,12 +348,14 @@ initDynFlags file = do -- Based on GHC backpack driver doBackPack dflags0 <- GHC.getSessionDynFlags let parser_opts0 = GHC.initParserOpts dflags0 + logger <- GHC.getLogger (_, src_opts) <- GHC.liftIO $ GHC.getOptionsFromFile parser_opts0 (GHC.supportedLanguagePragmas dflags0) file - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 src_opts + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 src_opts -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 @@ -375,13 +377,15 @@ initDynFlagsPure fp s = do -- as long as `parseDynamicFilePragma` is impure there seems to be -- no reason to use it. dflags0 <- GHC.getSessionDynFlags + logger <- GHC.getLogger let parser_opts0 = GHC.initParserOpts dflags0 let (_, pragmaInfo) = GHC.getOptions parser_opts0 (GHC.supportedLanguagePragmas dflags0) (GHC.stringToStringBuffer $ s) fp - (dflags1, _, _) <- GHC.parseDynamicFilePragma dflags0 pragmaInfo + (dflags1, _, _) <- GHC.parseDynamicFilePragma logger dflags0 pragmaInfo -- Turn this on last to avoid T10942 let dflags2 = dflags1 `GHC.gopt_set` GHC.Opt_KeepRawTokenStream -- Prevent parsing of .ghc.environment.* "package environment files" (dflags3, _, _) <- GHC.parseDynamicFlagsCmdLine + logger dflags2 [GHC.noLoc "-hide-all-packages"] _ <- GHC.setSessionDynFlags dflags3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3c619b43fcf950dfef646e52282d30918534142e...710ba89fba258007b6075aba9931e821cdd45f75 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3c619b43fcf950dfef646e52282d30918534142e...710ba89fba258007b6075aba9931e821cdd45f75 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/1120636e/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 11:46:29 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 14 Mar 2025 07:46:29 -0400 Subject: [Git][ghc/ghc][wip/refactor-iface] iface: Store logical parts of ModIface together Message-ID: <67d4171545a64_21899f3b559c181e2@gitlab.mail> Matthew Pickering pushed to branch wip/refactor-iface at Glasgow Haskell Compiler / GHC Commits: 9d84972f by Matthew Pickering at 2025-03-14T11:06:06+00:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore ------------------------- - - - - - 17 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - ghc/Main.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -100,29 +100,37 @@ module GHC ( findGlobalAnns, mkNamePprCtxForModule, ModIface, - ModIface_( - mi_module, - mi_sig_of, - mi_hsc_src, - mi_hi_bytes, - mi_deps, - mi_exports, - mi_fixities, - mi_warns, - mi_anns, - mi_insts, - mi_fam_insts, - mi_rules, - mi_decls, - mi_extra_decls, - mi_top_env, - mi_trust, - mi_trust_pkg, - mi_complete_matches, - mi_docs, - mi_final_exts, - mi_ext_fields - ), + ModIface_( mi_mod_info + , mi_module + , mi_sig_of + , mi_hsc_src + , mi_iface_hash + , mi_deps + , mi_public + , mi_exports + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_defaults + , mi_simplified_core + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_abi_hashes + , mi_ext_fields + , mi_hi_bytes + , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn + ), pattern ModIface, SafeHaskellMode(..), ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -844,7 +844,7 @@ hscRecompStatus case recomp_if_result of OutOfDateItem reason mb_checked_iface -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ fmap (mi_iface_hash . mi_final_exts) mb_checked_iface + return $ HscRecompNeeded $ fmap mi_iface_hash mb_checked_iface UpToDateItem checked_iface -> do let lcl_dflags = ms_hspp_opts mod_summary if | not (backendGeneratesCode (backend lcl_dflags)) -> do @@ -862,7 +862,7 @@ hscRecompStatus , xopt LangExt.TemplateHaskell lcl_dflags -> do msg $ needsRecompileBecause THWithJS - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface | otherwise -> do -- Do need linkable @@ -918,7 +918,7 @@ hscRecompStatus return $ HscUpToDate checked_iface $ linkable OutOfDateItem reason _ -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface -- | Check that the .o files produced by compilation are already up-to-date -- or not. @@ -968,10 +968,8 @@ loadByteCode iface mod_sum = do let this_mod = ms_mod mod_sum if_date = fromJust $ ms_iface_date mod_sum - case mi_extra_decls iface of - Just extra_decls -> do - let fi = WholeCoreBindings extra_decls this_mod (ms_location mod_sum) - (mi_foreign iface) + case iface_core_bindings iface (ms_location mod_sum) of + Just fi -> do return (UpToDateItem (Linkable if_date this_mod (NE.singleton (CoreBindings fi)))) _ -> return $ outOfDateItemBecause MissingBytecode Nothing @@ -1019,15 +1017,15 @@ compile_for_interpreter hsc_env use = -- | Assemble 'WholeCoreBindings' if the interface contains Core bindings. iface_core_bindings :: ModIface -> ModLocation -> Maybe WholeCoreBindings iface_core_bindings iface wcb_mod_location = - mi_extra_decls <&> \ wcb_bindings -> + mi_simplified_core <&> \(IfaceSimplifiedCore bindings foreign') -> WholeCoreBindings { - wcb_bindings, + wcb_bindings = bindings, wcb_module = mi_module, wcb_mod_location, - wcb_foreign = mi_foreign + wcb_foreign = foreign' } where - ModIface {mi_module, mi_extra_decls, mi_foreign} = iface + ModIface {mi_module, mi_simplified_core} = iface -- | Return an 'IO' that hydrates Core bindings and compiles them to bytecode if -- the interface contains any, using the supplied type env for typechecking. @@ -1376,7 +1374,7 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do -- dynamic interfaces. Hopefully both the dynamic and the non-dynamic -- interfaces stay in sync... -- - let change = old_iface /= Just (mi_iface_hash (mi_final_exts iface)) + let change = old_iface /= Just (mi_iface_hash iface) let dt = dynamicTooState dflags ===================================== compiler/GHC/HsToCore/Usage.hs ===================================== @@ -185,7 +185,7 @@ mkObjectUsage pit plugins fc hug th_links_needed th_pkgs_needed = do case miface of Nothing -> pprPanic "mkObjectUsage" (ppr m) Just iface -> - return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash (mi_final_exts iface)) + return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash iface) librarySpecToUsage :: LibrarySpec -> IO [Usage] librarySpecToUsage (Objects os) = traverse (fing Nothing) os @@ -278,10 +278,10 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names usg_entities = Map.toList ent_hashs, usg_safe = imp_safe } where - finsts_mod = mi_finsts (mi_final_exts iface) - hash_env = mi_hash_fn (mi_final_exts iface) - mod_hash = mi_mod_hash (mi_final_exts iface) - export_hash | depend_on_exports = Just (mi_exp_hash (mi_final_exts iface)) + finsts_mod = mi_finsts iface + hash_env = mi_hash_fn iface + mod_hash = mi_mod_hash iface + export_hash | depend_on_exports = Just (mi_exp_hash iface) | otherwise = Nothing by_is_safe (ImportedByUser imv) = imv_is_safe imv ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -41,34 +41,28 @@ data IfaceDynFlags = IfaceDynFlags , ifaceCallerCCFilters :: [CallerCcFilter] } -pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc -pprIfaceDynFlags (f, mflags) = - vcat $ - [ text "fingerprint:" <+> (ppr f) - ] - ++ case mflags of - Nothing -> [missingExtraFlagInfo] - Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> - [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) - , text "safe-mode:" <+> ppr a2 - , text "lang:" <+> ppr a3 - , text "exts:" <+> ppr a4 - , text "cpp-options:" - , nest 2 $ ppr a5 - , text "js-options:" - , nest 2 $ ppr a6 - , text "cmm-options:" - , nest 2 $ ppr a7 - , text "paths:" <+> hcat (map text a8) - , text "prof:" <+> ppr a9 - , text "ticky:" - , nest 2 $ vcat (map ppr a10) - , text "codegen:" - , nest 2 $ vcat (map ppr a11) - , text "fat-iface:" <+> ppr a12 - , text "debug-level:" <+> ppr a13 - , text "caller-cc-filters:" <+> ppr a14 - ] +pprIfaceDynFlags :: IfaceDynFlags -> SDoc +pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + vcat [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] missingExtraFlagInfo :: SDoc missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,7 +59,6 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields -import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -74,7 +73,6 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Logger -import GHC.Utils.Fingerprint( Fingerprint ) import GHC.Settings.Constants @@ -644,7 +642,7 @@ loadInterface doc_str mod from & set_mi_fam_insts (panic "No mi_fam_insts in PIT") & set_mi_rules (panic "No mi_rules in PIT") & set_mi_anns (panic "No mi_anns in PIT") - & set_mi_extra_decls (panic "No mi_extra_decls in PIT") + & set_mi_simplified_core (panic "No mi_simplified_core in PIT") bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1083,7 +1081,7 @@ load_dynamic_too :: Logger -> NameCache -> UnitState -> DynFlags load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do read_file logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case Succeeded (dynIface, _) - | mi_mod_hash (mi_final_exts iface) == mi_mod_hash (mi_final_exts dynIface) + | mi_mod_hash iface == mi_mod_hash dynIface -> return (Succeeded ()) | otherwise -> do return $ (Failed $ DynamicHashMismatchError wanted_mod loc) @@ -1174,11 +1172,10 @@ ghcPrimIface & set_mi_exports ghcPrimExports & set_mi_decls [] & set_mi_fixities ghcPrimFixities - & set_mi_final_exts ((mi_final_exts empty_iface) - { mi_fix_fn = mkIfaceFixCache ghcPrimFixities - , mi_decl_warn_fn = mkIfaceDeclWarnCache ghcPrimWarns - , mi_export_warn_fn = mkIfaceExportWarnCache ghcPrimWarns - }) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) + & set_mi_decl_warn_fn (mkIfaceDeclWarnCache ghcPrimWarns) + & set_mi_export_warn_fn (mkIfaceExportWarnCache ghcPrimWarns) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] in GHC.Builtin.Utils & set_mi_warns (toIfaceWarnings ghcPrimWarns) -- See Note [GHC.Prim Deprecations] in GHC.Builtin.Utils @@ -1263,21 +1260,14 @@ pprModIface unit_state iface = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") - <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) - <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) + <+> (if mi_orphan iface then text "[orphan module]" else Outputable.empty) + <+> (if mi_finsts iface then text "[family instance module]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) - , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) - , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat - [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) - , nest 2 (text "opt_hash:" <+> ppr opt_hash) - , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) - , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) - , vcat (map pprUsage usages) - ] - , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) + , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash iface)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash iface)) + , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash iface)) + , withSelfRecomp iface empty ppr + , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "where") , text "exports:" @@ -1288,10 +1278,14 @@ pprModIface unit_state iface , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] - , case mi_extra_decls iface of + , case mi_simplified_core iface of Nothing -> empty - Just eds -> text "extra decls:" - $$ nest 2 (vcat ([ppr bs | bs <- eds])) + Just (IfaceSimplifiedCore eds fs) -> + vcat [ text "extra decls:" + $$ nest 2 (vcat ([ppr bs | bs <- eds])) + , text "foreign stubs:" + $$ nest 2 (ppr fs) + ] , vcat (map ppr (mi_insts iface)) , vcat (map ppr (mi_fam_insts iface)) , vcat (map ppr (mi_rules iface)) @@ -1303,7 +1297,6 @@ pprModIface unit_state iface , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where - exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" @@ -1329,35 +1322,6 @@ pprExport avail@(AvailTC n _) = pp_export [] = Outputable.empty pp_export names = braces (hsep (map ppr names)) -pprUsage :: Usage -> SDoc -pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } - = pprUsageImport mod hash safe -pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name - , usg_mod_hash = hash, usg_safe = safe - , usg_exports = exports, usg_entities = entities } - = pprUsageImport (mkModule unit_id mod_name) hash safe $$ - nest 2 ( - maybe Outputable.empty (\v -> text "exports: " <> ppr v) exports $$ - vcat [ ppr n <+> ppr v | (n,v) <- entities ] - ) -pprUsage usage at UsageFile{} - = hsep [text "addDependentFile", - doubleQuotes (ftext (usg_file_path usage)), - ppr (usg_file_hash usage)] -pprUsage usage at UsageMergedRequirement{} - = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] -pprUsage usage at UsageHomeModuleInterface{} - = hsep [text "implementation", ppr (usg_mod_name usage) - , ppr (usg_unit_id usage) - , ppr (usg_iface_hash usage)] - -pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc -pprUsageImport mod hash safe - = hsep [ text "import", pp_safe, ppr mod - , ppr hash ] - where - pp_safe | safe = text "safe" - | otherwise = text " -/ " pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -88,13 +88,13 @@ import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModSummary import GHC.Unit.Module.Deps -import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign, emptyIfaceForeign) import Data.Function import Data.List ( sortBy ) import Data.Ord import Data.IORef - +import Data.Traversable {- ************************************************************************ @@ -143,11 +143,13 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos stubs foreign_files = updateDecl (mi_decls partial_iface) mb_stg_infos mb_cmm_infos -- See Note [Foreign stubs and TH bytecode linking] - foreign_ <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + mi_simplified_core <- for (mi_simplified_core partial_iface) $ \simpl_core -> do + fs <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + return $ (simpl_core { mi_sc_foreign = fs }) full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env $ set_mi_foreign foreign_ $ set_mi_decls decls partial_iface + addFingerprints hsc_env $ set_mi_simplified_core mi_simplified_core $ set_mi_decls decls partial_iface -- Debug printing let unit_state = hsc_units hsc_env @@ -289,7 +291,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode - -> Maybe ModIfaceSelfRecomp + -> Maybe IfaceSelfRecomp -> Maybe Docs -> ModDetails -> PartialModIface @@ -316,8 +318,8 @@ mkIface_ hsc_env entities = typeEnvElts type_env show_linear_types = xopt LangExt.LinearTypes (hsc_dflags hsc_env) - extra_decls = if gopt Opt_WriteIfSimplifiedCore dflags then Just [ toIfaceTopBind b | b <- core_prog ] - else Nothing + simplified_core = if gopt Opt_WriteIfSimplifiedCore dflags then Just (IfaceSimplifiedCore [ toIfaceTopBind b | b <- core_prog ] emptyIfaceForeign) + else Nothing decls = [ tyThingToIfaceDecl show_linear_types entity | entity <- entities, let name = getName entity, @@ -370,12 +372,12 @@ mkIface_ hsc_env & set_mi_anns annotations & set_mi_top_env rdrs & set_mi_decls decls - & set_mi_extra_decls extra_decls + & set_mi_simplified_core simplified_core & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) & set_mi_docs docs - & set_mi_final_exts () + & set_mi_abi_hashes () & set_mi_ext_fields emptyExtensibleFields & set_mi_hi_bytes PartialIfaceBinHandle ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -88,6 +88,7 @@ import Data.Ord import Data.Containers.ListUtils import Data.Bifunctor import GHC.Iface.Errors.Ppr +import Data.Functor {- ----------------------------------------------- @@ -325,8 +326,8 @@ check_old_iface hsc_env mod_summary maybe_iface maybe_dyn_iface <- liftIO $ loadIface (setDynamicNow dflags) (msDynHiFilePath mod_summary) case maybe_dyn_iface of Nothing -> return $ outOfDateItemBecause MissingDynHiFile Nothing - Just dyn_iface | mi_iface_hash (mi_final_exts dyn_iface) - /= mi_iface_hash (mi_final_exts normal_iface) + Just dyn_iface | mi_iface_hash dyn_iface + /= mi_iface_hash normal_iface -> return $ outOfDateItemBecause MismatchedDynHiFile Nothing Just {} -> return res _ -> return res @@ -382,7 +383,7 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface - -> ModIfaceSelfRecomp + -> IfaceSelfRecomp -> IfG (MaybeValidated ModIface) checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger @@ -435,7 +436,7 @@ checkVersions hsc_env mod_summary iface self_recomp -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins :: Plugins -> IfaceSelfRecomp -> IfG RecompileRequired checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp @@ -528,10 +529,10 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash :: HscEnv -> Module -> IfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + let FingerprintWithValue old_fp old_flags = mi_sr_flag_hash self_recomp (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally if old_fp == new_fp then up_to_date logger (text "Module flags unchanged") @@ -573,7 +574,7 @@ checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkOptimHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env let old_hash = mi_sr_opt_hash iface @@ -589,7 +590,7 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env let old_hash = mi_sr_hpc_hash self_recomp @@ -606,7 +607,7 @@ checkHpcHash hsc_env self_recomp = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures :: HscEnv -> ModSummary -> IfaceSelfRecomp -> IO RecompileRequired checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env @@ -748,7 +749,7 @@ checkModUsage _ UsagePackageModule{ logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChanged (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) -- We only track the ABI hash of package modules, rather than -- individual entity usages, so if the ABI hash changes we must -- recompile. This is safe but may entail more recompilation when @@ -758,7 +759,7 @@ checkModUsage _ UsageMergedRequirement{ usg_mod = mod, usg_mod_hash = old_mod_ha logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedRaw (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name , usg_unit_id = uid , usg_iface_hash = old_mod_hash } = do @@ -766,7 +767,7 @@ checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedIface mod_name - checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash (mi_final_exts iface)) + checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash iface) checkModUsage _ UsageHomeModule{ usg_mod_name = mod_name, @@ -779,9 +780,9 @@ checkModUsage _ UsageHomeModule{ logger <- getLogger needInterface mod $ \iface -> do let - new_mod_hash = mi_mod_hash (mi_final_exts iface) - new_decl_hash = mi_hash_fn (mi_final_exts iface) - new_export_hash = mi_exp_hash (mi_final_exts iface) + new_mod_hash = mi_mod_hash iface + new_decl_hash = mi_hash_fn iface + new_export_hash = mi_exp_hash iface reason = ModuleChanged (moduleName mod) @@ -986,7 +987,7 @@ we use is: -- | Compute the information needed for self-recompilation checking. This -- information can be computed before the backend phase. -mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO IfaceSelfRecomp mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env @@ -1000,10 +1001,10 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do let include_detailed_flags (flag_hash, flags) = if gopt Opt_WriteSelfRecompFlags dflags - then (flag_hash, Just flags) - else (flag_hash, Nothing) + then FingerprintWithValue flag_hash (Just flags) + else FingerprintWithValue flag_hash Nothing - return (ModIfaceSelfRecomp + return (IfaceSelfRecomp { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash @@ -1018,28 +1019,92 @@ addFingerprints :: HscEnv -> PartialModIface -> IO ModIface -addFingerprints hsc_env iface0 - = do - eps <- hscEPS hsc_env - let - decls = mi_decls iface0 - decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings $ mi_warns iface0) - export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ mi_warns iface0) - fix_fn = mkIfaceFixCache (mi_fixities iface0) +addFingerprints hsc_env iface0 = do + (abiHashes, caches, decls_w_hashes) <- addAbiHashes hsc_env (mi_mod_info iface0) (mi_public iface0) (mi_deps iface0) + + -- put the declarations in a canonical order, sorted by OccName + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ + [(getOccName d, e) | e@(_, d) <- decls_w_hashes] + + -- This key is safe because mi_extra_decls contains tidied things. + getOcc (IfGblTopBndr b) = getOccName b + getOcc (IfLclTopBndr fs _ _ details) = + case details of + IfRecSelId { ifRecSelFirstCon = first_con } + -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) + _ -> mkVarOccFS (ifLclNameFS fs) + + binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () + binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) + + sorted_extra_decls :: Maybe IfaceSimplifiedCore + sorted_extra_decls = mi_simplified_core iface0 <&> \simpl_core -> + IfaceSimplifiedCore (sortOn binding_key (mi_sc_extra_decls simpl_core)) (mi_sc_foreign simpl_core) + + -- The interface hash depends on: + -- - the ABI hash, plus + -- - the things which can affect whether a module is recompiled + -- - the module level annotations, + -- - deps (home and external packages, dependent files) + iface_hash <- computeFingerprint putNameLiterally + (mi_abi_mod_hash abiHashes, + mi_self_recomp_info iface0, + mi_deps iface0) + + let final_iface = completePartialModIface iface0 iface_hash + sorted_decls sorted_extra_decls abiHashes caches + -- + return final_iface + + + +-- The ABI hash should depend on everything in IfacePublic +-- This is however computed in a very convoluted way, so be careful your +-- addition ends up in the right place. In essence all this function does is +-- compute a hash of the arguments. +-- +-- Why the convoluted way? Hashing individual declarations allows us to do fine-grained +-- recompilation checking for home package modules, which record precisely what they use +-- from each module. +addAbiHashes :: HscEnv -> IfaceModInfo -> PartialIfacePublic -> Dependencies -> IO (IfaceAbiHashes, IfaceCache, [(Fingerprint, IfaceDecl)]) +addAbiHashes hsc_env info iface_public deps = do + eps <- hscEPS hsc_env + let + -- If you have arrived here by accident then congratulations, + -- you have discovered the ABI hash. Your reward is to update the ABI hash to + -- account for your change to the interface file. Omitting your field using a + -- wildcard may lead to some unfortunate consequences. + + -- MP: TODO: Existing bug where defaults, trust_pkg and complete are not taken into account + -- when computing the ABI hash. + IfacePublic exports fixities warns anns decls _defaults insts fam_insts rules trust _trust_pkg _complete _cache () = iface_public + -- And these fields of deps should be in IfacePublic, but in good time. + Dependencies _ _ _ sig_mods trusted_pkgs boot_mods orph_mods fis_mods = deps + decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings warns) + export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ warns) + fix_fn = mkIfaceFixCache fixities + + this_mod = mi_mod_info_module info + semantic_mod = mi_mod_info_semantic_module info + (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph insts + (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph rules + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph fam_insts + ann_fn = mkIfaceAnnCache anns -- The ABI of a declaration represents everything that is made -- visible about the declaration that a client can depend on. -- see IfaceDeclABI below. - declABI :: IfaceDecl -> IfaceDeclABI + declABI :: IfaceDecl -> IfaceDeclABI -- TODO: I'm not sure if this should be semantic_mod or this_mod. -- See also Note [Identity versus semantic module] - declABI decl = (this_mod, decl, extras) + declABI decl = (this_mod, decl, extras) where extras = declExtras fix_fn ann_fn non_orph_rules non_orph_insts non_orph_fis top_lvl_name_env decl -- This is used for looking up the Name of a default method -- from its OccName. See Note [default method Name] - top_lvl_name_env = + top_lvl_name_env = mkOccEnv [ (nameOccName nm, nm) | IfaceId { ifName = nm } <- decls ] @@ -1047,15 +1112,15 @@ addFingerprints hsc_env iface0 -- This is computed by finding the free external names of each -- declaration, including IfaceDeclExtras (things that a -- declaration implicitly depends on). - edges :: [ Node OccName IfaceDeclABI ] - edges = [ DigraphNode abi (getOccName decl) out + edges :: [ Node OccName IfaceDeclABI ] + edges = [ DigraphNode abi (getOccName decl) out | decl <- decls , let abi = declABI decl , let out = localOccs $ freeNamesDeclABI abi ] - name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) - localOccs = + name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) + localOccs = map (getParent . getOccName) -- NB: names always use semantic module, so -- filtering must be on the semantic module! @@ -1073,17 +1138,17 @@ addFingerprints hsc_env iface0 -- maps OccNames to their parents in the current module. -- e.g. a reference to a constructor must be turned into a reference -- to the TyCon for the purposes of calculating dependencies. - parent_map :: OccEnv OccName - parent_map = foldl' extend emptyOccEnv decls + parent_map :: OccEnv OccName + parent_map = foldl' extend emptyOccEnv decls where extend env d = extendOccEnvList env [ (b,n) | b <- ifaceDeclImplicitBndrs d ] where n = getOccName d -- Strongly-connected groups of declarations, in dependency order - groups :: [SCC IfaceDeclABI] - groups = stronglyConnCompFromEdgedVerticesOrd edges + groups :: [SCC IfaceDeclABI] + groups = stronglyConnCompFromEdgedVerticesOrd edges - global_hash_fn = mkHashFun hsc_env eps + global_hash_fn = mkHashFun hsc_env eps -- How to output Names when generating the data to fingerprint. -- Here we want to output the fingerprint for each top-level @@ -1091,9 +1156,9 @@ addFingerprints hsc_env iface0 -- module. In this way, the fingerprint for a declaration will -- change if the fingerprint for anything it refers to (transitively) -- changes. - mk_put_name :: OccEnv (OccName,Fingerprint) + mk_put_name :: OccEnv (OccName,Fingerprint) -> WriteBinHandle -> Name -> IO () - mk_put_name local_env bh name + mk_put_name local_env bh name | isWiredInName name = putNameLiterally bh name -- wired-in names don't have fingerprints | otherwise @@ -1120,21 +1185,21 @@ addFingerprints hsc_env iface0 -- take a strongly-connected group of declarations and compute -- its fingerprint. - fingerprint_group :: (OccEnv (OccName,Fingerprint), + fingerprint_group :: (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) -> SCC IfaceDeclABI -> IO (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) - fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) - = do let hash_fn = mk_put_name local_env - decl = abiDecl abi + fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) + = do let hash_fn = mk_put_name local_env + decl = abiDecl abi --pprTrace "fingerprinting" (ppr (ifName decl) ) $ do - hash <- computeFingerprint hash_fn abi - env' <- extend_hash_env local_env (hash,decl) - return (env', (hash,decl) : decls_w_hashes) + hash <- computeFingerprint hash_fn abi + env' <- extend_hash_env local_env (hash,decl) + return (env', (hash,decl) : decls_w_hashes) - fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) + fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) = do let stable_abis = sortBy cmp_abiNames abis stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env @@ -1150,33 +1215,27 @@ addFingerprints hsc_env iface0 return (local_env2, pairs ++ decls_w_hashes) -- Make a fingerprint from the ordinal position of a binding in its group. - mkRecFingerprint :: Word64 -> Fingerprint - mkRecFingerprint i = Fingerprint 0 i + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i - bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint - bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. -- - extend_hash_env :: OccEnv (OccName,Fingerprint) + extend_hash_env :: OccEnv (OccName,Fingerprint) -> (Fingerprint,IfaceDecl) -> IO (OccEnv (OccName,Fingerprint)) - extend_hash_env env0 (hash,d) = + extend_hash_env env0 (hash,d) = return (foldr (\(b,fp) env -> extendOccEnv env b (b,fp)) env0 (ifaceDeclFingerprints hash d)) -- - (local_env, decls_w_hashes) <- + (local_env, decls_w_hashes) <- foldM fingerprint_group (emptyOccEnv, []) groups - -- when calculating fingerprints, we always need to use canonical ordering - -- for lists of things. The mi_deps has various lists of modules and - -- suchlike, which are stored in canonical order: - let sorted_deps :: Dependencies - sorted_deps = mi_deps iface0 - -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way -- that changes in orphans get propagated all the way up the @@ -1202,10 +1261,11 @@ addFingerprints hsc_env iface0 -- External. It's true that Home1 will get rebuilt if the orphans -- of External, but we also need to make sure Home2 gets rebuilt -- as well. See #12733 for more details. - let orph_mods - = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] - $ dep_orphs sorted_deps - dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods + let orph_mods_no_self + = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] + $ orph_mods + dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods_no_self + -- Note [Do not update EPS with your own hi-boot] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1216,26 +1276,26 @@ addFingerprints hsc_env iface0 -- instances yourself, no need to consult hs-boot; if you do load the -- interface into EPS, you will see a duplicate orphan instance. - orphan_hash <- computeFingerprint (mk_put_name local_env) + orphan_hash <- computeFingerprint (mk_put_name local_env) (map ifDFun orph_insts, orph_rules, orph_fis) - -- Hash of the transitive things in dependencies - dep_hash <- computeFingerprint putNameLiterally - (dep_sig_mods (mi_deps iface0), - dep_boot_mods (mi_deps iface0), - -- Trusted packages are like orphans - dep_trusted_pkgs (mi_deps iface0), + -- Hash of the transitive things in dependencies + dep_hash <- computeFingerprint putNameLiterally + (sig_mods, + boot_mods, + -- Trusted packages are like orphans + trusted_pkgs, -- See Note [Export hash depends on non-orphan family instances] - dep_finsts (mi_deps iface0) ) + fis_mods ) - -- the export list hash doesn't depend on the fingerprints of - -- the Names it mentions, only the Names themselves, hence putNameLiterally. - export_hash <- computeFingerprint putNameLiterally - (mi_exports iface0, + -- the export list hash doesn't depend on the fingerprints of + -- the Names it mentions, only the Names themselves, hence putNameLiterally. + export_hash <- computeFingerprint putNameLiterally + (exports, orphan_hash, dep_hash, dep_orphan_hashes, - mi_trust iface0) + trust) -- Make sure change of Safe Haskell mode causes recomp. -- Note [Export hash depends on non-orphan family instances] @@ -1266,79 +1326,44 @@ addFingerprints hsc_env iface0 -- (also we didn't store it anywhere!) -- - -- put the declarations in a canonical order, sorted by OccName - let sorted_decls :: [(Fingerprint, IfaceDecl)] - sorted_decls = Map.elems $ Map.fromList $ - [(getOccName d, e) | e@(_, d) <- decls_w_hashes] - -- This key is safe because mi_extra_decls contains tidied things. - getOcc (IfGblTopBndr b) = getOccName b - getOcc (IfLclTopBndr fs _ _ details) = - case details of - IfRecSelId { ifRecSelFirstCon = first_con } - -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) - _ -> mkVarOccFS (ifLclNameFS fs) - - binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () - binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) - - sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - - -- the ABI hash depends on: - -- - decls - -- - export list - -- - orphans - -- - deprecations - -- - flag abi hash - -- - foreign stubs and files - mod_hash <- computeFingerprint putNameLiterally - (map fst sorted_decls, + -- the ABI hash depends on: + -- - decls + -- - export list + -- - orphans + -- - deprecations + -- - flag abi hash + mod_hash <- computeFingerprint putNameLiterally + (sort (map fst decls_w_hashes), export_hash, -- includes orphan_hash - mi_warns iface0, - mi_foreign iface0) - - - -- The interface hash depends on: - -- - the ABI hash, plus - -- - the things which can affect whether a module is recompiled - -- - the module level annotations, - -- - deps (home and external packages, dependent files) - iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_self_recomp_info iface0, - sorted_deps ) + ann_fn AnnModule, + warns) - let - final_iface_exts = ModIfaceBackend - { mi_mod_hash = mod_hash - , mi_iface_hash = iface_hash - , mi_orphan = not ( all ifRuleAuto orph_rules + -- Surely the ABI depends on "module" annotations? + -- Also named defaults + + + + let + final_iface_exts = IfaceAbiHashes + { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts && null orph_fis) - , mi_finsts = not (null (mi_fam_insts iface0)) - , mi_exp_hash = export_hash - , mi_orphan_hash = orphan_hash - , mi_decl_warn_fn = decl_warn_fn - , mi_export_warn_fn = export_warn_fn - , mi_fix_fn = fix_fn - , mi_hash_fn = lookupOccEnv local_env + , mi_abi_finsts = not (null fam_insts) + , mi_abi_exp_hash = export_hash + , mi_abi_orphan_hash = orphan_hash } - final_iface = completePartialModIface iface0 - sorted_decls sorted_extra_decls final_iface_exts - -- - return final_iface + caches = IfaceCache + { mi_cache_decl_warn_fn = decl_warn_fn + , mi_cache_export_warn_fn = export_warn_fn + , mi_cache_fix_fn = fix_fn + , mi_cache_hash_fn = lookupOccEnv local_env + } + return (final_iface_exts, caches, decls_w_hashes) where - this_mod = mi_module iface0 - semantic_mod = mi_semantic_module iface0 - (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) - (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) - (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - ann_fn = mkIfaceAnnCache (mi_anns iface0) - -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the @@ -1378,7 +1403,7 @@ getOrphanHashes hsc_env mods = do get_orph_hash mod = do iface <- initIfaceLoad hsc_env . withIfaceErr ctx $ loadInterface (text "getOrphanHashes") mod ImportBySystem - return (mi_orphan_hash (mi_final_exts iface)) + return (mi_orphan_hash iface) mapM get_orph_hash mods @@ -1531,7 +1556,7 @@ instance Binary IfaceIdExtras where put_ bh (IdExtras fix rules anns)= do { put_ bh fix; put_ bh rules; put_ bh anns } declExtras :: (OccName -> Maybe Fixity) - -> (OccName -> [AnnPayload]) + -> (AnnCacheKey -> [AnnPayload]) -> OccEnv [IfaceRule] -> OccEnv [IfaceClsInst] -> OccEnv [IfaceFamInst] @@ -1546,10 +1571,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl IfaceDataExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n) ++ map ifDFun (lookupOccEnvL inst_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) (map (id_extras . occName . ifConName) (visibleIfConDecls cons)) IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} -> - IfaceClassExtras (fix_fn n) insts (ann_fn n) meths defms + IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms where insts = (map ifDFun $ (concatMap at_extras ats) ++ lookupOccEnvL inst_env n) @@ -1562,17 +1587,16 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl , let dmOcc = mkDefaultMethodOcc (nameOccName bndr) , Just dmName <- [lookupOccEnv dm_env dmOcc] ] IfaceSynonym{} -> IfaceSynonymExtras (fix_fn n) - (ann_fn n) + (ann_fn (AnnOccName n)) IfaceFamily{} -> IfaceFamilyExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) _other -> IfaceOtherDeclExtras where n = getOccName decl - id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn occ) + id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl) - {- Note [default method Name] (see also #15970) ~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1685,20 +1709,25 @@ mkHashFun hsc_env eps name -- just one of the many horrible hacks in the backpack -- implementation. $ loadInterface (text "lookupVers2") mod ImportBySystem - return $ snd (mi_hash_fn (mi_final_exts iface) occ `orElse` + return $ snd (mi_hash_fn iface occ `orElse` pprPanic "lookupVers1" (ppr mod <+> ppr occ)) +data AnnCacheKey = AnnModule | AnnOccName OccName + -- | Creates cached lookup for the 'mi_anns' field of ModIface -- Hackily, we use "module" as the OccName for any module-level annotations -mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload] +mkIfaceAnnCache :: [IfaceAnnotation] -> AnnCacheKey -> [AnnPayload] mkIfaceAnnCache anns - = \n -> lookupOccEnv env n `orElse` [] + = \n -> case n of + AnnModule -> module_anns + AnnOccName occn -> lookupOccEnv env occn `orElse` [] where - pair (IfaceAnnotation target value) = - (case target of - NamedTarget occn -> occn - ModuleTarget _ -> mkVarOccFS (fsLit "module") - , [value]) + (module_anns, occ_anns) = partitionEithers $ map classify anns + classify (IfaceAnnotation target value) = + case target of + NamedTarget occn -> Right (occn, [value]) + ModuleTarget _ -> Left value + -- flipping (++), so the first argument is always short - env = mkOccEnv_C (flip (++)) (map pair anns) + env = mkOccEnv_C (flip (++)) occ_anns ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,5 +1,5 @@ module GHC.Iface.Recomp.Types ( - ModIfaceSelfRecomp(..), + IfaceSelfRecomp(..), IfaceDynFlags(..), pprIfaceDynFlags, missingExtraFlagInfo, @@ -9,7 +9,9 @@ import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable import GHC.Iface.Flags +import GHC.Types.SafeHaskell import GHC.Unit.Module.Deps +import GHC.Unit.Module import GHC.Utils.Binary @@ -59,8 +61,8 @@ proper way. -- itself. -- -- See Note [Self recompilation information in interface files] -data ModIfaceSelfRecomp = - ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint +data IfaceSelfRecomp = + IfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint -- ^ Hash of the .hs source, used for recompilation checking. , mi_sr_usages :: [Usage] -- ^ Usages; kept sorted so that it's easy to decide @@ -69,7 +71,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) + , mi_sr_flag_hash :: !(FingerprintWithValue IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -81,8 +83,8 @@ data ModIfaceSelfRecomp = } -instance Binary ModIfaceSelfRecomp where - put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do +instance Binary IfaceSelfRecomp where + put_ bh (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do put_ bh mi_sr_src_hash lazyPut bh mi_sr_usages put_ bh mi_sr_flag_hash @@ -97,19 +99,58 @@ instance Binary ModIfaceSelfRecomp where opt_hash <- get bh hpc_hash <- get bh plugin_hash <- get bh - return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + return $ IfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } -instance Outputable ModIfaceSelfRecomp where - ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) +instance Outputable IfaceSelfRecomp where + ppr (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash - , text "usages:" <+> ppr (length mi_sr_usages) - , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash + , text "flags:" <+> pprFingerprintWithValue missingExtraFlagInfo (fmap pprIfaceDynFlags mi_sr_flag_hash) , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash + , text "usages:" <+> ppr (map pprUsage mi_sr_usages) ])] -instance NFData ModIfaceSelfRecomp where - rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file +instance NFData IfaceSelfRecomp where + rnf (IfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () + +pprFingerprintWithValue :: SDoc -> FingerprintWithValue SDoc -> SDoc +pprFingerprintWithValue missingInfo (FingerprintWithValue fp mflags) + = vcat $ + [ text "fingerprint:" <+> (ppr fp) + ] + ++ case mflags of + Nothing -> [missingInfo] + Just doc -> [doc] + +pprUsage :: Usage -> SDoc +pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } + = pprUsageImport mod hash safe +pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name + , usg_mod_hash = hash, usg_safe = safe + , usg_exports = exports, usg_entities = entities } + = pprUsageImport (mkModule unit_id mod_name) hash safe $$ + nest 2 ( + maybe empty (\v -> text "exports: " <> ppr v) exports $$ + vcat [ ppr n <+> ppr v | (n,v) <- entities ] + ) +pprUsage usage at UsageFile{} + = hsep [text "addDependentFile", + doubleQuotes (ftext (usg_file_path usage)), + ppr (usg_file_hash usage)] +pprUsage usage at UsageMergedRequirement{} + = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] +pprUsage usage at UsageHomeModuleInterface{} + = hsep [text "implementation", ppr (usg_mod_name usage) + , ppr (usg_unit_id usage) + , ppr (usg_iface_hash usage)] + +pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc +pprUsageImport mod hash safe + = hsep [ text "import", pp_safe, ppr mod + , ppr hash ] + where + pp_safe | safe = text "safe" + | otherwise = text " -/ " \ No newline at end of file ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -183,7 +183,7 @@ lookupFixityRn_help name -- loadInterfaceForName will find B.hi even if B is a hidden module, -- and that's what we want. = do { iface <- loadInterfaceForName doc name - ; let mb_fix = mi_fix_fn (mi_final_exts iface) occ + ; let mb_fix = mi_fix_fn iface occ ; let msg = case mb_fix of Nothing -> text "looking up name" <+> ppr name ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -485,8 +485,8 @@ calculateAvails :: HomeUnit calculateAvails home_unit other_home_units iface mod_safe' want_boot imported_by = let imp_mod = mi_module iface imp_sem_mod= mi_semantic_module iface - orph_iface = mi_orphan (mi_final_exts iface) - has_finsts = mi_finsts (mi_final_exts iface) + orph_iface = mi_orphan iface + has_finsts = mi_finsts iface deps = mi_deps iface trust = getSafeMode $ mi_trust iface trust_pkg = mi_trust_pkg iface @@ -1397,7 +1397,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) _ -> failLookupWith err mk_depr_export_warning gre - = DeprecatedExport name <$> mi_export_warn_fn (mi_final_exts iface) name + = DeprecatedExport name <$> mi_export_warn_fn iface name where name = greName gre ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -539,9 +539,9 @@ warnIfDeclDeprecated gre@(GRE { gre_imp = iss }) lookupImpDeclDeprec :: ModIface -> GlobalRdrElt -> Maybe (WarningTxt GhcRn) lookupImpDeclDeprec iface gre -- Bleat if the thing, or its parent, is warn'd - = mi_decl_warn_fn (mi_final_exts iface) (greOccName gre) `mplus` + = mi_decl_warn_fn iface (greOccName gre) `mplus` case greParent gre of - ParentIs p -> mi_decl_warn_fn (mi_final_exts iface) (nameOccName p) + ParentIs p -> mi_decl_warn_fn iface (nameOccName p) NoParent -> Nothing warnIfExportDeprecated :: GlobalRdrElt -> RnM () @@ -562,7 +562,7 @@ warnIfExportDeprecated gre@(GRE { gre_imp = iss }) process_import_spec is = do let mod = is_mod $ is_decl is iface <- loadInterfaceForModule doc mod - let mb_warn_txt = mi_export_warn_fn (mi_final_exts iface) name + let mb_warn_txt = mi_export_warn_fn iface name return $ (moduleName mod, ) <$> mb_warn_txt ------------------------- ===================================== compiler/GHC/Tc/Instance/Family.hs ===================================== @@ -308,7 +308,7 @@ checkFamInstConsistency directlyImpMods ifc <- modIface mod deps <- dep_finsts . mi_deps <$> modIface mod pure $ - if mi_finsts (mi_final_exts ifc) + if mi_finsts ifc then mod:deps else deps ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -97,7 +97,7 @@ checkHsigDeclM sig_iface sig_thing real_thing = do -- implementation cases. checkBootDeclM Hsig sig_thing real_thing real_fixity <- lookupFixityRn name - let sig_fixity = case mi_fix_fn (mi_final_exts sig_iface) (occName name) of + let sig_fixity = case mi_fix_fn sig_iface (occName name) of Nothing -> defaultFixity Just f -> f when (real_fixity /= sig_fixity) $ @@ -850,7 +850,7 @@ mergeSignatures if outer_mod == mi_module iface -- Don't add ourselves! then tcg_merged tcg_env - else (mi_module iface, mi_mod_hash (mi_final_exts iface)) : tcg_merged tcg_env + else (mi_module iface, mi_mod_hash iface) : tcg_merged tcg_env } -- Note [Signature merging DFuns] ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -1,18 +1,20 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ExplicitNamespaces #-} -- | Dependencies and Usage of a module module GHC.Unit.Module.Deps - ( Dependencies - , mkDependencies - , noDependencies - , dep_direct_mods - , dep_direct_pkgs - , dep_sig_mods - , dep_trusted_pkgs - , dep_orphs - , dep_plugin_pkgs - , dep_finsts - , dep_boot_mods + ( Dependencies(dep_direct_mods + , dep_direct_pkgs + , dep_sig_mods + , dep_trusted_pkgs + , dep_orphs + , dep_plugin_pkgs + , dep_finsts + , dep_boot_mods + , Dependencies) , dep_orphs_update , dep_finsts_update + , mkDependencies + , noDependencies , pprDeps , Usage (..) , ImportAvails (..) @@ -52,38 +54,38 @@ import Control.DeepSeq -- -- See Note [Transitive Information in Dependencies] data Dependencies = Deps - { dep_direct_mods :: Set (UnitId, ModuleNameWithIsBoot) + { dep_direct_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All home-package modules which are directly imported by this one. -- This may include modules from other units when using multiple home units - , dep_direct_pkgs :: Set UnitId + , dep_direct_pkgs_ :: Set UnitId -- ^ All packages directly imported by this module -- I.e. packages to which this module's direct imports belong. -- Does not include other home units when using multiple home units. -- Modules from these units will go in `dep_direct_mods` - , dep_plugin_pkgs :: Set UnitId + , dep_plugin_pkgs_ :: Set UnitId -- ^ All units needed for plugins ------------------------------------ -- Transitive information below here - , dep_sig_mods :: ![ModuleName] + , dep_sig_mods_ :: ![ModuleName] -- ^ Transitive closure of hsig files in the home package - , dep_trusted_pkgs :: Set UnitId + , dep_trusted_pkgs_ :: Set UnitId -- Packages which we are required to trust -- when the module is imported as a safe import -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names - , dep_boot_mods :: Set (UnitId, ModuleNameWithIsBoot) + , dep_boot_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All modules which have boot files below this one, and whether we -- should use the boot file or not. -- This information is only used to populate the eps_is_boot field. -- See Note [Structure of dep_boot_mods] - , dep_orphs :: [Module] + , dep_orphs_ :: [Module] -- ^ Transitive closure of orphan modules (whether -- home or external pkg). -- @@ -93,7 +95,7 @@ data Dependencies = Deps -- which relies on dep_orphs having the complete list!) -- This does NOT include us, unlike 'imp_orphs'. - , dep_finsts :: [Module] + , dep_finsts_ :: [Module] -- ^ Transitive closure of depended upon modules which -- contain family instances (whether home or external). -- This is used by 'checkFamInstConsistency'. This @@ -105,6 +107,26 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +pattern Dependencies :: Set (UnitId, ModuleNameWithIsBoot) + -> Set UnitId + -> Set UnitId + -> [ModuleName] + -> Set UnitId + -> Set (UnitId, ModuleNameWithIsBoot) + -> [Module] + -> [Module] + -> Dependencies +pattern Dependencies {dep_direct_mods, dep_direct_pkgs, dep_plugin_pkgs, dep_sig_mods, dep_trusted_pkgs, dep_boot_mods, dep_orphs, dep_finsts} + <- Deps {dep_direct_mods_ = dep_direct_mods + , dep_direct_pkgs_ = dep_direct_pkgs + , dep_plugin_pkgs_ = dep_plugin_pkgs + , dep_sig_mods_ = dep_sig_mods + , dep_trusted_pkgs_ = dep_trusted_pkgs + , dep_boot_mods_ = dep_boot_mods + , dep_orphs_ = dep_orphs + , dep_finsts_ = dep_finsts} +{-# COMPLETE Dependencies #-} + instance NFData Dependencies where rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) = rnf dmods @@ -158,14 +180,14 @@ mkDependencies home_unit mod imports plugin_mods = sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports - in Deps { dep_direct_mods = direct_mods - , dep_direct_pkgs = direct_pkgs - , dep_plugin_pkgs = plugin_units - , dep_sig_mods = sort sig_mods - , dep_trusted_pkgs = trust_pkgs - , dep_boot_mods = source_mods - , dep_orphs = sortBy stableModuleCmp dep_orphs - , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) + in Deps { dep_direct_mods_ = direct_mods + , dep_direct_pkgs_ = direct_pkgs + , dep_plugin_pkgs_ = plugin_units + , dep_sig_mods_ = sort sig_mods + , dep_trusted_pkgs_ = trust_pkgs + , dep_boot_mods_ = source_mods + , dep_orphs_ = sortBy stableModuleCmp dep_orphs + , dep_finsts_ = sortBy stableModuleCmp (imp_finsts imports) -- sort to get into canonical order -- NB. remember to use lexicographic ordering } @@ -174,14 +196,13 @@ mkDependencies home_unit mod imports plugin_mods = dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_orphs_update deps f = do r <- f (dep_orphs deps) - pure (deps { dep_orphs = sortBy stableModuleCmp r }) + pure (deps { dep_orphs_ = sortBy stableModuleCmp r }) -- | Update module dependencies containing family instances (used by Backpack) dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_finsts_update deps f = do r <- f (dep_finsts deps) - pure (deps { dep_finsts = sortBy stableModuleCmp r }) - + pure (deps { dep_finsts_ = sortBy stableModuleCmp r }) instance Binary Dependencies where put_ bh deps = do put_ bh (dep_direct_mods deps) @@ -201,36 +222,36 @@ instance Binary Dependencies where sms <- get bh os <- get bh fis <- get bh - return (Deps { dep_direct_mods = dms - , dep_direct_pkgs = dps - , dep_plugin_pkgs = plugin_pkgs - , dep_sig_mods = hsigms - , dep_boot_mods = sms - , dep_trusted_pkgs = tps - , dep_orphs = os, - dep_finsts = fis }) + return (Deps { dep_direct_mods_ = dms + , dep_direct_pkgs_ = dps + , dep_plugin_pkgs_ = plugin_pkgs + , dep_sig_mods_ = hsigms + , dep_boot_mods_ = sms + , dep_trusted_pkgs_ = tps + , dep_orphs_ = os, + dep_finsts_ = fis }) noDependencies :: Dependencies noDependencies = Deps - { dep_direct_mods = Set.empty - , dep_direct_pkgs = Set.empty - , dep_plugin_pkgs = Set.empty - , dep_sig_mods = [] - , dep_boot_mods = Set.empty - , dep_trusted_pkgs = Set.empty - , dep_orphs = [] - , dep_finsts = [] + { dep_direct_mods_ = Set.empty + , dep_direct_pkgs_ = Set.empty + , dep_plugin_pkgs_ = Set.empty + , dep_sig_mods_ = [] + , dep_boot_mods_ = Set.empty + , dep_trusted_pkgs_ = Set.empty + , dep_orphs_ = [] + , dep_finsts_ = [] } -- | Pretty-print unit dependencies pprDeps :: UnitState -> Dependencies -> SDoc -pprDeps unit_state (Deps { dep_direct_mods = dmods - , dep_boot_mods = bmods - , dep_plugin_pkgs = plgns - , dep_orphs = orphs - , dep_direct_pkgs = pkgs - , dep_trusted_pkgs = tps - , dep_finsts = finsts +pprDeps unit_state (Deps { dep_direct_mods_ = dmods + , dep_boot_mods_ = bmods + , dep_plugin_pkgs_ = plgns + , dep_orphs_ = orphs + , dep_direct_pkgs_ = pkgs + , dep_trusted_pkgs_ = tps + , dep_finsts_ = finsts }) = pprWithUnitState unit_state $ vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -11,18 +11,20 @@ module GHC.Unit.Module.ModIface ( ModIface , ModIface_ - ( mi_module + ( mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls , mi_defaults - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_top_env , mi_insts , mi_fam_insts @@ -31,12 +33,17 @@ module GHC.Unit.Module.ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn ) , pattern ModIface + , set_mi_mod_info , set_mi_module , set_mi_sig_of , set_mi_hsc_src @@ -52,24 +59,34 @@ module GHC.Unit.Module.ModIface , set_mi_rules , set_mi_decls , set_mi_defaults - , set_mi_extra_decls - , set_mi_foreign + , set_mi_simplified_core , set_mi_top_env , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches , set_mi_docs - , set_mi_final_exts + , set_mi_abi_hashes , set_mi_ext_fields + , set_mi_caches + , set_mi_decl_warn_fn + , set_mi_export_warn_fn + , set_mi_fix_fn + , set_mi_hash_fn , completePartialModIface , IfaceBinHandle(..) , PartialModIface - , ModIfaceBackend (..) - , ModIfaceSelfRecomp (..) + , IfaceAbiHashes (..) + , IfaceSelfRecomp (..) + , IfaceCache (..) + , IfaceSimplifiedCore (..) , withSelfRecomp , IfaceDeclExts - , IfaceBackendExts + , IfaceAbiHashesExts , IfaceExport + , IfacePublic_(..) + , IfacePublic + , PartialIfacePublic + , IfaceModInfo(..) , WhetherHasOrphans , WhetherHasFamInst , IfaceTopEnv (..) @@ -77,6 +94,7 @@ module GHC.Unit.Module.ModIface , mi_boot , mi_fix , mi_semantic_module + , mi_mod_info_semantic_module , mi_free_holes , mi_mnwib , mi_flag_hash @@ -85,6 +103,11 @@ module GHC.Unit.Module.ModIface , mi_plugin_hash , mi_src_hash , mi_usages + , mi_mod_hash + , mi_orphan + , mi_finsts + , mi_exp_hash + , mi_orphan_hash , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,7 +129,7 @@ import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings -import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..)) import GHC.Types.Avail @@ -147,36 +170,36 @@ We can build a full interface file two ways: type PartialModIface = ModIface_ 'ModIfaceCore type ModIface = ModIface_ 'ModIfaceFinal --- | Extends a PartialModIface with information which is either: --- * Computed after codegen --- * Or computed just before writing the iface to disk. (Hashes) --- In order to fully instantiate it. -data ModIfaceBackend = ModIfaceBackend - { mi_mod_hash :: !Fingerprint +type PartialIfacePublic = IfacePublic_ 'ModIfaceCore +type IfacePublic = IfacePublic_ 'ModIfaceFinal + +-- | Extends a PartialModIface with hashes of the ABI. +-- +-- * The mi_mod_hash is the hash of the entire ABI +-- * THe other fields are more specific hashes of parts of the ABI +data IfaceAbiHashes = IfaceAbiHashes + { mi_abi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_orphan :: !WhetherHasOrphans + , mi_abi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans - , mi_finsts :: !WhetherHasFamInst + , mi_abi_finsts :: !WhetherHasFamInst -- ^ Whether this module has family instances. See Note [The type family -- instance consistency story]. - , mi_exp_hash :: !Fingerprint + , mi_abi_exp_hash :: !Fingerprint -- ^ Hash of export list - , mi_orphan_hash :: !Fingerprint + , mi_abi_orphan_hash :: !Fingerprint -- ^ Hash for orphan rules, class and family instances combined + -- NOT transitive + } - -- Cached environments for easy lookup. These are computed (lazily) from - -- other fields and are not put into the interface file. - -- Not really produced by the backend but there is no need to create them - -- any earlier. - , mi_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) +data IfaceCache = IfaceCache + { mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for declaration deprecations - , mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) + , mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for export deprecations - , mi_fix_fn :: !(OccName -> Maybe Fixity) + , mi_cache_fix_fn :: !(OccName -> Maybe Fixity) -- ^ Cached lookup for 'mi_fixities' - , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) + , mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that -- the thing isn't in decls. It's useful to know that when seeing if we are -- up to date wrt. the old interface. The 'OccName' is the parent of the @@ -195,9 +218,9 @@ type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where IfaceDeclExts 'ModIfaceCore = IfaceDecl IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) -type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where - IfaceBackendExts 'ModIfaceCore = () - IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend +type family IfaceAbiHashesExts (phase :: ModIfacePhase) = bk | bk -> phase where + IfaceAbiHashesExts 'ModIfaceCore = () + IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes -- | In-memory byte array representation of a 'ModIface'. -- @@ -212,7 +235,7 @@ data IfaceBinHandle (phase :: ModIfacePhase) where FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp :: ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r withSelfRecomp iface nk jk = case mi_self_recomp_info iface of Nothing -> nk @@ -220,34 +243,80 @@ withSelfRecomp iface nk jk = --- | A 'ModIface' plus a 'ModDetails' summarises everything we know --- about a compiled module. The 'ModIface' is the stuff *before* linking, --- and can be written out to an interface file. The 'ModDetails is after --- linking and can be completely recovered from just the 'ModIface'. +-- | A 'ModIface' summarises everything we know +-- about a compiled module. -- --- When we read an interface file, we also construct a 'ModIface' from it, --- except that we explicitly make the 'mi_decls' and a few other fields empty; --- as when reading we consolidate the declarations etc. into a number of indexed --- maps and environments in the 'ExternalPackageState'. +-- See Note [Structure of ModIface] for information about what belongs in each field. -- --- See Note [Strictness in ModIface] to learn about why some fields are --- strict and others are not. +-- See Note [Strictness in ModIface] to learn about why all the fields are lazy. -- -- See Note [Private fields in ModIface] to learn why we don't export any of the -- fields. data ModIface_ (phase :: ModIfacePhase) = PrivateModIface { - mi_module_ :: !Module, -- ^ Name of the module we are for - mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? + mi_hi_bytes_ :: !(IfaceBinHandle phase), + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. + mi_iface_hash_ :: Fingerprint, -- A hash of the whole interface - mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? + mi_mod_info_ :: IfaceModInfo, + -- ^ Meta information about the module the interface file is for mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) + -- MP: Needs to be refactored (#25844) + + mi_public_ :: IfacePublic_ phase, + -- ^ The parts of interface which are used by other modules when + -- importing this module. The main, original part of an interface. - mi_exports_ :: ![IfaceExport], + + mi_self_recomp_ :: Maybe IfaceSelfRecomp, + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] + + mi_simplified_core_ :: Maybe IfaceSimplifiedCore, + -- ^ The part of the interface written when `-fwrite-if-simplified-core` is enabled. + -- These parts are used to restart bytecode generation. + + mi_docs_ :: Maybe Docs, + -- ^ Docstrings and related data for use by haddock, the ghci + -- @:doc@ command, and other tools. + -- + -- @Just _@ @<=>@ the module was built with @-haddock at . + + mi_top_env_ :: IfaceTopEnv, + -- ^ Just enough information to reconstruct the top level environment in + -- the /original source/ code for this module. which + -- is NOT the same as mi_exports, nor mi_decls (which + -- may contains declarations for things not actually + -- defined by the user). Used for GHCi and for inspecting + -- the contents of modules via the GHC API only. + + mi_ext_fields_ :: ExtensibleFields + -- ^ Additional optional fields, where the Map key represents + -- the field name, resulting in a (size, serialized data) pair. + -- Because the data is intended to be serialized through the + -- internal `Binary` class (increasing compatibility with types + -- using `Name` and `FastString`, such as HIE), this format is + -- chosen over `ByteString`s. + } + +-- | Meta information about the module the interface file is for +data IfaceModInfo = IfaceModInfo { + mi_mod_info_module :: Module, -- ^ Name of the module we are for + mi_mod_info_sig_of :: Maybe Module, -- ^ Are we a sig of another mod? + mi_mod_info_hsc_src :: HscSource -- ^ Boot? Signature? +} + +-- | The public interface of a module which are used by other modules when importing this module. +-- The ABI of a module. +data IfacePublic_ phase = IfacePublic { + mi_exports_ :: [IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things @@ -273,25 +342,10 @@ data ModIface_ (phase :: ModIfacePhase) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], - -- ^ Extra variable definitions which are **NOT** exposed but when - -- combined with mi_decls allows us to restart code generation. - -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - - mi_foreign_ :: !IfaceForeign, - -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. - -- See Note [Foreign stubs and TH bytecode linking] mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: IfaceTopEnv, - -- ^ Just enough information to reconstruct the top level environment in - -- the /original source/ code for this module. which - -- is NOT the same as mi_exports, nor mi_decls (which - -- may contains declarations for things not actually - -- defined by the user). Used for GHCi and for inspecting - -- the contents of modules via the GHC API only. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -299,53 +353,81 @@ data ModIface_ (phase :: ModIfacePhase) mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_trust_ :: !IfaceTrustInfo, + mi_trust_ :: IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg_ :: !Bool, + mi_trust_pkg_ :: Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches_ :: ![IfaceCompleteMatch], + mi_complete_matches_ :: [IfaceCompleteMatch], + -- ^ {-# COMPLETE #-} declarations - mi_docs_ :: !(Maybe Docs), - -- ^ Docstrings and related data for use by haddock, the ghci - -- @:doc@ command, and other tools. - -- - -- @Just _@ @<=>@ the module was built with @-haddock at . + mi_caches_ :: IfaceCache, + -- ^ Cached lookups of some parts of mi_public - mi_final_exts_ :: !(IfaceBackendExts phase), - -- ^ Either `()` or `ModIfaceBackend` for + mi_abi_hashes_ :: (IfaceAbiHashesExts phase) + -- ^ Either `()` or `IfaceAbiHashes` for -- a fully instantiated interface. - - mi_ext_fields_ :: !ExtensibleFields, - -- ^ Additional optional fields, where the Map key represents - -- the field name, resulting in a (size, serialized data) pair. - -- Because the data is intended to be serialized through the - -- internal `Binary` class (increasing compatibility with types - -- using `Name` and `FastString`, such as HIE), this format is - -- chosen over `ByteString`s. - -- - - mi_hi_bytes_ :: !(IfaceBinHandle phase), - -- ^ A serialised in-memory buffer of this 'ModIface'. - -- If this handle is given, we can avoid serialising the 'ModIface' - -- when writing this 'ModIface' to disk, and write this buffer to disk instead. - -- See Note [Sharing of ModIface]. - - mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) - -- ^ Information needed for checking self-recompilation. - -- See Note [Self recompilation information in interface files] - } + -- These fields are hashes of different parts of the public interface. +} + +mkIfacePublic :: [IfaceExport] + -> [IfaceDeclExts 'ModIfaceFinal] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDefault] + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> IfaceAbiHashes + -> IfacePublic +mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes = IfacePublic { + mi_exports_ = exports, + mi_decls_ = decls, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_defaults_ = defaults, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, + mi_cache_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, + mi_cache_fix_fn = mkIfaceFixCache fixities, + mi_cache_hash_fn = mkIfaceHashCache decls + }, + mi_abi_hashes_ = abi_hashes +} + +-- | The information needed to restart bytecode generation. +-- Enabled by `-fwrite-if-simplified-core`. +data IfaceSimplifiedCore = IfaceSimplifiedCore { + mi_sc_extra_decls :: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -- ^ Extra variable definitions which are **NOT** exposed but when + -- combined with mi_decls allows us to restart code generation. + -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] + , mi_sc_foreign :: IfaceForeign + -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. + -- See Note [Foreign stubs and TH bytecode linking] +} -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff - , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module + { ifaceTopExports :: DetOrdAvails -- ^ all top level things in this module, including unexported stuff + , ifaceImports :: [IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where @@ -362,6 +444,35 @@ instance Binary IfaceTopEnv where {- +Note [Structure of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The ModIface structure is divided into several logical parts: + +1. mi_mod_info: Basic module metadata (name, version, etc.) + +2. mi_public: The public interface of the module, which includes: + - Exports, declarations, fixities, warnings, annotations + - Class and type family instances + - Rewrite rules and COMPLETE pragmas + - Safe Haskell and package trust information + - ABI hashes for recompilation checking + +4. mi_self_recomp: Information needed for self-recompilation checking + (see Note [Self recompilation information in interface files]) + +5. mi_simplified_core: Optional simplified Core for bytecode generation + (only present when -fwrite-if-simplified-core is enabled) + +6. mi_docs: Optional documentation (only present when -haddock is enabled) + +7. mi_top_env: Information about the top-level environment of the original source + +8. mi_ext_fields: Additional fields for extensibility + +This structure helps organize the interface data according to its purpose and usage +patterns. Different parts of the compiler use different fields. By separating them +logically in the interface we can arrange to only deserialize the fields that are needed. + Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -371,7 +482,7 @@ The ModIface is the Haskell representation of an interface (.hi) file. that we have just compiled * For packages that we depend on we load the ModIface from disk. -Some fields in the ModIface are deliberately lazy because when we read +All fields in the ModIface are deliberately lazy because when we read an interface file we don't always need all the parts. For example, an interface file contains information about documentation which is often not needed during compilation. This is achieved using the lazyPut/lazyGet pair. @@ -384,23 +495,43 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) -mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ +mi_flag_hash :: ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags) +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint -mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_ mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint -mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_ mi_src_hash :: ModIface_ phase -> Maybe Fingerprint -mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_ mi_usages :: ModIface_ phase -> Maybe [Usage] -mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ +mi_usages = fmap mi_sr_usages . mi_self_recomp_ mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint -mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_ + +-- | Accessor for the module hash of the ABI from a ModIface. +mi_mod_hash :: ModIface -> Fingerprint +mi_mod_hash iface = mi_abi_mod_hash (mi_abi_hashes iface) + +-- | Accessor for whether this module has orphans from a ModIface. +mi_orphan :: ModIface -> WhetherHasOrphans +mi_orphan iface = mi_abi_orphan (mi_abi_hashes iface) + +-- | Accessor for whether this module has family instances from a ModIface. +mi_finsts :: ModIface -> WhetherHasFamInst +mi_finsts iface = mi_abi_finsts (mi_abi_hashes iface) + +-- | Accessor for the hash of the export list from a ModIface. +mi_exp_hash :: ModIface -> Fingerprint +mi_exp_hash iface = mi_abi_exp_hash (mi_abi_hashes iface) + +-- | Accessor for the hash of orphan rules, class and family instances combined from a ModIface. +mi_orphan_hash :: ModIface -> Fingerprint +mi_orphan_hash iface = mi_abi_orphan_hash (mi_abi_hashes iface) -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. @@ -415,16 +546,19 @@ mi_mnwib iface = GWIB (moduleName $ mi_module iface) (mi_boot iface) -- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be -- found, 'defaultFixity' is returned instead. mi_fix :: ModIface -> OccName -> Fixity -mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity +mi_fix iface name = mi_fix_fn iface name `orElse` defaultFixity -- | The semantic module for this interface; e.g., if it's a interface -- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module' -- will be @<A>@. -mi_semantic_module :: ModIface_ a -> Module -mi_semantic_module iface = case mi_sig_of iface of - Nothing -> mi_module iface +mi_mod_info_semantic_module :: IfaceModInfo -> Module +mi_mod_info_semantic_module iface = case mi_mod_info_sig_of iface of + Nothing -> mi_mod_info_module iface Just mod -> mod +mi_semantic_module :: ModIface_ a -> Module +mi_semantic_module iface = mi_mod_info_semantic_module (mi_mod_info iface) + -- | The "precise" free holes, e.g., the signatures that this -- 'ModIface' depends on. mi_free_holes :: ModIface -> UniqDSet ModuleName @@ -455,191 +589,229 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + put_ bh (PrivateModIface + { mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then -- we likely have a good reason, and do not want to reuse -- the byte array. -- See Note [Private fields in ModIface] + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_anns_ = anns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - mi_complete_matches_ = complete_matches, + mi_public_ = public, mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_self_recomp_info_ = self_recomp, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash - }}) = do - put_ bh mod - put_ bh sig_of - put_ bh hsc_src - put_ bh self_recomp - put_ bh mod_hash + mi_self_recomp_ = self_recomp, + mi_simplified_core_ = simplified_core + }) = do + put_ bh mod_info put_ bh iface_hash - put_ bh orphan - put_ bh hasFamInsts lazyPut bh deps - put_ bh exports - put_ bh exp_hash - put_ bh fixities - lazyPut bh warns - lazyPut bh anns - put_ bh decls - put_ bh extra_decls - put_ bh defaults - put_ bh foreign_ - put_ bh insts - put_ bh fam_insts - lazyPut bh rules - put_ bh orphan_hash - put_ bh trust - put_ bh trust_pkg - put_ bh complete_matches + lazyPut bh public lazyPut bh top_env lazyPutMaybe bh docs + lazyPutMaybe bh self_recomp + lazyPutMaybe bh simplified_core get bh = do - mod <- get bh - sig_of <- get bh - hsc_src <- get bh - self_recomp_info <- get bh - mod_hash <- get bh + mod_info <- get bh iface_hash <- get bh - orphan <- get bh - hasFamInsts <- get bh deps <- lazyGet bh - exports <- {-# SCC "bin_exports" #-} get bh - exp_hash <- get bh - fixities <- {-# SCC "bin_fixities" #-} get bh - warns <- {-# SCC "bin_warns" #-} lazyGet bh - anns <- {-# SCC "bin_anns" #-} lazyGet bh - decls <- {-# SCC "bin_tycldecls" #-} get bh - extra_decls <- get bh - defaults <- get bh - foreign_ <- get bh - insts <- {-# SCC "bin_insts" #-} get bh - fam_insts <- {-# SCC "bin_fam_insts" #-} get bh - rules <- {-# SCC "bin_rules" #-} lazyGet bh - orphan_hash <- get bh - trust <- get bh - trust_pkg <- get bh - complete_matches <- get bh + public <- lazyGet bh top_env <- lazyGet bh docs <- lazyGetMaybe bh + self_recomp <- lazyGetMaybe bh + simplified_core <- lazyGetMaybe bh + return (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = - -- We can't populate this field here, as we are - -- missing the 'mi_ext_fields_' field, which is - -- handled in 'getIfaceWithExtFields'. - FullIfaceBinHandle Strict.Nothing, + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_anns_ = anns, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - -- And build the cached values - mi_complete_matches_ = complete_matches, + mi_public_ = public, + mi_simplified_core_ = simplified_core, mi_docs_ = docs, mi_top_env_ = top_env, - mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt - -- with specially when the file is read - mi_self_recomp_info_ = self_recomp_info, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash, - mi_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, - mi_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, - mi_fix_fn = mkIfaceFixCache fixities, - mi_hash_fn = mkIfaceHashCache decls - }}) + mi_self_recomp_ = self_recomp, + -- placeholder because this is dealt + -- with specially when the file is read + mi_ext_fields_ = emptyExtensibleFields, + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + }) + +instance Binary IfaceModInfo where + put_ bh (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) = do + put_ bh mod + put_ bh sig_of + put_ bh hsc_src + get bh = do + mod <- get bh + sig_of <- get bh + hsc_src <- get bh + return (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) + + +instance Binary (IfacePublic_ 'ModIfaceFinal) where + put_ bh (IfacePublic { mi_exports_ = exports + , mi_decls_ = decls + , mi_fixities_ = fixities + , mi_warns_ = warns + , mi_anns_ = anns + , mi_defaults_ = defaults + , mi_insts_ = insts + , mi_fam_insts_ = fam_insts + , mi_rules_ = rules + , mi_trust_ = trust + , mi_trust_pkg_ = trust_pkg + , mi_complete_matches_ = complete_matches + , mi_abi_hashes_ = abi_hashes + }) = do + + lazyPut bh exports + lazyPut bh decls + lazyPut bh fixities + lazyPut bh warns + lazyPut bh anns + lazyPut bh defaults + lazyPut bh insts + lazyPut bh fam_insts + lazyPut bh rules + lazyPut bh trust + lazyPut bh trust_pkg + lazyPut bh complete_matches + lazyPut bh abi_hashes + + get bh = do + exports <- lazyGet bh + decls <- lazyGet bh + fixities <- lazyGet bh + warns <- lazyGet bh + anns <- lazyGet bh + defaults <- lazyGet bh + insts <- lazyGet bh + fam_insts <- lazyGet bh + rules <- lazyGet bh + trust <- lazyGet bh + trust_pkg <- lazyGet bh + complete_matches <- lazyGet bh + abi_hashes <- lazyGet bh + return (mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes) + +instance Binary IfaceAbiHashes where + put_ bh (IfaceAbiHashes { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = orphan + , mi_abi_finsts = hasFamInsts + , mi_abi_exp_hash = exp_hash + , mi_abi_orphan_hash = orphan_hash + }) = do + put_ bh mod_hash + put_ bh orphan + put_ bh hasFamInsts + put_ bh exp_hash + put_ bh orphan_hash + get bh = do + mod_hash <- get bh + orphan <- get bh + hasFamInsts <- get bh + exp_hash <- get bh + orphan_hash <- get bh + return $ IfaceAbiHashes { + mi_abi_mod_hash = mod_hash, + mi_abi_orphan = orphan, + mi_abi_finsts = hasFamInsts, + mi_abi_exp_hash = exp_hash, + mi_abi_orphan_hash = orphan_hash + } + +instance Binary IfaceSimplifiedCore where + put_ bh (IfaceSimplifiedCore eds fs) = do + put_ bh eds + put_ bh fs + + get bh = do + eds <- get bh + fs <- get bh + return (IfaceSimplifiedCore eds fs) emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface - { mi_module_ = mod, - mi_sig_of_ = Nothing, - mi_hsc_src_ = HsSrcFile, + { mi_mod_info_ = emptyIfaceModInfo mod, + mi_iface_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_exports_ = [], - mi_fixities_ = [], - mi_warns_ = IfWarnSome [] [], - mi_anns_ = [], - mi_defaults_ = [], - mi_insts_ = [], - mi_fam_insts_ = [], - mi_rules_ = [], - mi_decls_ = [], - mi_extra_decls_ = Nothing, - mi_foreign_ = emptyIfaceForeign, + mi_public_ = emptyPublicModIface (), + mi_simplified_core_ = Nothing, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_trust_ = noIfaceTrustInfo, - mi_trust_pkg_ = False, - mi_complete_matches_ = [], mi_docs_ = Nothing, - mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields, - mi_self_recomp_info_ = Nothing + mi_self_recomp_ = Nothing, + mi_ext_fields_ = emptyExtensibleFields + } +emptyIfaceModInfo :: Module -> IfaceModInfo +emptyIfaceModInfo mod = IfaceModInfo + { mi_mod_info_module = mod + , mi_mod_info_sig_of = Nothing + , mi_mod_info_hsc_src = HsSrcFile + } + + +emptyPublicModIface :: IfaceAbiHashesExts phase -> IfacePublic_ phase +emptyPublicModIface abi_hashes = IfacePublic + { mi_exports_ = [] + , mi_decls_ = [] + , mi_fixities_ = [] + , mi_warns_ = IfWarnSome [] [] + , mi_anns_ = [] + , mi_defaults_ = [] + , mi_insts_ = [] + , mi_fam_insts_ = [] + , mi_rules_ = [] + , mi_abi_hashes_ = abi_hashes + , mi_trust_ = noIfaceTrustInfo + , mi_trust_pkg_ = False + , mi_caches_ = emptyModIfaceCache + , mi_complete_matches_ = [] + } + +emptyModIfaceCache :: IfaceCache +emptyModIfaceCache = IfaceCache { + mi_cache_decl_warn_fn = emptyIfaceWarnCache, + mi_cache_export_warn_fn = emptyIfaceWarnCache, + mi_cache_fix_fn = emptyIfaceFixCache, + mi_cache_hash_fn = emptyIfaceHashCache +} + +emptyIfaceBackend :: IfaceAbiHashes +emptyIfaceBackend = IfaceAbiHashes + { mi_abi_mod_hash = fingerprint0, + mi_abi_orphan = False, + mi_abi_finsts = False, + mi_abi_exp_hash = fingerprint0, + mi_abi_orphan_hash = fingerprint0 + } + emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls_ = [] - , mi_self_recomp_info_ = Nothing + { mi_public_ = emptyPublicModIface emptyIfaceBackend , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing - , mi_final_exts_ = ModIfaceBackend - { mi_mod_hash = fingerprint0, - mi_iface_hash = fingerprint0, - mi_orphan = False, - mi_finsts = False, - mi_exp_hash = fingerprint0, - mi_orphan_hash = fingerprint0, - mi_decl_warn_fn = emptyIfaceWarnCache, - mi_export_warn_fn = emptyIfaceWarnCache, - mi_fix_fn = emptyIfaceFixCache, - mi_hash_fn = emptyIfaceHashCache } } + } + -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface' mkIfaceHashCache :: [(Fingerprint,IfaceDecl)] @@ -657,11 +829,11 @@ emptyIfaceHashCache _occ = Nothing -- ModIface is completely forced since it will live in memory for a long time. -- If forcing it uses a lot of memory, then store less things in ModIface. -instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) +instance ( NFData (IfaceAbiHashesExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) - = rnf a1 + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = (a1 :: IfaceBinHandle phase) `seq` rnf a2 `seq` rnf a3 `seq` rnf a4 @@ -671,24 +843,27 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 - `seq` rnf a11 - `seq` rnf a12 - `seq` rnf a13 - `seq` rnf a14 - `seq` rnf a15 - `seq` rnf a16 - `seq` rnf a17 - `seq` rnf a18 - `seq` rnf a19 - `seq` rnf a20 - `seq` rnf a21 - `seq` rnf a22 - -- IfaceBinHandle - `seq` (a23 :: IfaceBinHandle phase) - `seq` rnf a24 - -instance NFData ModIfaceBackend where - rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + +instance NFData IfaceModInfo where + rnf (IfaceModInfo a1 a2 a3) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + + +instance NFData IfaceSimplifiedCore where + rnf (IfaceSimplifiedCore eds fs) = rnf eds `seq` rnf fs + +instance NFData IfaceAbiHashes where + rnf (IfaceAbiHashes a1 a2 a3 a4 a5) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + +instance (NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) where + rnf (IfacePublic a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = rnf a1 `seq` rnf a2 `seq` rnf a3 @@ -699,6 +874,18 @@ instance NFData ModIfaceBackend where `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +instance NFData IfaceCache where + rnf (IfaceCache a1 a2 a3 a4) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + forceModIface :: ModIface -> IO () @@ -745,28 +932,38 @@ to serialise the 'ModIface' to disk again. -- | Given a 'PartialModIface', turn it into a 'ModIface' by completing -- missing fields. completePartialModIface :: PartialModIface + -> Fingerprint -> [(Fingerprint, IfaceDecl)] - -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - -> ModIfaceBackend + -> Maybe IfaceSimplifiedCore + -> IfaceAbiHashes + -> IfaceCache -> ModIface -completePartialModIface partial decls extra_decls final_exts = partial - { mi_decls_ = decls - , mi_extra_decls_ = extra_decls - , mi_final_exts_ = final_exts +completePartialModIface partial iface_hash decls extra_decls final_exts cache = partial + { mi_public_ = completePublicModIface decls final_exts cache (mi_public_ partial) + , mi_simplified_core_ = extra_decls , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_iface_hash_ = iface_hash } + where -set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase -set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } - -set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase -set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } +-- | Given a 'PartialIfacePublic', turn it into an 'IfacePublic' by completing +-- missing fields. +completePublicModIface :: [(Fingerprint, IfaceDecl)] + -> IfaceAbiHashes + -> IfaceCache + -> PartialIfacePublic + -> IfacePublic +completePublicModIface decls abi_hashes cache partial = partial + { mi_decls_ = decls + , mi_abi_hashes_ = abi_hashes + , mi_caches_ = cache + } -set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase -set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } +set_mi_mod_info :: IfaceModInfo -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info val iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = val } -set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase -set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } +set_mi_self_recomp :: Maybe IfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -774,59 +971,100 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } +set_mi_public :: (IfacePublic_ phase -> IfacePublic_ phase) -> ModIface_ phase -> ModIface_ phase +set_mi_public f iface = clear_mi_hi_bytes $ iface { mi_public_ = f (mi_public_ iface) } + +set_mi_simplified_core :: Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase +set_mi_simplified_core val iface = clear_mi_hi_bytes $ iface { mi_simplified_core_ = val } + +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +{- Settings for mi_public interface fields -} + set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase -set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } +set_mi_exports val = set_mi_public (\iface -> iface { mi_exports_ = val }) set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase -set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } +set_mi_fixities val = set_mi_public (\iface -> iface { mi_fixities_ = val }) set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase -set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } +set_mi_warns val = set_mi_public (\iface -> iface { mi_warns_ = val }) set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase -set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } +set_mi_anns val = set_mi_public (\iface -> iface { mi_anns_ = val }) set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase -set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } +set_mi_insts val = set_mi_public (\iface -> iface { mi_insts_ = val }) set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase -set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } +set_mi_fam_insts val = set_mi_public (\iface -> iface { mi_fam_insts_ = val }) set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase -set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } +set_mi_rules val = set_mi_public (\iface -> iface { mi_rules_ = val }) set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase -set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } +set_mi_decls val = set_mi_public (\iface -> iface { mi_decls_ = val }) set_mi_defaults :: [IfaceDefault] -> ModIface_ phase -> ModIface_ phase -set_mi_defaults val iface = clear_mi_hi_bytes $ iface { mi_defaults_ = val } - -set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase -set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } - -set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase -set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } - -set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase -set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } +set_mi_defaults val = set_mi_public (\iface -> iface { mi_defaults_ = val }) set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase -set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } +set_mi_trust val = set_mi_public (\iface -> iface { mi_trust_ = val }) set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase -set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } +set_mi_trust_pkg val = set_mi_public (\iface -> iface { mi_trust_pkg_ = val }) set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase -set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } +set_mi_complete_matches val = set_mi_public (\iface -> iface { mi_complete_matches_ = val }) + +set_mi_abi_hashes :: IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_abi_hashes val = set_mi_public (\iface -> iface { mi_abi_hashes_ = val }) + +{- Setters for mi_caches interface fields -} + +set_mi_decl_warn_fn :: (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_decl_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_decl_warn_fn = val } }) + +set_mi_export_warn_fn :: (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_export_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_export_warn_fn = val } }) + +set_mi_fix_fn :: (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase +set_mi_fix_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_fix_fn = val } }) + +set_mi_hash_fn :: (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase +set_mi_hash_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_hash_fn = val } }) + +set_mi_caches :: IfaceCache -> ModIface_ phase -> ModIface_ phase +set_mi_caches val = set_mi_public (\iface -> iface { mi_caches_ = val }) + +{- + +-} + +{- Setters for mi_mod_info interface fields -} + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val = set_mi_mod_info_field (\info -> info { mi_mod_info_module = val }) + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val = set_mi_mod_info_field (\info -> info { mi_mod_info_sig_of = val }) + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val = set_mi_mod_info_field (\info -> info { mi_mod_info_hsc_src = val }) + +-- | Helper function for setting fields in mi_mod_info_ +set_mi_mod_info_field :: (IfaceModInfo -> IfaceModInfo) -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info_field f iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = f (mi_mod_info_ iface) } -set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase -set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } -set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase -set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } -set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase -set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } -- | Invalidate any byte array buffer we might have. clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase @@ -887,18 +1125,20 @@ However, with the pragma, the correct core is generated: -- See Note [Inline Pattern synonym of ModIface] for why we have all these -- inline pragmas. -{-# INLINE ModIface #-} +{-# INLINE mi_mod_info #-} +{-# INLINE mi_iface_hash #-} {-# INLINE mi_module #-} {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} +{-# INLINE mi_public #-} {-# INLINE mi_exports #-} {-# INLINE mi_fixities #-} {-# INLINE mi_warns #-} {-# INLINE mi_anns #-} {-# INLINE mi_decls #-} -{-# INLINE mi_extra_decls #-} -{-# INLINE mi_foreign #-} +{-# INLINE mi_simplified_core #-} +{-# INLINE mi_defaults #-} {-# INLINE mi_top_env #-} {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} @@ -907,32 +1147,63 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} {-# INLINE mi_docs #-} -{-# INLINE mi_final_exts #-} +{-# INLINE mi_abi_hashes #-} {-# INLINE mi_ext_fields #-} {-# INLINE mi_hi_bytes #-} +{-# INLINE mi_self_recomp_info #-} +{-# INLINE mi_fix_fn #-} +{-# INLINE mi_hash_fn #-} +{-# INLINE mi_decl_warn_fn #-} +{-# INLINE mi_export_warn_fn #-} +{-# INLINE ModIface #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> - [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> - [IfaceAnnotation] -> [IfaceDeclExts phase] -> - Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> + IfaceModInfo + -> Module + -> Maybe Module + -> HscSource + -> Fingerprint + -> Dependencies + -> IfacePublic_ phase + -> [IfaceExport] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDeclExts phase] + -> Maybe IfaceSimplifiedCore + -> [IfaceDefault] + -> IfaceTopEnv + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> Maybe Docs + -> IfaceAbiHashesExts phase + -> ExtensibleFields + -> IfaceBinHandle phase + -> Maybe IfaceSelfRecomp + -> (OccName -> Maybe Fixity) + -> (OccName -> Maybe (OccName, Fingerprint)) + -> (OccName -> Maybe (WarningTxt GhcRn)) + -> (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase pattern ModIface - { mi_module + { mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_defaults , mi_top_env , mi_insts @@ -942,33 +1213,45 @@ pattern ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_hash_fn + , mi_decl_warn_fn + , mi_export_warn_fn } <- PrivateModIface - { mi_module_ = mi_module - , mi_sig_of_ = mi_sig_of - , mi_hsc_src_ = mi_hsc_src + { mi_mod_info_ = mi_mod_info at IfaceModInfo { mi_mod_info_module = mi_module + , mi_mod_info_sig_of = mi_sig_of + , mi_mod_info_hsc_src = mi_hsc_src } + , mi_iface_hash_ = mi_iface_hash , mi_deps_ = mi_deps - , mi_exports_ = mi_exports - , mi_fixities_ = mi_fixities - , mi_warns_ = mi_warns - , mi_anns_ = mi_anns - , mi_decls_ = mi_decls - , mi_extra_decls_ = mi_extra_decls - , mi_foreign_ = mi_foreign - , mi_defaults_ = mi_defaults - , mi_top_env_ = mi_top_env - , mi_insts_ = mi_insts - , mi_fam_insts_ = mi_fam_insts - , mi_rules_ = mi_rules - , mi_trust_ = mi_trust - , mi_trust_pkg_ = mi_trust_pkg - , mi_complete_matches_ = mi_complete_matches + , mi_public_ = mi_public at IfacePublic { + mi_exports_ = mi_exports + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_defaults_ = mi_defaults + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mi_decl_warn_fn, + mi_cache_export_warn_fn = mi_export_warn_fn, + mi_cache_fix_fn = mi_fix_fn, + mi_cache_hash_fn = mi_hash_fn + } + , mi_abi_hashes_ = mi_abi_hashes + } , mi_docs_ = mi_docs - , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields , mi_hi_bytes_ = mi_hi_bytes - , mi_self_recomp_info_ = mi_self_recomp_info + , mi_self_recomp_ = mi_self_recomp_info + , mi_simplified_core_ = mi_simplified_core + , mi_top_env_ = mi_top_env } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -107,6 +107,9 @@ module GHC.Utils.Binary simpleBindingNameReader, FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, BinArray, + + -- * FingerprintWithValue + FingerprintWithValue(..) ) where import GHC.Prelude @@ -2088,3 +2091,39 @@ source location as part of a larger structure. instance (Binary v) => Binary (IntMap v) where put_ bh m = put_ bh (IntMap.toAscList m) get bh = IntMap.fromAscList <$> get bh + + +{- +Note [FingerprintWithValue] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +FingerprintWithValue is a wrapper which allows us to store a fingerprint and +optionally the value which was used to create the fingerprint. + +This is useful for storing information in interface files, where we want to +store the fingerprint of the interface file, but also the value which was used +to create the fingerprint (e.g. the DynFlags). + +The wrapper is useful to ensure that the fingerprint can be read quickly without +having to deserialise the value itself. + +-} + +-- | A wrapper which allows us to store a fingerprint and optionally the value which +-- was used to create the fingerprint. +data FingerprintWithValue a = FingerprintWithValue !Fingerprint (Maybe a) + deriving Functor + +instance Binary a => Binary (FingerprintWithValue a) where + put_ bh (FingerprintWithValue fp val) = do + put_ bh fp + lazyPutMaybe bh val + + get bh = do + fp <- get bh + val <- lazyGetMaybe bh + return $ FingerprintWithValue fp val + +instance NFData a => NFData (FingerprintWithValue a) where + rnf (FingerprintWithValue fp mflags) + = rnf fp `seq` rnf mflags `seq` () \ No newline at end of file ===================================== ghc/Main.hs ===================================== @@ -1133,6 +1133,8 @@ abiHash strs = do mods <- mapM find_it strs + -- MP: loadUserInterface is inefficient here since we will never find a cached + -- interface. computeInterface is probably better. let get_iface modl = loadUserInterface NotBoot (text "abiHash") modl ifaces <- initIfaceCheck (text "abiHash") hsc_env $ mapM get_iface mods @@ -1140,7 +1142,7 @@ abiHash strs = do put_ bh hiVersion -- package hashes change when the compiler version changes (for now) -- see #5328 - mapM_ (put_ bh . mi_mod_hash . mi_final_exts) ifaces + mapM_ (put_ bh . mi_mod_hash) ifaces f <- fingerprintBinMem bh putStrLn (showPpr dflags f) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9d84972fb5489ea924a4022dbd782e4726733b5a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9d84972fb5489ea924a4022dbd782e4726733b5a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/7d942468/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 12:02:32 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Mar 2025 08:02:32 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] Apply rules before simplifying Message-ID: <67d41ad84d941_21899f412c6018739@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: e6ecb199 by Simon Peyton Jones at 2025-03-14T11:47:20+00:00 Apply rules before simplifying ...only for class-ops Reduces calls to tryRules, which is especially important for primop constant-folding, where rule-matching is quite expensive - - - - - 1 changed file: - compiler/GHC/Core/Opt/Simplify/Iteration.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -1540,7 +1540,7 @@ rebuild_go env expr cont -> rebuildCase (se `setInScopeFromE` env) expr bndr alts cont StrictArg { sc_fun = fun, sc_cont = cont, sc_fun_ty = fun_ty } - -> rebuildCall env (addValArgTo fun expr fun_ty ) cont + -> rebuildCall env (addValArgTo fun expr fun_ty) cont StrictBind { sc_bndr = b, sc_body = body, sc_env = se , sc_cont = cont, sc_from = from_what } @@ -2328,7 +2328,9 @@ simplOutId env fun cont ; rule_base <- getSimplRules ; let rules_for_me = getRules rule_base fun out_args = contOutArgs env cont1 :: [OutExpr] - ; mb_match <- tryRules zapped_env rules_for_me fun out_args + ; mb_match <- if isClassOpId fun + then tryRules zapped_env rules_for_me fun out_args + else return Nothing ; case mb_match of { Just (rule_arity, rhs) -> simplExprF zapped_env rhs $ dropContArgs rule_arity cont1 ; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6ecb1999aff700fb971eed6557403c7de7fcefc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6ecb1999aff700fb971eed6557403c7de7fcefc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/38b901f9/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 12:11:41 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Mar 2025 08:11:41 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: interfaces: Ensure that forceModIface deeply forces a ModIface Message-ID: <67d41cfde269b_21899f86c39c23720@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - abbfcd5e by sheaf at 2025-03-14T08:11:29-04:00 Don't report used duplicate record fields as unused This commit fixes the bug reported in #24035 in which the import of a duplicate record field could be erroneously reported as unused. The issue is that an import of the form "import M (fld)" can import several different 'Name's, and we should only report an error if ALL of those 'Name's are unused, not if ANY are. Note [Reporting unused imported duplicate record fields] in GHC.Rename.Names explains the solution to this problem. Fixes #24035 - - - - - c3b77039 by Matthew Pickering at 2025-03-14T08:11:29-04:00 binary: Directly copy ShortByteString to buffer rather than go via ByteString This avoids allocating an intermediate bytestring. I just noticed on a profile that `putFS` was allocating, and it seemed strange to me why since it should just copy the contents of the FastString into the already allocated buffer. It turned out we were going indirectly via a ByteString. Fixes #25861 - - - - - 47 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - libraries/ghc-boot/GHC/Serialized.hs - testsuite/tests/deriving/should_compile/T17324.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/module/T11970A.stderr - testsuite/tests/module/mod176.stderr - testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr - testsuite/tests/rename/should_compile/T14881.stderr - + testsuite/tests/rename/should_compile/T24035.hs - + testsuite/tests/rename/should_compile/T24035_aux.hs - + testsuite/tests/rename/should_compile/T24035b.hs - + testsuite/tests/rename/should_compile/T24035b.stderr - testsuite/tests/rename/should_compile/all.T - utils/dump-decls/Main.hs - utils/haddock/haddock-api/src/Haddock/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5346c9c653dc5a65f3f476956ac18ed21af3049c...c3b770390fee5cc9c170e745b6c513a4aa67868b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5346c9c653dc5a65f3f476956ac18ed21af3049c...c3b770390fee5cc9c170e745b6c513a4aa67868b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/a7cff15a/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 14 13:17:09 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 14 Mar 2025 09:17:09 -0400 Subject: [Git][ghc/ghc][wip/refactor-iface] Apply 2 suggestion(s) to 1 file(s) Message-ID: <67d42c55d3fda_23186e70326c7102f@gitlab.mail> Matthew Pickering pushed to branch wip/refactor-iface at Glasgow Haskell Compiler / GHC Commits: aee6cf07 by Matthew Pickering at 2025-03-14T13:17:05+00:00 Apply 2 suggestion(s) to 1 file(s) Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 1 changed file: - compiler/GHC/Utils/Binary.hs Changes: ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -2093,10 +2093,8 @@ instance (Binary v) => Binary (IntMap v) where get bh = IntMap.fromAscList <$> get bh -{- -Note [FingerprintWithValue] -~~~~~~~~~~~~~~~~~~~~~~~~~~~ - +{- Note [FingerprintWithValue] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ FingerprintWithValue is a wrapper which allows us to store a fingerprint and optionally the value which was used to create the fingerprint. @@ -2106,7 +2104,6 @@ to create the fingerprint (e.g. the DynFlags). The wrapper is useful to ensure that the fingerprint can be read quickly without having to deserialise the value itself. - -} -- | A wrapper which allows us to store a fingerprint and optionally the value which View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aee6cf07f486388b289ac9d100ef5070249476fd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aee6cf07f486388b289ac9d100ef5070249476fd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/cd8377f1/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 13:18:08 2025 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 14 Mar 2025 09:18:08 -0400 Subject: [Git][ghc/ghc][wip/refactor-iface] iface: Store logical parts of ModIface together Message-ID: <67d42c90d1b08_23186e6af7847277d@gitlab.mail> Matthew Pickering pushed to branch wip/refactor-iface at Glasgow Haskell Compiler / GHC Commits: d391272e by Matthew Pickering at 2025-03-14T13:17:30+00:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore ------------------------- - - - - - 17 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - ghc/Main.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -100,29 +100,37 @@ module GHC ( findGlobalAnns, mkNamePprCtxForModule, ModIface, - ModIface_( - mi_module, - mi_sig_of, - mi_hsc_src, - mi_hi_bytes, - mi_deps, - mi_exports, - mi_fixities, - mi_warns, - mi_anns, - mi_insts, - mi_fam_insts, - mi_rules, - mi_decls, - mi_extra_decls, - mi_top_env, - mi_trust, - mi_trust_pkg, - mi_complete_matches, - mi_docs, - mi_final_exts, - mi_ext_fields - ), + ModIface_( mi_mod_info + , mi_module + , mi_sig_of + , mi_hsc_src + , mi_iface_hash + , mi_deps + , mi_public + , mi_exports + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_defaults + , mi_simplified_core + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_abi_hashes + , mi_ext_fields + , mi_hi_bytes + , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn + ), pattern ModIface, SafeHaskellMode(..), ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -844,7 +844,7 @@ hscRecompStatus case recomp_if_result of OutOfDateItem reason mb_checked_iface -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ fmap (mi_iface_hash . mi_final_exts) mb_checked_iface + return $ HscRecompNeeded $ fmap mi_iface_hash mb_checked_iface UpToDateItem checked_iface -> do let lcl_dflags = ms_hspp_opts mod_summary if | not (backendGeneratesCode (backend lcl_dflags)) -> do @@ -862,7 +862,7 @@ hscRecompStatus , xopt LangExt.TemplateHaskell lcl_dflags -> do msg $ needsRecompileBecause THWithJS - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface | otherwise -> do -- Do need linkable @@ -918,7 +918,7 @@ hscRecompStatus return $ HscUpToDate checked_iface $ linkable OutOfDateItem reason _ -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface -- | Check that the .o files produced by compilation are already up-to-date -- or not. @@ -968,10 +968,8 @@ loadByteCode iface mod_sum = do let this_mod = ms_mod mod_sum if_date = fromJust $ ms_iface_date mod_sum - case mi_extra_decls iface of - Just extra_decls -> do - let fi = WholeCoreBindings extra_decls this_mod (ms_location mod_sum) - (mi_foreign iface) + case iface_core_bindings iface (ms_location mod_sum) of + Just fi -> do return (UpToDateItem (Linkable if_date this_mod (NE.singleton (CoreBindings fi)))) _ -> return $ outOfDateItemBecause MissingBytecode Nothing @@ -1019,15 +1017,15 @@ compile_for_interpreter hsc_env use = -- | Assemble 'WholeCoreBindings' if the interface contains Core bindings. iface_core_bindings :: ModIface -> ModLocation -> Maybe WholeCoreBindings iface_core_bindings iface wcb_mod_location = - mi_extra_decls <&> \ wcb_bindings -> + mi_simplified_core <&> \(IfaceSimplifiedCore bindings foreign') -> WholeCoreBindings { - wcb_bindings, + wcb_bindings = bindings, wcb_module = mi_module, wcb_mod_location, - wcb_foreign = mi_foreign + wcb_foreign = foreign' } where - ModIface {mi_module, mi_extra_decls, mi_foreign} = iface + ModIface {mi_module, mi_simplified_core} = iface -- | Return an 'IO' that hydrates Core bindings and compiles them to bytecode if -- the interface contains any, using the supplied type env for typechecking. @@ -1376,7 +1374,7 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do -- dynamic interfaces. Hopefully both the dynamic and the non-dynamic -- interfaces stay in sync... -- - let change = old_iface /= Just (mi_iface_hash (mi_final_exts iface)) + let change = old_iface /= Just (mi_iface_hash iface) let dt = dynamicTooState dflags ===================================== compiler/GHC/HsToCore/Usage.hs ===================================== @@ -185,7 +185,7 @@ mkObjectUsage pit plugins fc hug th_links_needed th_pkgs_needed = do case miface of Nothing -> pprPanic "mkObjectUsage" (ppr m) Just iface -> - return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash (mi_final_exts iface)) + return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash iface) librarySpecToUsage :: LibrarySpec -> IO [Usage] librarySpecToUsage (Objects os) = traverse (fing Nothing) os @@ -278,10 +278,10 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names usg_entities = Map.toList ent_hashs, usg_safe = imp_safe } where - finsts_mod = mi_finsts (mi_final_exts iface) - hash_env = mi_hash_fn (mi_final_exts iface) - mod_hash = mi_mod_hash (mi_final_exts iface) - export_hash | depend_on_exports = Just (mi_exp_hash (mi_final_exts iface)) + finsts_mod = mi_finsts iface + hash_env = mi_hash_fn iface + mod_hash = mi_mod_hash iface + export_hash | depend_on_exports = Just (mi_exp_hash iface) | otherwise = Nothing by_is_safe (ImportedByUser imv) = imv_is_safe imv ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -41,34 +41,28 @@ data IfaceDynFlags = IfaceDynFlags , ifaceCallerCCFilters :: [CallerCcFilter] } -pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc -pprIfaceDynFlags (f, mflags) = - vcat $ - [ text "fingerprint:" <+> (ppr f) - ] - ++ case mflags of - Nothing -> [missingExtraFlagInfo] - Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> - [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) - , text "safe-mode:" <+> ppr a2 - , text "lang:" <+> ppr a3 - , text "exts:" <+> ppr a4 - , text "cpp-options:" - , nest 2 $ ppr a5 - , text "js-options:" - , nest 2 $ ppr a6 - , text "cmm-options:" - , nest 2 $ ppr a7 - , text "paths:" <+> hcat (map text a8) - , text "prof:" <+> ppr a9 - , text "ticky:" - , nest 2 $ vcat (map ppr a10) - , text "codegen:" - , nest 2 $ vcat (map ppr a11) - , text "fat-iface:" <+> ppr a12 - , text "debug-level:" <+> ppr a13 - , text "caller-cc-filters:" <+> ppr a14 - ] +pprIfaceDynFlags :: IfaceDynFlags -> SDoc +pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + vcat [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] missingExtraFlagInfo :: SDoc missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,7 +59,6 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields -import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -74,7 +73,6 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Logger -import GHC.Utils.Fingerprint( Fingerprint ) import GHC.Settings.Constants @@ -644,7 +642,7 @@ loadInterface doc_str mod from & set_mi_fam_insts (panic "No mi_fam_insts in PIT") & set_mi_rules (panic "No mi_rules in PIT") & set_mi_anns (panic "No mi_anns in PIT") - & set_mi_extra_decls (panic "No mi_extra_decls in PIT") + & set_mi_simplified_core (panic "No mi_simplified_core in PIT") bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1083,7 +1081,7 @@ load_dynamic_too :: Logger -> NameCache -> UnitState -> DynFlags load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do read_file logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case Succeeded (dynIface, _) - | mi_mod_hash (mi_final_exts iface) == mi_mod_hash (mi_final_exts dynIface) + | mi_mod_hash iface == mi_mod_hash dynIface -> return (Succeeded ()) | otherwise -> do return $ (Failed $ DynamicHashMismatchError wanted_mod loc) @@ -1174,11 +1172,10 @@ ghcPrimIface & set_mi_exports ghcPrimExports & set_mi_decls [] & set_mi_fixities ghcPrimFixities - & set_mi_final_exts ((mi_final_exts empty_iface) - { mi_fix_fn = mkIfaceFixCache ghcPrimFixities - , mi_decl_warn_fn = mkIfaceDeclWarnCache ghcPrimWarns - , mi_export_warn_fn = mkIfaceExportWarnCache ghcPrimWarns - }) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) + & set_mi_decl_warn_fn (mkIfaceDeclWarnCache ghcPrimWarns) + & set_mi_export_warn_fn (mkIfaceExportWarnCache ghcPrimWarns) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] in GHC.Builtin.Utils & set_mi_warns (toIfaceWarnings ghcPrimWarns) -- See Note [GHC.Prim Deprecations] in GHC.Builtin.Utils @@ -1263,21 +1260,14 @@ pprModIface unit_state iface = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") - <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) - <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) + <+> (if mi_orphan iface then text "[orphan module]" else Outputable.empty) + <+> (if mi_finsts iface then text "[family instance module]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) - , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) - , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat - [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) - , nest 2 (text "opt_hash:" <+> ppr opt_hash) - , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) - , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) - , vcat (map pprUsage usages) - ] - , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) + , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash iface)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash iface)) + , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash iface)) + , withSelfRecomp iface empty ppr + , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "where") , text "exports:" @@ -1288,10 +1278,14 @@ pprModIface unit_state iface , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] - , case mi_extra_decls iface of + , case mi_simplified_core iface of Nothing -> empty - Just eds -> text "extra decls:" - $$ nest 2 (vcat ([ppr bs | bs <- eds])) + Just (IfaceSimplifiedCore eds fs) -> + vcat [ text "extra decls:" + $$ nest 2 (vcat ([ppr bs | bs <- eds])) + , text "foreign stubs:" + $$ nest 2 (ppr fs) + ] , vcat (map ppr (mi_insts iface)) , vcat (map ppr (mi_fam_insts iface)) , vcat (map ppr (mi_rules iface)) @@ -1303,7 +1297,6 @@ pprModIface unit_state iface , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where - exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" @@ -1329,35 +1322,6 @@ pprExport avail@(AvailTC n _) = pp_export [] = Outputable.empty pp_export names = braces (hsep (map ppr names)) -pprUsage :: Usage -> SDoc -pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } - = pprUsageImport mod hash safe -pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name - , usg_mod_hash = hash, usg_safe = safe - , usg_exports = exports, usg_entities = entities } - = pprUsageImport (mkModule unit_id mod_name) hash safe $$ - nest 2 ( - maybe Outputable.empty (\v -> text "exports: " <> ppr v) exports $$ - vcat [ ppr n <+> ppr v | (n,v) <- entities ] - ) -pprUsage usage at UsageFile{} - = hsep [text "addDependentFile", - doubleQuotes (ftext (usg_file_path usage)), - ppr (usg_file_hash usage)] -pprUsage usage at UsageMergedRequirement{} - = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] -pprUsage usage at UsageHomeModuleInterface{} - = hsep [text "implementation", ppr (usg_mod_name usage) - , ppr (usg_unit_id usage) - , ppr (usg_iface_hash usage)] - -pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc -pprUsageImport mod hash safe - = hsep [ text "import", pp_safe, ppr mod - , ppr hash ] - where - pp_safe | safe = text "safe" - | otherwise = text " -/ " pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -88,13 +88,13 @@ import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModSummary import GHC.Unit.Module.Deps -import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign, emptyIfaceForeign) import Data.Function import Data.List ( sortBy ) import Data.Ord import Data.IORef - +import Data.Traversable {- ************************************************************************ @@ -143,11 +143,13 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos stubs foreign_files = updateDecl (mi_decls partial_iface) mb_stg_infos mb_cmm_infos -- See Note [Foreign stubs and TH bytecode linking] - foreign_ <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + mi_simplified_core <- for (mi_simplified_core partial_iface) $ \simpl_core -> do + fs <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + return $ (simpl_core { mi_sc_foreign = fs }) full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env $ set_mi_foreign foreign_ $ set_mi_decls decls partial_iface + addFingerprints hsc_env $ set_mi_simplified_core mi_simplified_core $ set_mi_decls decls partial_iface -- Debug printing let unit_state = hsc_units hsc_env @@ -289,7 +291,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode - -> Maybe ModIfaceSelfRecomp + -> Maybe IfaceSelfRecomp -> Maybe Docs -> ModDetails -> PartialModIface @@ -316,8 +318,8 @@ mkIface_ hsc_env entities = typeEnvElts type_env show_linear_types = xopt LangExt.LinearTypes (hsc_dflags hsc_env) - extra_decls = if gopt Opt_WriteIfSimplifiedCore dflags then Just [ toIfaceTopBind b | b <- core_prog ] - else Nothing + simplified_core = if gopt Opt_WriteIfSimplifiedCore dflags then Just (IfaceSimplifiedCore [ toIfaceTopBind b | b <- core_prog ] emptyIfaceForeign) + else Nothing decls = [ tyThingToIfaceDecl show_linear_types entity | entity <- entities, let name = getName entity, @@ -370,12 +372,12 @@ mkIface_ hsc_env & set_mi_anns annotations & set_mi_top_env rdrs & set_mi_decls decls - & set_mi_extra_decls extra_decls + & set_mi_simplified_core simplified_core & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) & set_mi_docs docs - & set_mi_final_exts () + & set_mi_abi_hashes () & set_mi_ext_fields emptyExtensibleFields & set_mi_hi_bytes PartialIfaceBinHandle ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -88,6 +88,7 @@ import Data.Ord import Data.Containers.ListUtils import Data.Bifunctor import GHC.Iface.Errors.Ppr +import Data.Functor {- ----------------------------------------------- @@ -325,8 +326,8 @@ check_old_iface hsc_env mod_summary maybe_iface maybe_dyn_iface <- liftIO $ loadIface (setDynamicNow dflags) (msDynHiFilePath mod_summary) case maybe_dyn_iface of Nothing -> return $ outOfDateItemBecause MissingDynHiFile Nothing - Just dyn_iface | mi_iface_hash (mi_final_exts dyn_iface) - /= mi_iface_hash (mi_final_exts normal_iface) + Just dyn_iface | mi_iface_hash dyn_iface + /= mi_iface_hash normal_iface -> return $ outOfDateItemBecause MismatchedDynHiFile Nothing Just {} -> return res _ -> return res @@ -382,7 +383,7 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface - -> ModIfaceSelfRecomp + -> IfaceSelfRecomp -> IfG (MaybeValidated ModIface) checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger @@ -435,7 +436,7 @@ checkVersions hsc_env mod_summary iface self_recomp -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins :: Plugins -> IfaceSelfRecomp -> IfG RecompileRequired checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp @@ -528,10 +529,10 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash :: HscEnv -> Module -> IfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + let FingerprintWithValue old_fp old_flags = mi_sr_flag_hash self_recomp (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally if old_fp == new_fp then up_to_date logger (text "Module flags unchanged") @@ -573,7 +574,7 @@ checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkOptimHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env let old_hash = mi_sr_opt_hash iface @@ -589,7 +590,7 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env let old_hash = mi_sr_hpc_hash self_recomp @@ -606,7 +607,7 @@ checkHpcHash hsc_env self_recomp = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures :: HscEnv -> ModSummary -> IfaceSelfRecomp -> IO RecompileRequired checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env @@ -748,7 +749,7 @@ checkModUsage _ UsagePackageModule{ logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChanged (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) -- We only track the ABI hash of package modules, rather than -- individual entity usages, so if the ABI hash changes we must -- recompile. This is safe but may entail more recompilation when @@ -758,7 +759,7 @@ checkModUsage _ UsageMergedRequirement{ usg_mod = mod, usg_mod_hash = old_mod_ha logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedRaw (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name , usg_unit_id = uid , usg_iface_hash = old_mod_hash } = do @@ -766,7 +767,7 @@ checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedIface mod_name - checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash (mi_final_exts iface)) + checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash iface) checkModUsage _ UsageHomeModule{ usg_mod_name = mod_name, @@ -779,9 +780,9 @@ checkModUsage _ UsageHomeModule{ logger <- getLogger needInterface mod $ \iface -> do let - new_mod_hash = mi_mod_hash (mi_final_exts iface) - new_decl_hash = mi_hash_fn (mi_final_exts iface) - new_export_hash = mi_exp_hash (mi_final_exts iface) + new_mod_hash = mi_mod_hash iface + new_decl_hash = mi_hash_fn iface + new_export_hash = mi_exp_hash iface reason = ModuleChanged (moduleName mod) @@ -986,7 +987,7 @@ we use is: -- | Compute the information needed for self-recompilation checking. This -- information can be computed before the backend phase. -mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO IfaceSelfRecomp mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env @@ -1000,10 +1001,10 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do let include_detailed_flags (flag_hash, flags) = if gopt Opt_WriteSelfRecompFlags dflags - then (flag_hash, Just flags) - else (flag_hash, Nothing) + then FingerprintWithValue flag_hash (Just flags) + else FingerprintWithValue flag_hash Nothing - return (ModIfaceSelfRecomp + return (IfaceSelfRecomp { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash @@ -1018,28 +1019,92 @@ addFingerprints :: HscEnv -> PartialModIface -> IO ModIface -addFingerprints hsc_env iface0 - = do - eps <- hscEPS hsc_env - let - decls = mi_decls iface0 - decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings $ mi_warns iface0) - export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ mi_warns iface0) - fix_fn = mkIfaceFixCache (mi_fixities iface0) +addFingerprints hsc_env iface0 = do + (abiHashes, caches, decls_w_hashes) <- addAbiHashes hsc_env (mi_mod_info iface0) (mi_public iface0) (mi_deps iface0) + + -- put the declarations in a canonical order, sorted by OccName + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ + [(getOccName d, e) | e@(_, d) <- decls_w_hashes] + + -- This key is safe because mi_extra_decls contains tidied things. + getOcc (IfGblTopBndr b) = getOccName b + getOcc (IfLclTopBndr fs _ _ details) = + case details of + IfRecSelId { ifRecSelFirstCon = first_con } + -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) + _ -> mkVarOccFS (ifLclNameFS fs) + + binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () + binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) + + sorted_extra_decls :: Maybe IfaceSimplifiedCore + sorted_extra_decls = mi_simplified_core iface0 <&> \simpl_core -> + IfaceSimplifiedCore (sortOn binding_key (mi_sc_extra_decls simpl_core)) (mi_sc_foreign simpl_core) + + -- The interface hash depends on: + -- - the ABI hash, plus + -- - the things which can affect whether a module is recompiled + -- - the module level annotations, + -- - deps (home and external packages, dependent files) + iface_hash <- computeFingerprint putNameLiterally + (mi_abi_mod_hash abiHashes, + mi_self_recomp_info iface0, + mi_deps iface0) + + let final_iface = completePartialModIface iface0 iface_hash + sorted_decls sorted_extra_decls abiHashes caches + -- + return final_iface + + + +-- The ABI hash should depend on everything in IfacePublic +-- This is however computed in a very convoluted way, so be careful your +-- addition ends up in the right place. In essence all this function does is +-- compute a hash of the arguments. +-- +-- Why the convoluted way? Hashing individual declarations allows us to do fine-grained +-- recompilation checking for home package modules, which record precisely what they use +-- from each module. +addAbiHashes :: HscEnv -> IfaceModInfo -> PartialIfacePublic -> Dependencies -> IO (IfaceAbiHashes, IfaceCache, [(Fingerprint, IfaceDecl)]) +addAbiHashes hsc_env info iface_public deps = do + eps <- hscEPS hsc_env + let + -- If you have arrived here by accident then congratulations, + -- you have discovered the ABI hash. Your reward is to update the ABI hash to + -- account for your change to the interface file. Omitting your field using a + -- wildcard may lead to some unfortunate consequences. + + -- MP: TODO: Existing bug where defaults, trust_pkg and complete are not taken into account + -- when computing the ABI hash. + IfacePublic exports fixities warns anns decls _defaults insts fam_insts rules trust _trust_pkg _complete _cache () = iface_public + -- And these fields of deps should be in IfacePublic, but in good time. + Dependencies _ _ _ sig_mods trusted_pkgs boot_mods orph_mods fis_mods = deps + decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings warns) + export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ warns) + fix_fn = mkIfaceFixCache fixities + + this_mod = mi_mod_info_module info + semantic_mod = mi_mod_info_semantic_module info + (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph insts + (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph rules + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph fam_insts + ann_fn = mkIfaceAnnCache anns -- The ABI of a declaration represents everything that is made -- visible about the declaration that a client can depend on. -- see IfaceDeclABI below. - declABI :: IfaceDecl -> IfaceDeclABI + declABI :: IfaceDecl -> IfaceDeclABI -- TODO: I'm not sure if this should be semantic_mod or this_mod. -- See also Note [Identity versus semantic module] - declABI decl = (this_mod, decl, extras) + declABI decl = (this_mod, decl, extras) where extras = declExtras fix_fn ann_fn non_orph_rules non_orph_insts non_orph_fis top_lvl_name_env decl -- This is used for looking up the Name of a default method -- from its OccName. See Note [default method Name] - top_lvl_name_env = + top_lvl_name_env = mkOccEnv [ (nameOccName nm, nm) | IfaceId { ifName = nm } <- decls ] @@ -1047,15 +1112,15 @@ addFingerprints hsc_env iface0 -- This is computed by finding the free external names of each -- declaration, including IfaceDeclExtras (things that a -- declaration implicitly depends on). - edges :: [ Node OccName IfaceDeclABI ] - edges = [ DigraphNode abi (getOccName decl) out + edges :: [ Node OccName IfaceDeclABI ] + edges = [ DigraphNode abi (getOccName decl) out | decl <- decls , let abi = declABI decl , let out = localOccs $ freeNamesDeclABI abi ] - name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) - localOccs = + name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) + localOccs = map (getParent . getOccName) -- NB: names always use semantic module, so -- filtering must be on the semantic module! @@ -1073,17 +1138,17 @@ addFingerprints hsc_env iface0 -- maps OccNames to their parents in the current module. -- e.g. a reference to a constructor must be turned into a reference -- to the TyCon for the purposes of calculating dependencies. - parent_map :: OccEnv OccName - parent_map = foldl' extend emptyOccEnv decls + parent_map :: OccEnv OccName + parent_map = foldl' extend emptyOccEnv decls where extend env d = extendOccEnvList env [ (b,n) | b <- ifaceDeclImplicitBndrs d ] where n = getOccName d -- Strongly-connected groups of declarations, in dependency order - groups :: [SCC IfaceDeclABI] - groups = stronglyConnCompFromEdgedVerticesOrd edges + groups :: [SCC IfaceDeclABI] + groups = stronglyConnCompFromEdgedVerticesOrd edges - global_hash_fn = mkHashFun hsc_env eps + global_hash_fn = mkHashFun hsc_env eps -- How to output Names when generating the data to fingerprint. -- Here we want to output the fingerprint for each top-level @@ -1091,9 +1156,9 @@ addFingerprints hsc_env iface0 -- module. In this way, the fingerprint for a declaration will -- change if the fingerprint for anything it refers to (transitively) -- changes. - mk_put_name :: OccEnv (OccName,Fingerprint) + mk_put_name :: OccEnv (OccName,Fingerprint) -> WriteBinHandle -> Name -> IO () - mk_put_name local_env bh name + mk_put_name local_env bh name | isWiredInName name = putNameLiterally bh name -- wired-in names don't have fingerprints | otherwise @@ -1120,21 +1185,21 @@ addFingerprints hsc_env iface0 -- take a strongly-connected group of declarations and compute -- its fingerprint. - fingerprint_group :: (OccEnv (OccName,Fingerprint), + fingerprint_group :: (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) -> SCC IfaceDeclABI -> IO (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) - fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) - = do let hash_fn = mk_put_name local_env - decl = abiDecl abi + fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) + = do let hash_fn = mk_put_name local_env + decl = abiDecl abi --pprTrace "fingerprinting" (ppr (ifName decl) ) $ do - hash <- computeFingerprint hash_fn abi - env' <- extend_hash_env local_env (hash,decl) - return (env', (hash,decl) : decls_w_hashes) + hash <- computeFingerprint hash_fn abi + env' <- extend_hash_env local_env (hash,decl) + return (env', (hash,decl) : decls_w_hashes) - fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) + fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) = do let stable_abis = sortBy cmp_abiNames abis stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env @@ -1150,33 +1215,27 @@ addFingerprints hsc_env iface0 return (local_env2, pairs ++ decls_w_hashes) -- Make a fingerprint from the ordinal position of a binding in its group. - mkRecFingerprint :: Word64 -> Fingerprint - mkRecFingerprint i = Fingerprint 0 i + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i - bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint - bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. -- - extend_hash_env :: OccEnv (OccName,Fingerprint) + extend_hash_env :: OccEnv (OccName,Fingerprint) -> (Fingerprint,IfaceDecl) -> IO (OccEnv (OccName,Fingerprint)) - extend_hash_env env0 (hash,d) = + extend_hash_env env0 (hash,d) = return (foldr (\(b,fp) env -> extendOccEnv env b (b,fp)) env0 (ifaceDeclFingerprints hash d)) -- - (local_env, decls_w_hashes) <- + (local_env, decls_w_hashes) <- foldM fingerprint_group (emptyOccEnv, []) groups - -- when calculating fingerprints, we always need to use canonical ordering - -- for lists of things. The mi_deps has various lists of modules and - -- suchlike, which are stored in canonical order: - let sorted_deps :: Dependencies - sorted_deps = mi_deps iface0 - -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way -- that changes in orphans get propagated all the way up the @@ -1202,10 +1261,11 @@ addFingerprints hsc_env iface0 -- External. It's true that Home1 will get rebuilt if the orphans -- of External, but we also need to make sure Home2 gets rebuilt -- as well. See #12733 for more details. - let orph_mods - = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] - $ dep_orphs sorted_deps - dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods + let orph_mods_no_self + = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] + $ orph_mods + dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods_no_self + -- Note [Do not update EPS with your own hi-boot] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1216,26 +1276,26 @@ addFingerprints hsc_env iface0 -- instances yourself, no need to consult hs-boot; if you do load the -- interface into EPS, you will see a duplicate orphan instance. - orphan_hash <- computeFingerprint (mk_put_name local_env) + orphan_hash <- computeFingerprint (mk_put_name local_env) (map ifDFun orph_insts, orph_rules, orph_fis) - -- Hash of the transitive things in dependencies - dep_hash <- computeFingerprint putNameLiterally - (dep_sig_mods (mi_deps iface0), - dep_boot_mods (mi_deps iface0), - -- Trusted packages are like orphans - dep_trusted_pkgs (mi_deps iface0), + -- Hash of the transitive things in dependencies + dep_hash <- computeFingerprint putNameLiterally + (sig_mods, + boot_mods, + -- Trusted packages are like orphans + trusted_pkgs, -- See Note [Export hash depends on non-orphan family instances] - dep_finsts (mi_deps iface0) ) + fis_mods ) - -- the export list hash doesn't depend on the fingerprints of - -- the Names it mentions, only the Names themselves, hence putNameLiterally. - export_hash <- computeFingerprint putNameLiterally - (mi_exports iface0, + -- the export list hash doesn't depend on the fingerprints of + -- the Names it mentions, only the Names themselves, hence putNameLiterally. + export_hash <- computeFingerprint putNameLiterally + (exports, orphan_hash, dep_hash, dep_orphan_hashes, - mi_trust iface0) + trust) -- Make sure change of Safe Haskell mode causes recomp. -- Note [Export hash depends on non-orphan family instances] @@ -1266,79 +1326,44 @@ addFingerprints hsc_env iface0 -- (also we didn't store it anywhere!) -- - -- put the declarations in a canonical order, sorted by OccName - let sorted_decls :: [(Fingerprint, IfaceDecl)] - sorted_decls = Map.elems $ Map.fromList $ - [(getOccName d, e) | e@(_, d) <- decls_w_hashes] - -- This key is safe because mi_extra_decls contains tidied things. - getOcc (IfGblTopBndr b) = getOccName b - getOcc (IfLclTopBndr fs _ _ details) = - case details of - IfRecSelId { ifRecSelFirstCon = first_con } - -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) - _ -> mkVarOccFS (ifLclNameFS fs) - - binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () - binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) - - sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - - -- the ABI hash depends on: - -- - decls - -- - export list - -- - orphans - -- - deprecations - -- - flag abi hash - -- - foreign stubs and files - mod_hash <- computeFingerprint putNameLiterally - (map fst sorted_decls, + -- the ABI hash depends on: + -- - decls + -- - export list + -- - orphans + -- - deprecations + -- - flag abi hash + mod_hash <- computeFingerprint putNameLiterally + (sort (map fst decls_w_hashes), export_hash, -- includes orphan_hash - mi_warns iface0, - mi_foreign iface0) - - - -- The interface hash depends on: - -- - the ABI hash, plus - -- - the things which can affect whether a module is recompiled - -- - the module level annotations, - -- - deps (home and external packages, dependent files) - iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_self_recomp_info iface0, - sorted_deps ) + ann_fn AnnModule, + warns) - let - final_iface_exts = ModIfaceBackend - { mi_mod_hash = mod_hash - , mi_iface_hash = iface_hash - , mi_orphan = not ( all ifRuleAuto orph_rules + -- Surely the ABI depends on "module" annotations? + -- Also named defaults + + + + let + final_iface_exts = IfaceAbiHashes + { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts && null orph_fis) - , mi_finsts = not (null (mi_fam_insts iface0)) - , mi_exp_hash = export_hash - , mi_orphan_hash = orphan_hash - , mi_decl_warn_fn = decl_warn_fn - , mi_export_warn_fn = export_warn_fn - , mi_fix_fn = fix_fn - , mi_hash_fn = lookupOccEnv local_env + , mi_abi_finsts = not (null fam_insts) + , mi_abi_exp_hash = export_hash + , mi_abi_orphan_hash = orphan_hash } - final_iface = completePartialModIface iface0 - sorted_decls sorted_extra_decls final_iface_exts - -- - return final_iface + caches = IfaceCache + { mi_cache_decl_warn_fn = decl_warn_fn + , mi_cache_export_warn_fn = export_warn_fn + , mi_cache_fix_fn = fix_fn + , mi_cache_hash_fn = lookupOccEnv local_env + } + return (final_iface_exts, caches, decls_w_hashes) where - this_mod = mi_module iface0 - semantic_mod = mi_semantic_module iface0 - (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) - (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) - (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - ann_fn = mkIfaceAnnCache (mi_anns iface0) - -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the @@ -1378,7 +1403,7 @@ getOrphanHashes hsc_env mods = do get_orph_hash mod = do iface <- initIfaceLoad hsc_env . withIfaceErr ctx $ loadInterface (text "getOrphanHashes") mod ImportBySystem - return (mi_orphan_hash (mi_final_exts iface)) + return (mi_orphan_hash iface) mapM get_orph_hash mods @@ -1531,7 +1556,7 @@ instance Binary IfaceIdExtras where put_ bh (IdExtras fix rules anns)= do { put_ bh fix; put_ bh rules; put_ bh anns } declExtras :: (OccName -> Maybe Fixity) - -> (OccName -> [AnnPayload]) + -> (AnnCacheKey -> [AnnPayload]) -> OccEnv [IfaceRule] -> OccEnv [IfaceClsInst] -> OccEnv [IfaceFamInst] @@ -1546,10 +1571,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl IfaceDataExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n) ++ map ifDFun (lookupOccEnvL inst_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) (map (id_extras . occName . ifConName) (visibleIfConDecls cons)) IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} -> - IfaceClassExtras (fix_fn n) insts (ann_fn n) meths defms + IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms where insts = (map ifDFun $ (concatMap at_extras ats) ++ lookupOccEnvL inst_env n) @@ -1562,17 +1587,16 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl , let dmOcc = mkDefaultMethodOcc (nameOccName bndr) , Just dmName <- [lookupOccEnv dm_env dmOcc] ] IfaceSynonym{} -> IfaceSynonymExtras (fix_fn n) - (ann_fn n) + (ann_fn (AnnOccName n)) IfaceFamily{} -> IfaceFamilyExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) _other -> IfaceOtherDeclExtras where n = getOccName decl - id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn occ) + id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl) - {- Note [default method Name] (see also #15970) ~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1685,20 +1709,25 @@ mkHashFun hsc_env eps name -- just one of the many horrible hacks in the backpack -- implementation. $ loadInterface (text "lookupVers2") mod ImportBySystem - return $ snd (mi_hash_fn (mi_final_exts iface) occ `orElse` + return $ snd (mi_hash_fn iface occ `orElse` pprPanic "lookupVers1" (ppr mod <+> ppr occ)) +data AnnCacheKey = AnnModule | AnnOccName OccName + -- | Creates cached lookup for the 'mi_anns' field of ModIface -- Hackily, we use "module" as the OccName for any module-level annotations -mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload] +mkIfaceAnnCache :: [IfaceAnnotation] -> AnnCacheKey -> [AnnPayload] mkIfaceAnnCache anns - = \n -> lookupOccEnv env n `orElse` [] + = \n -> case n of + AnnModule -> module_anns + AnnOccName occn -> lookupOccEnv env occn `orElse` [] where - pair (IfaceAnnotation target value) = - (case target of - NamedTarget occn -> occn - ModuleTarget _ -> mkVarOccFS (fsLit "module") - , [value]) + (module_anns, occ_anns) = partitionEithers $ map classify anns + classify (IfaceAnnotation target value) = + case target of + NamedTarget occn -> Right (occn, [value]) + ModuleTarget _ -> Left value + -- flipping (++), so the first argument is always short - env = mkOccEnv_C (flip (++)) (map pair anns) + env = mkOccEnv_C (flip (++)) occ_anns ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,5 +1,5 @@ module GHC.Iface.Recomp.Types ( - ModIfaceSelfRecomp(..), + IfaceSelfRecomp(..), IfaceDynFlags(..), pprIfaceDynFlags, missingExtraFlagInfo, @@ -9,7 +9,9 @@ import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable import GHC.Iface.Flags +import GHC.Types.SafeHaskell import GHC.Unit.Module.Deps +import GHC.Unit.Module import GHC.Utils.Binary @@ -59,8 +61,8 @@ proper way. -- itself. -- -- See Note [Self recompilation information in interface files] -data ModIfaceSelfRecomp = - ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint +data IfaceSelfRecomp = + IfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint -- ^ Hash of the .hs source, used for recompilation checking. , mi_sr_usages :: [Usage] -- ^ Usages; kept sorted so that it's easy to decide @@ -69,7 +71,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) + , mi_sr_flag_hash :: !(FingerprintWithValue IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -81,8 +83,8 @@ data ModIfaceSelfRecomp = } -instance Binary ModIfaceSelfRecomp where - put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do +instance Binary IfaceSelfRecomp where + put_ bh (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do put_ bh mi_sr_src_hash lazyPut bh mi_sr_usages put_ bh mi_sr_flag_hash @@ -97,19 +99,58 @@ instance Binary ModIfaceSelfRecomp where opt_hash <- get bh hpc_hash <- get bh plugin_hash <- get bh - return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + return $ IfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } -instance Outputable ModIfaceSelfRecomp where - ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) +instance Outputable IfaceSelfRecomp where + ppr (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash - , text "usages:" <+> ppr (length mi_sr_usages) - , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash + , text "flags:" <+> pprFingerprintWithValue missingExtraFlagInfo (fmap pprIfaceDynFlags mi_sr_flag_hash) , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash + , text "usages:" <+> ppr (map pprUsage mi_sr_usages) ])] -instance NFData ModIfaceSelfRecomp where - rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file +instance NFData IfaceSelfRecomp where + rnf (IfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () + +pprFingerprintWithValue :: SDoc -> FingerprintWithValue SDoc -> SDoc +pprFingerprintWithValue missingInfo (FingerprintWithValue fp mflags) + = vcat $ + [ text "fingerprint:" <+> (ppr fp) + ] + ++ case mflags of + Nothing -> [missingInfo] + Just doc -> [doc] + +pprUsage :: Usage -> SDoc +pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } + = pprUsageImport mod hash safe +pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name + , usg_mod_hash = hash, usg_safe = safe + , usg_exports = exports, usg_entities = entities } + = pprUsageImport (mkModule unit_id mod_name) hash safe $$ + nest 2 ( + maybe empty (\v -> text "exports: " <> ppr v) exports $$ + vcat [ ppr n <+> ppr v | (n,v) <- entities ] + ) +pprUsage usage at UsageFile{} + = hsep [text "addDependentFile", + doubleQuotes (ftext (usg_file_path usage)), + ppr (usg_file_hash usage)] +pprUsage usage at UsageMergedRequirement{} + = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] +pprUsage usage at UsageHomeModuleInterface{} + = hsep [text "implementation", ppr (usg_mod_name usage) + , ppr (usg_unit_id usage) + , ppr (usg_iface_hash usage)] + +pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc +pprUsageImport mod hash safe + = hsep [ text "import", pp_safe, ppr mod + , ppr hash ] + where + pp_safe | safe = text "safe" + | otherwise = text " -/ " \ No newline at end of file ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -183,7 +183,7 @@ lookupFixityRn_help name -- loadInterfaceForName will find B.hi even if B is a hidden module, -- and that's what we want. = do { iface <- loadInterfaceForName doc name - ; let mb_fix = mi_fix_fn (mi_final_exts iface) occ + ; let mb_fix = mi_fix_fn iface occ ; let msg = case mb_fix of Nothing -> text "looking up name" <+> ppr name ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -485,8 +485,8 @@ calculateAvails :: HomeUnit calculateAvails home_unit other_home_units iface mod_safe' want_boot imported_by = let imp_mod = mi_module iface imp_sem_mod= mi_semantic_module iface - orph_iface = mi_orphan (mi_final_exts iface) - has_finsts = mi_finsts (mi_final_exts iface) + orph_iface = mi_orphan iface + has_finsts = mi_finsts iface deps = mi_deps iface trust = getSafeMode $ mi_trust iface trust_pkg = mi_trust_pkg iface @@ -1397,7 +1397,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) _ -> failLookupWith err mk_depr_export_warning gre - = DeprecatedExport name <$> mi_export_warn_fn (mi_final_exts iface) name + = DeprecatedExport name <$> mi_export_warn_fn iface name where name = greName gre ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -539,9 +539,9 @@ warnIfDeclDeprecated gre@(GRE { gre_imp = iss }) lookupImpDeclDeprec :: ModIface -> GlobalRdrElt -> Maybe (WarningTxt GhcRn) lookupImpDeclDeprec iface gre -- Bleat if the thing, or its parent, is warn'd - = mi_decl_warn_fn (mi_final_exts iface) (greOccName gre) `mplus` + = mi_decl_warn_fn iface (greOccName gre) `mplus` case greParent gre of - ParentIs p -> mi_decl_warn_fn (mi_final_exts iface) (nameOccName p) + ParentIs p -> mi_decl_warn_fn iface (nameOccName p) NoParent -> Nothing warnIfExportDeprecated :: GlobalRdrElt -> RnM () @@ -562,7 +562,7 @@ warnIfExportDeprecated gre@(GRE { gre_imp = iss }) process_import_spec is = do let mod = is_mod $ is_decl is iface <- loadInterfaceForModule doc mod - let mb_warn_txt = mi_export_warn_fn (mi_final_exts iface) name + let mb_warn_txt = mi_export_warn_fn iface name return $ (moduleName mod, ) <$> mb_warn_txt ------------------------- ===================================== compiler/GHC/Tc/Instance/Family.hs ===================================== @@ -308,7 +308,7 @@ checkFamInstConsistency directlyImpMods ifc <- modIface mod deps <- dep_finsts . mi_deps <$> modIface mod pure $ - if mi_finsts (mi_final_exts ifc) + if mi_finsts ifc then mod:deps else deps ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -97,7 +97,7 @@ checkHsigDeclM sig_iface sig_thing real_thing = do -- implementation cases. checkBootDeclM Hsig sig_thing real_thing real_fixity <- lookupFixityRn name - let sig_fixity = case mi_fix_fn (mi_final_exts sig_iface) (occName name) of + let sig_fixity = case mi_fix_fn sig_iface (occName name) of Nothing -> defaultFixity Just f -> f when (real_fixity /= sig_fixity) $ @@ -850,7 +850,7 @@ mergeSignatures if outer_mod == mi_module iface -- Don't add ourselves! then tcg_merged tcg_env - else (mi_module iface, mi_mod_hash (mi_final_exts iface)) : tcg_merged tcg_env + else (mi_module iface, mi_mod_hash iface) : tcg_merged tcg_env } -- Note [Signature merging DFuns] ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -1,18 +1,20 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ExplicitNamespaces #-} -- | Dependencies and Usage of a module module GHC.Unit.Module.Deps - ( Dependencies - , mkDependencies - , noDependencies - , dep_direct_mods - , dep_direct_pkgs - , dep_sig_mods - , dep_trusted_pkgs - , dep_orphs - , dep_plugin_pkgs - , dep_finsts - , dep_boot_mods + ( Dependencies(dep_direct_mods + , dep_direct_pkgs + , dep_sig_mods + , dep_trusted_pkgs + , dep_orphs + , dep_plugin_pkgs + , dep_finsts + , dep_boot_mods + , Dependencies) , dep_orphs_update , dep_finsts_update + , mkDependencies + , noDependencies , pprDeps , Usage (..) , ImportAvails (..) @@ -52,38 +54,38 @@ import Control.DeepSeq -- -- See Note [Transitive Information in Dependencies] data Dependencies = Deps - { dep_direct_mods :: Set (UnitId, ModuleNameWithIsBoot) + { dep_direct_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All home-package modules which are directly imported by this one. -- This may include modules from other units when using multiple home units - , dep_direct_pkgs :: Set UnitId + , dep_direct_pkgs_ :: Set UnitId -- ^ All packages directly imported by this module -- I.e. packages to which this module's direct imports belong. -- Does not include other home units when using multiple home units. -- Modules from these units will go in `dep_direct_mods` - , dep_plugin_pkgs :: Set UnitId + , dep_plugin_pkgs_ :: Set UnitId -- ^ All units needed for plugins ------------------------------------ -- Transitive information below here - , dep_sig_mods :: ![ModuleName] + , dep_sig_mods_ :: ![ModuleName] -- ^ Transitive closure of hsig files in the home package - , dep_trusted_pkgs :: Set UnitId + , dep_trusted_pkgs_ :: Set UnitId -- Packages which we are required to trust -- when the module is imported as a safe import -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names - , dep_boot_mods :: Set (UnitId, ModuleNameWithIsBoot) + , dep_boot_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All modules which have boot files below this one, and whether we -- should use the boot file or not. -- This information is only used to populate the eps_is_boot field. -- See Note [Structure of dep_boot_mods] - , dep_orphs :: [Module] + , dep_orphs_ :: [Module] -- ^ Transitive closure of orphan modules (whether -- home or external pkg). -- @@ -93,7 +95,7 @@ data Dependencies = Deps -- which relies on dep_orphs having the complete list!) -- This does NOT include us, unlike 'imp_orphs'. - , dep_finsts :: [Module] + , dep_finsts_ :: [Module] -- ^ Transitive closure of depended upon modules which -- contain family instances (whether home or external). -- This is used by 'checkFamInstConsistency'. This @@ -105,6 +107,26 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +pattern Dependencies :: Set (UnitId, ModuleNameWithIsBoot) + -> Set UnitId + -> Set UnitId + -> [ModuleName] + -> Set UnitId + -> Set (UnitId, ModuleNameWithIsBoot) + -> [Module] + -> [Module] + -> Dependencies +pattern Dependencies {dep_direct_mods, dep_direct_pkgs, dep_plugin_pkgs, dep_sig_mods, dep_trusted_pkgs, dep_boot_mods, dep_orphs, dep_finsts} + <- Deps {dep_direct_mods_ = dep_direct_mods + , dep_direct_pkgs_ = dep_direct_pkgs + , dep_plugin_pkgs_ = dep_plugin_pkgs + , dep_sig_mods_ = dep_sig_mods + , dep_trusted_pkgs_ = dep_trusted_pkgs + , dep_boot_mods_ = dep_boot_mods + , dep_orphs_ = dep_orphs + , dep_finsts_ = dep_finsts} +{-# COMPLETE Dependencies #-} + instance NFData Dependencies where rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) = rnf dmods @@ -158,14 +180,14 @@ mkDependencies home_unit mod imports plugin_mods = sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports - in Deps { dep_direct_mods = direct_mods - , dep_direct_pkgs = direct_pkgs - , dep_plugin_pkgs = plugin_units - , dep_sig_mods = sort sig_mods - , dep_trusted_pkgs = trust_pkgs - , dep_boot_mods = source_mods - , dep_orphs = sortBy stableModuleCmp dep_orphs - , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) + in Deps { dep_direct_mods_ = direct_mods + , dep_direct_pkgs_ = direct_pkgs + , dep_plugin_pkgs_ = plugin_units + , dep_sig_mods_ = sort sig_mods + , dep_trusted_pkgs_ = trust_pkgs + , dep_boot_mods_ = source_mods + , dep_orphs_ = sortBy stableModuleCmp dep_orphs + , dep_finsts_ = sortBy stableModuleCmp (imp_finsts imports) -- sort to get into canonical order -- NB. remember to use lexicographic ordering } @@ -174,14 +196,13 @@ mkDependencies home_unit mod imports plugin_mods = dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_orphs_update deps f = do r <- f (dep_orphs deps) - pure (deps { dep_orphs = sortBy stableModuleCmp r }) + pure (deps { dep_orphs_ = sortBy stableModuleCmp r }) -- | Update module dependencies containing family instances (used by Backpack) dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_finsts_update deps f = do r <- f (dep_finsts deps) - pure (deps { dep_finsts = sortBy stableModuleCmp r }) - + pure (deps { dep_finsts_ = sortBy stableModuleCmp r }) instance Binary Dependencies where put_ bh deps = do put_ bh (dep_direct_mods deps) @@ -201,36 +222,36 @@ instance Binary Dependencies where sms <- get bh os <- get bh fis <- get bh - return (Deps { dep_direct_mods = dms - , dep_direct_pkgs = dps - , dep_plugin_pkgs = plugin_pkgs - , dep_sig_mods = hsigms - , dep_boot_mods = sms - , dep_trusted_pkgs = tps - , dep_orphs = os, - dep_finsts = fis }) + return (Deps { dep_direct_mods_ = dms + , dep_direct_pkgs_ = dps + , dep_plugin_pkgs_ = plugin_pkgs + , dep_sig_mods_ = hsigms + , dep_boot_mods_ = sms + , dep_trusted_pkgs_ = tps + , dep_orphs_ = os, + dep_finsts_ = fis }) noDependencies :: Dependencies noDependencies = Deps - { dep_direct_mods = Set.empty - , dep_direct_pkgs = Set.empty - , dep_plugin_pkgs = Set.empty - , dep_sig_mods = [] - , dep_boot_mods = Set.empty - , dep_trusted_pkgs = Set.empty - , dep_orphs = [] - , dep_finsts = [] + { dep_direct_mods_ = Set.empty + , dep_direct_pkgs_ = Set.empty + , dep_plugin_pkgs_ = Set.empty + , dep_sig_mods_ = [] + , dep_boot_mods_ = Set.empty + , dep_trusted_pkgs_ = Set.empty + , dep_orphs_ = [] + , dep_finsts_ = [] } -- | Pretty-print unit dependencies pprDeps :: UnitState -> Dependencies -> SDoc -pprDeps unit_state (Deps { dep_direct_mods = dmods - , dep_boot_mods = bmods - , dep_plugin_pkgs = plgns - , dep_orphs = orphs - , dep_direct_pkgs = pkgs - , dep_trusted_pkgs = tps - , dep_finsts = finsts +pprDeps unit_state (Deps { dep_direct_mods_ = dmods + , dep_boot_mods_ = bmods + , dep_plugin_pkgs_ = plgns + , dep_orphs_ = orphs + , dep_direct_pkgs_ = pkgs + , dep_trusted_pkgs_ = tps + , dep_finsts_ = finsts }) = pprWithUnitState unit_state $ vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -11,18 +11,20 @@ module GHC.Unit.Module.ModIface ( ModIface , ModIface_ - ( mi_module + ( mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls , mi_defaults - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_top_env , mi_insts , mi_fam_insts @@ -31,12 +33,17 @@ module GHC.Unit.Module.ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn ) , pattern ModIface + , set_mi_mod_info , set_mi_module , set_mi_sig_of , set_mi_hsc_src @@ -52,24 +59,34 @@ module GHC.Unit.Module.ModIface , set_mi_rules , set_mi_decls , set_mi_defaults - , set_mi_extra_decls - , set_mi_foreign + , set_mi_simplified_core , set_mi_top_env , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches , set_mi_docs - , set_mi_final_exts + , set_mi_abi_hashes , set_mi_ext_fields + , set_mi_caches + , set_mi_decl_warn_fn + , set_mi_export_warn_fn + , set_mi_fix_fn + , set_mi_hash_fn , completePartialModIface , IfaceBinHandle(..) , PartialModIface - , ModIfaceBackend (..) - , ModIfaceSelfRecomp (..) + , IfaceAbiHashes (..) + , IfaceSelfRecomp (..) + , IfaceCache (..) + , IfaceSimplifiedCore (..) , withSelfRecomp , IfaceDeclExts - , IfaceBackendExts + , IfaceAbiHashesExts , IfaceExport + , IfacePublic_(..) + , IfacePublic + , PartialIfacePublic + , IfaceModInfo(..) , WhetherHasOrphans , WhetherHasFamInst , IfaceTopEnv (..) @@ -77,6 +94,7 @@ module GHC.Unit.Module.ModIface , mi_boot , mi_fix , mi_semantic_module + , mi_mod_info_semantic_module , mi_free_holes , mi_mnwib , mi_flag_hash @@ -85,6 +103,11 @@ module GHC.Unit.Module.ModIface , mi_plugin_hash , mi_src_hash , mi_usages + , mi_mod_hash + , mi_orphan + , mi_finsts + , mi_exp_hash + , mi_orphan_hash , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,7 +129,7 @@ import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings -import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..)) import GHC.Types.Avail @@ -147,36 +170,36 @@ We can build a full interface file two ways: type PartialModIface = ModIface_ 'ModIfaceCore type ModIface = ModIface_ 'ModIfaceFinal --- | Extends a PartialModIface with information which is either: --- * Computed after codegen --- * Or computed just before writing the iface to disk. (Hashes) --- In order to fully instantiate it. -data ModIfaceBackend = ModIfaceBackend - { mi_mod_hash :: !Fingerprint +type PartialIfacePublic = IfacePublic_ 'ModIfaceCore +type IfacePublic = IfacePublic_ 'ModIfaceFinal + +-- | Extends a PartialModIface with hashes of the ABI. +-- +-- * The mi_mod_hash is the hash of the entire ABI +-- * THe other fields are more specific hashes of parts of the ABI +data IfaceAbiHashes = IfaceAbiHashes + { mi_abi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_orphan :: !WhetherHasOrphans + , mi_abi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans - , mi_finsts :: !WhetherHasFamInst + , mi_abi_finsts :: !WhetherHasFamInst -- ^ Whether this module has family instances. See Note [The type family -- instance consistency story]. - , mi_exp_hash :: !Fingerprint + , mi_abi_exp_hash :: !Fingerprint -- ^ Hash of export list - , mi_orphan_hash :: !Fingerprint + , mi_abi_orphan_hash :: !Fingerprint -- ^ Hash for orphan rules, class and family instances combined + -- NOT transitive + } - -- Cached environments for easy lookup. These are computed (lazily) from - -- other fields and are not put into the interface file. - -- Not really produced by the backend but there is no need to create them - -- any earlier. - , mi_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) +data IfaceCache = IfaceCache + { mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for declaration deprecations - , mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) + , mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for export deprecations - , mi_fix_fn :: !(OccName -> Maybe Fixity) + , mi_cache_fix_fn :: !(OccName -> Maybe Fixity) -- ^ Cached lookup for 'mi_fixities' - , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) + , mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that -- the thing isn't in decls. It's useful to know that when seeing if we are -- up to date wrt. the old interface. The 'OccName' is the parent of the @@ -195,9 +218,9 @@ type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where IfaceDeclExts 'ModIfaceCore = IfaceDecl IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) -type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where - IfaceBackendExts 'ModIfaceCore = () - IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend +type family IfaceAbiHashesExts (phase :: ModIfacePhase) = bk | bk -> phase where + IfaceAbiHashesExts 'ModIfaceCore = () + IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes -- | In-memory byte array representation of a 'ModIface'. -- @@ -212,7 +235,7 @@ data IfaceBinHandle (phase :: ModIfacePhase) where FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp :: ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r withSelfRecomp iface nk jk = case mi_self_recomp_info iface of Nothing -> nk @@ -220,34 +243,80 @@ withSelfRecomp iface nk jk = --- | A 'ModIface' plus a 'ModDetails' summarises everything we know --- about a compiled module. The 'ModIface' is the stuff *before* linking, --- and can be written out to an interface file. The 'ModDetails is after --- linking and can be completely recovered from just the 'ModIface'. +-- | A 'ModIface' summarises everything we know +-- about a compiled module. -- --- When we read an interface file, we also construct a 'ModIface' from it, --- except that we explicitly make the 'mi_decls' and a few other fields empty; --- as when reading we consolidate the declarations etc. into a number of indexed --- maps and environments in the 'ExternalPackageState'. +-- See Note [Structure of ModIface] for information about what belongs in each field. -- --- See Note [Strictness in ModIface] to learn about why some fields are --- strict and others are not. +-- See Note [Strictness in ModIface] to learn about why all the fields are lazy. -- -- See Note [Private fields in ModIface] to learn why we don't export any of the -- fields. data ModIface_ (phase :: ModIfacePhase) = PrivateModIface { - mi_module_ :: !Module, -- ^ Name of the module we are for - mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? + mi_hi_bytes_ :: !(IfaceBinHandle phase), + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. + mi_iface_hash_ :: Fingerprint, -- A hash of the whole interface - mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? + mi_mod_info_ :: IfaceModInfo, + -- ^ Meta information about the module the interface file is for mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) + -- MP: Needs to be refactored (#25844) + + mi_public_ :: IfacePublic_ phase, + -- ^ The parts of interface which are used by other modules when + -- importing this module. The main, original part of an interface. - mi_exports_ :: ![IfaceExport], + + mi_self_recomp_ :: Maybe IfaceSelfRecomp, + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] + + mi_simplified_core_ :: Maybe IfaceSimplifiedCore, + -- ^ The part of the interface written when `-fwrite-if-simplified-core` is enabled. + -- These parts are used to restart bytecode generation. + + mi_docs_ :: Maybe Docs, + -- ^ Docstrings and related data for use by haddock, the ghci + -- @:doc@ command, and other tools. + -- + -- @Just _@ @<=>@ the module was built with @-haddock at . + + mi_top_env_ :: IfaceTopEnv, + -- ^ Just enough information to reconstruct the top level environment in + -- the /original source/ code for this module. which + -- is NOT the same as mi_exports, nor mi_decls (which + -- may contains declarations for things not actually + -- defined by the user). Used for GHCi and for inspecting + -- the contents of modules via the GHC API only. + + mi_ext_fields_ :: ExtensibleFields + -- ^ Additional optional fields, where the Map key represents + -- the field name, resulting in a (size, serialized data) pair. + -- Because the data is intended to be serialized through the + -- internal `Binary` class (increasing compatibility with types + -- using `Name` and `FastString`, such as HIE), this format is + -- chosen over `ByteString`s. + } + +-- | Meta information about the module the interface file is for +data IfaceModInfo = IfaceModInfo { + mi_mod_info_module :: Module, -- ^ Name of the module we are for + mi_mod_info_sig_of :: Maybe Module, -- ^ Are we a sig of another mod? + mi_mod_info_hsc_src :: HscSource -- ^ Boot? Signature? +} + +-- | The public interface of a module which are used by other modules when importing this module. +-- The ABI of a module. +data IfacePublic_ phase = IfacePublic { + mi_exports_ :: [IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things @@ -273,25 +342,10 @@ data ModIface_ (phase :: ModIfacePhase) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], - -- ^ Extra variable definitions which are **NOT** exposed but when - -- combined with mi_decls allows us to restart code generation. - -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - - mi_foreign_ :: !IfaceForeign, - -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. - -- See Note [Foreign stubs and TH bytecode linking] mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: IfaceTopEnv, - -- ^ Just enough information to reconstruct the top level environment in - -- the /original source/ code for this module. which - -- is NOT the same as mi_exports, nor mi_decls (which - -- may contains declarations for things not actually - -- defined by the user). Used for GHCi and for inspecting - -- the contents of modules via the GHC API only. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -299,53 +353,81 @@ data ModIface_ (phase :: ModIfacePhase) mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_trust_ :: !IfaceTrustInfo, + mi_trust_ :: IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg_ :: !Bool, + mi_trust_pkg_ :: Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches_ :: ![IfaceCompleteMatch], + mi_complete_matches_ :: [IfaceCompleteMatch], + -- ^ {-# COMPLETE #-} declarations - mi_docs_ :: !(Maybe Docs), - -- ^ Docstrings and related data for use by haddock, the ghci - -- @:doc@ command, and other tools. - -- - -- @Just _@ @<=>@ the module was built with @-haddock at . + mi_caches_ :: IfaceCache, + -- ^ Cached lookups of some parts of mi_public - mi_final_exts_ :: !(IfaceBackendExts phase), - -- ^ Either `()` or `ModIfaceBackend` for + mi_abi_hashes_ :: (IfaceAbiHashesExts phase) + -- ^ Either `()` or `IfaceAbiHashes` for -- a fully instantiated interface. - - mi_ext_fields_ :: !ExtensibleFields, - -- ^ Additional optional fields, where the Map key represents - -- the field name, resulting in a (size, serialized data) pair. - -- Because the data is intended to be serialized through the - -- internal `Binary` class (increasing compatibility with types - -- using `Name` and `FastString`, such as HIE), this format is - -- chosen over `ByteString`s. - -- - - mi_hi_bytes_ :: !(IfaceBinHandle phase), - -- ^ A serialised in-memory buffer of this 'ModIface'. - -- If this handle is given, we can avoid serialising the 'ModIface' - -- when writing this 'ModIface' to disk, and write this buffer to disk instead. - -- See Note [Sharing of ModIface]. - - mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) - -- ^ Information needed for checking self-recompilation. - -- See Note [Self recompilation information in interface files] - } + -- These fields are hashes of different parts of the public interface. +} + +mkIfacePublic :: [IfaceExport] + -> [IfaceDeclExts 'ModIfaceFinal] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDefault] + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> IfaceAbiHashes + -> IfacePublic +mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes = IfacePublic { + mi_exports_ = exports, + mi_decls_ = decls, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_defaults_ = defaults, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, + mi_cache_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, + mi_cache_fix_fn = mkIfaceFixCache fixities, + mi_cache_hash_fn = mkIfaceHashCache decls + }, + mi_abi_hashes_ = abi_hashes +} + +-- | The information needed to restart bytecode generation. +-- Enabled by `-fwrite-if-simplified-core`. +data IfaceSimplifiedCore = IfaceSimplifiedCore { + mi_sc_extra_decls :: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -- ^ Extra variable definitions which are **NOT** exposed but when + -- combined with mi_decls allows us to restart code generation. + -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] + , mi_sc_foreign :: IfaceForeign + -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. + -- See Note [Foreign stubs and TH bytecode linking] +} -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff - , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module + { ifaceTopExports :: DetOrdAvails -- ^ all top level things in this module, including unexported stuff + , ifaceImports :: [IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where @@ -362,6 +444,35 @@ instance Binary IfaceTopEnv where {- +Note [Structure of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The ModIface structure is divided into several logical parts: + +1. mi_mod_info: Basic module metadata (name, version, etc.) + +2. mi_public: The public interface of the module, which includes: + - Exports, declarations, fixities, warnings, annotations + - Class and type family instances + - Rewrite rules and COMPLETE pragmas + - Safe Haskell and package trust information + - ABI hashes for recompilation checking + +4. mi_self_recomp: Information needed for self-recompilation checking + (see Note [Self recompilation information in interface files]) + +5. mi_simplified_core: Optional simplified Core for bytecode generation + (only present when -fwrite-if-simplified-core is enabled) + +6. mi_docs: Optional documentation (only present when -haddock is enabled) + +7. mi_top_env: Information about the top-level environment of the original source + +8. mi_ext_fields: Additional fields for extensibility + +This structure helps organize the interface data according to its purpose and usage +patterns. Different parts of the compiler use different fields. By separating them +logically in the interface we can arrange to only deserialize the fields that are needed. + Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -371,7 +482,7 @@ The ModIface is the Haskell representation of an interface (.hi) file. that we have just compiled * For packages that we depend on we load the ModIface from disk. -Some fields in the ModIface are deliberately lazy because when we read +All fields in the ModIface are deliberately lazy because when we read an interface file we don't always need all the parts. For example, an interface file contains information about documentation which is often not needed during compilation. This is achieved using the lazyPut/lazyGet pair. @@ -384,23 +495,43 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) -mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ +mi_flag_hash :: ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags) +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint -mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_ mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint -mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_ mi_src_hash :: ModIface_ phase -> Maybe Fingerprint -mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_ mi_usages :: ModIface_ phase -> Maybe [Usage] -mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ +mi_usages = fmap mi_sr_usages . mi_self_recomp_ mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint -mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_ + +-- | Accessor for the module hash of the ABI from a ModIface. +mi_mod_hash :: ModIface -> Fingerprint +mi_mod_hash iface = mi_abi_mod_hash (mi_abi_hashes iface) + +-- | Accessor for whether this module has orphans from a ModIface. +mi_orphan :: ModIface -> WhetherHasOrphans +mi_orphan iface = mi_abi_orphan (mi_abi_hashes iface) + +-- | Accessor for whether this module has family instances from a ModIface. +mi_finsts :: ModIface -> WhetherHasFamInst +mi_finsts iface = mi_abi_finsts (mi_abi_hashes iface) + +-- | Accessor for the hash of the export list from a ModIface. +mi_exp_hash :: ModIface -> Fingerprint +mi_exp_hash iface = mi_abi_exp_hash (mi_abi_hashes iface) + +-- | Accessor for the hash of orphan rules, class and family instances combined from a ModIface. +mi_orphan_hash :: ModIface -> Fingerprint +mi_orphan_hash iface = mi_abi_orphan_hash (mi_abi_hashes iface) -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. @@ -415,16 +546,19 @@ mi_mnwib iface = GWIB (moduleName $ mi_module iface) (mi_boot iface) -- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be -- found, 'defaultFixity' is returned instead. mi_fix :: ModIface -> OccName -> Fixity -mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity +mi_fix iface name = mi_fix_fn iface name `orElse` defaultFixity -- | The semantic module for this interface; e.g., if it's a interface -- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module' -- will be @<A>@. -mi_semantic_module :: ModIface_ a -> Module -mi_semantic_module iface = case mi_sig_of iface of - Nothing -> mi_module iface +mi_mod_info_semantic_module :: IfaceModInfo -> Module +mi_mod_info_semantic_module iface = case mi_mod_info_sig_of iface of + Nothing -> mi_mod_info_module iface Just mod -> mod +mi_semantic_module :: ModIface_ a -> Module +mi_semantic_module iface = mi_mod_info_semantic_module (mi_mod_info iface) + -- | The "precise" free holes, e.g., the signatures that this -- 'ModIface' depends on. mi_free_holes :: ModIface -> UniqDSet ModuleName @@ -455,191 +589,229 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + put_ bh (PrivateModIface + { mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then -- we likely have a good reason, and do not want to reuse -- the byte array. -- See Note [Private fields in ModIface] + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_anns_ = anns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - mi_complete_matches_ = complete_matches, + mi_public_ = public, mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_self_recomp_info_ = self_recomp, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash - }}) = do - put_ bh mod - put_ bh sig_of - put_ bh hsc_src - put_ bh self_recomp - put_ bh mod_hash + mi_self_recomp_ = self_recomp, + mi_simplified_core_ = simplified_core + }) = do + put_ bh mod_info put_ bh iface_hash - put_ bh orphan - put_ bh hasFamInsts lazyPut bh deps - put_ bh exports - put_ bh exp_hash - put_ bh fixities - lazyPut bh warns - lazyPut bh anns - put_ bh decls - put_ bh extra_decls - put_ bh defaults - put_ bh foreign_ - put_ bh insts - put_ bh fam_insts - lazyPut bh rules - put_ bh orphan_hash - put_ bh trust - put_ bh trust_pkg - put_ bh complete_matches + lazyPut bh public lazyPut bh top_env lazyPutMaybe bh docs + lazyPutMaybe bh self_recomp + lazyPutMaybe bh simplified_core get bh = do - mod <- get bh - sig_of <- get bh - hsc_src <- get bh - self_recomp_info <- get bh - mod_hash <- get bh + mod_info <- get bh iface_hash <- get bh - orphan <- get bh - hasFamInsts <- get bh deps <- lazyGet bh - exports <- {-# SCC "bin_exports" #-} get bh - exp_hash <- get bh - fixities <- {-# SCC "bin_fixities" #-} get bh - warns <- {-# SCC "bin_warns" #-} lazyGet bh - anns <- {-# SCC "bin_anns" #-} lazyGet bh - decls <- {-# SCC "bin_tycldecls" #-} get bh - extra_decls <- get bh - defaults <- get bh - foreign_ <- get bh - insts <- {-# SCC "bin_insts" #-} get bh - fam_insts <- {-# SCC "bin_fam_insts" #-} get bh - rules <- {-# SCC "bin_rules" #-} lazyGet bh - orphan_hash <- get bh - trust <- get bh - trust_pkg <- get bh - complete_matches <- get bh + public <- lazyGet bh top_env <- lazyGet bh docs <- lazyGetMaybe bh + self_recomp <- lazyGetMaybe bh + simplified_core <- lazyGetMaybe bh + return (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = - -- We can't populate this field here, as we are - -- missing the 'mi_ext_fields_' field, which is - -- handled in 'getIfaceWithExtFields'. - FullIfaceBinHandle Strict.Nothing, + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_anns_ = anns, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - -- And build the cached values - mi_complete_matches_ = complete_matches, + mi_public_ = public, + mi_simplified_core_ = simplified_core, mi_docs_ = docs, mi_top_env_ = top_env, - mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt - -- with specially when the file is read - mi_self_recomp_info_ = self_recomp_info, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash, - mi_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, - mi_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, - mi_fix_fn = mkIfaceFixCache fixities, - mi_hash_fn = mkIfaceHashCache decls - }}) + mi_self_recomp_ = self_recomp, + -- placeholder because this is dealt + -- with specially when the file is read + mi_ext_fields_ = emptyExtensibleFields, + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + }) + +instance Binary IfaceModInfo where + put_ bh (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) = do + put_ bh mod + put_ bh sig_of + put_ bh hsc_src + get bh = do + mod <- get bh + sig_of <- get bh + hsc_src <- get bh + return (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) + + +instance Binary (IfacePublic_ 'ModIfaceFinal) where + put_ bh (IfacePublic { mi_exports_ = exports + , mi_decls_ = decls + , mi_fixities_ = fixities + , mi_warns_ = warns + , mi_anns_ = anns + , mi_defaults_ = defaults + , mi_insts_ = insts + , mi_fam_insts_ = fam_insts + , mi_rules_ = rules + , mi_trust_ = trust + , mi_trust_pkg_ = trust_pkg + , mi_complete_matches_ = complete_matches + , mi_abi_hashes_ = abi_hashes + }) = do + + lazyPut bh exports + lazyPut bh decls + lazyPut bh fixities + lazyPut bh warns + lazyPut bh anns + lazyPut bh defaults + lazyPut bh insts + lazyPut bh fam_insts + lazyPut bh rules + lazyPut bh trust + lazyPut bh trust_pkg + lazyPut bh complete_matches + lazyPut bh abi_hashes + + get bh = do + exports <- lazyGet bh + decls <- lazyGet bh + fixities <- lazyGet bh + warns <- lazyGet bh + anns <- lazyGet bh + defaults <- lazyGet bh + insts <- lazyGet bh + fam_insts <- lazyGet bh + rules <- lazyGet bh + trust <- lazyGet bh + trust_pkg <- lazyGet bh + complete_matches <- lazyGet bh + abi_hashes <- lazyGet bh + return (mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes) + +instance Binary IfaceAbiHashes where + put_ bh (IfaceAbiHashes { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = orphan + , mi_abi_finsts = hasFamInsts + , mi_abi_exp_hash = exp_hash + , mi_abi_orphan_hash = orphan_hash + }) = do + put_ bh mod_hash + put_ bh orphan + put_ bh hasFamInsts + put_ bh exp_hash + put_ bh orphan_hash + get bh = do + mod_hash <- get bh + orphan <- get bh + hasFamInsts <- get bh + exp_hash <- get bh + orphan_hash <- get bh + return $ IfaceAbiHashes { + mi_abi_mod_hash = mod_hash, + mi_abi_orphan = orphan, + mi_abi_finsts = hasFamInsts, + mi_abi_exp_hash = exp_hash, + mi_abi_orphan_hash = orphan_hash + } + +instance Binary IfaceSimplifiedCore where + put_ bh (IfaceSimplifiedCore eds fs) = do + put_ bh eds + put_ bh fs + + get bh = do + eds <- get bh + fs <- get bh + return (IfaceSimplifiedCore eds fs) emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface - { mi_module_ = mod, - mi_sig_of_ = Nothing, - mi_hsc_src_ = HsSrcFile, + { mi_mod_info_ = emptyIfaceModInfo mod, + mi_iface_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_exports_ = [], - mi_fixities_ = [], - mi_warns_ = IfWarnSome [] [], - mi_anns_ = [], - mi_defaults_ = [], - mi_insts_ = [], - mi_fam_insts_ = [], - mi_rules_ = [], - mi_decls_ = [], - mi_extra_decls_ = Nothing, - mi_foreign_ = emptyIfaceForeign, + mi_public_ = emptyPublicModIface (), + mi_simplified_core_ = Nothing, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_trust_ = noIfaceTrustInfo, - mi_trust_pkg_ = False, - mi_complete_matches_ = [], mi_docs_ = Nothing, - mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields, - mi_self_recomp_info_ = Nothing + mi_self_recomp_ = Nothing, + mi_ext_fields_ = emptyExtensibleFields + } +emptyIfaceModInfo :: Module -> IfaceModInfo +emptyIfaceModInfo mod = IfaceModInfo + { mi_mod_info_module = mod + , mi_mod_info_sig_of = Nothing + , mi_mod_info_hsc_src = HsSrcFile + } + + +emptyPublicModIface :: IfaceAbiHashesExts phase -> IfacePublic_ phase +emptyPublicModIface abi_hashes = IfacePublic + { mi_exports_ = [] + , mi_decls_ = [] + , mi_fixities_ = [] + , mi_warns_ = IfWarnSome [] [] + , mi_anns_ = [] + , mi_defaults_ = [] + , mi_insts_ = [] + , mi_fam_insts_ = [] + , mi_rules_ = [] + , mi_abi_hashes_ = abi_hashes + , mi_trust_ = noIfaceTrustInfo + , mi_trust_pkg_ = False + , mi_caches_ = emptyModIfaceCache + , mi_complete_matches_ = [] + } + +emptyModIfaceCache :: IfaceCache +emptyModIfaceCache = IfaceCache { + mi_cache_decl_warn_fn = emptyIfaceWarnCache, + mi_cache_export_warn_fn = emptyIfaceWarnCache, + mi_cache_fix_fn = emptyIfaceFixCache, + mi_cache_hash_fn = emptyIfaceHashCache +} + +emptyIfaceBackend :: IfaceAbiHashes +emptyIfaceBackend = IfaceAbiHashes + { mi_abi_mod_hash = fingerprint0, + mi_abi_orphan = False, + mi_abi_finsts = False, + mi_abi_exp_hash = fingerprint0, + mi_abi_orphan_hash = fingerprint0 + } + emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls_ = [] - , mi_self_recomp_info_ = Nothing + { mi_public_ = emptyPublicModIface emptyIfaceBackend , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing - , mi_final_exts_ = ModIfaceBackend - { mi_mod_hash = fingerprint0, - mi_iface_hash = fingerprint0, - mi_orphan = False, - mi_finsts = False, - mi_exp_hash = fingerprint0, - mi_orphan_hash = fingerprint0, - mi_decl_warn_fn = emptyIfaceWarnCache, - mi_export_warn_fn = emptyIfaceWarnCache, - mi_fix_fn = emptyIfaceFixCache, - mi_hash_fn = emptyIfaceHashCache } } + } + -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface' mkIfaceHashCache :: [(Fingerprint,IfaceDecl)] @@ -657,11 +829,11 @@ emptyIfaceHashCache _occ = Nothing -- ModIface is completely forced since it will live in memory for a long time. -- If forcing it uses a lot of memory, then store less things in ModIface. -instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) +instance ( NFData (IfaceAbiHashesExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) - = rnf a1 + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = (a1 :: IfaceBinHandle phase) `seq` rnf a2 `seq` rnf a3 `seq` rnf a4 @@ -671,24 +843,27 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 - `seq` rnf a11 - `seq` rnf a12 - `seq` rnf a13 - `seq` rnf a14 - `seq` rnf a15 - `seq` rnf a16 - `seq` rnf a17 - `seq` rnf a18 - `seq` rnf a19 - `seq` rnf a20 - `seq` rnf a21 - `seq` rnf a22 - -- IfaceBinHandle - `seq` (a23 :: IfaceBinHandle phase) - `seq` rnf a24 - -instance NFData ModIfaceBackend where - rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + +instance NFData IfaceModInfo where + rnf (IfaceModInfo a1 a2 a3) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + + +instance NFData IfaceSimplifiedCore where + rnf (IfaceSimplifiedCore eds fs) = rnf eds `seq` rnf fs + +instance NFData IfaceAbiHashes where + rnf (IfaceAbiHashes a1 a2 a3 a4 a5) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + +instance (NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) where + rnf (IfacePublic a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = rnf a1 `seq` rnf a2 `seq` rnf a3 @@ -699,6 +874,18 @@ instance NFData ModIfaceBackend where `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +instance NFData IfaceCache where + rnf (IfaceCache a1 a2 a3 a4) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + forceModIface :: ModIface -> IO () @@ -745,28 +932,38 @@ to serialise the 'ModIface' to disk again. -- | Given a 'PartialModIface', turn it into a 'ModIface' by completing -- missing fields. completePartialModIface :: PartialModIface + -> Fingerprint -> [(Fingerprint, IfaceDecl)] - -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - -> ModIfaceBackend + -> Maybe IfaceSimplifiedCore + -> IfaceAbiHashes + -> IfaceCache -> ModIface -completePartialModIface partial decls extra_decls final_exts = partial - { mi_decls_ = decls - , mi_extra_decls_ = extra_decls - , mi_final_exts_ = final_exts +completePartialModIface partial iface_hash decls extra_decls final_exts cache = partial + { mi_public_ = completePublicModIface decls final_exts cache (mi_public_ partial) + , mi_simplified_core_ = extra_decls , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_iface_hash_ = iface_hash } + where -set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase -set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } - -set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase -set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } +-- | Given a 'PartialIfacePublic', turn it into an 'IfacePublic' by completing +-- missing fields. +completePublicModIface :: [(Fingerprint, IfaceDecl)] + -> IfaceAbiHashes + -> IfaceCache + -> PartialIfacePublic + -> IfacePublic +completePublicModIface decls abi_hashes cache partial = partial + { mi_decls_ = decls + , mi_abi_hashes_ = abi_hashes + , mi_caches_ = cache + } -set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase -set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } +set_mi_mod_info :: IfaceModInfo -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info val iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = val } -set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase -set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } +set_mi_self_recomp :: Maybe IfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -774,59 +971,100 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } +set_mi_public :: (IfacePublic_ phase -> IfacePublic_ phase) -> ModIface_ phase -> ModIface_ phase +set_mi_public f iface = clear_mi_hi_bytes $ iface { mi_public_ = f (mi_public_ iface) } + +set_mi_simplified_core :: Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase +set_mi_simplified_core val iface = clear_mi_hi_bytes $ iface { mi_simplified_core_ = val } + +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +{- Settings for mi_public interface fields -} + set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase -set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } +set_mi_exports val = set_mi_public (\iface -> iface { mi_exports_ = val }) set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase -set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } +set_mi_fixities val = set_mi_public (\iface -> iface { mi_fixities_ = val }) set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase -set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } +set_mi_warns val = set_mi_public (\iface -> iface { mi_warns_ = val }) set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase -set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } +set_mi_anns val = set_mi_public (\iface -> iface { mi_anns_ = val }) set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase -set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } +set_mi_insts val = set_mi_public (\iface -> iface { mi_insts_ = val }) set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase -set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } +set_mi_fam_insts val = set_mi_public (\iface -> iface { mi_fam_insts_ = val }) set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase -set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } +set_mi_rules val = set_mi_public (\iface -> iface { mi_rules_ = val }) set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase -set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } +set_mi_decls val = set_mi_public (\iface -> iface { mi_decls_ = val }) set_mi_defaults :: [IfaceDefault] -> ModIface_ phase -> ModIface_ phase -set_mi_defaults val iface = clear_mi_hi_bytes $ iface { mi_defaults_ = val } - -set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase -set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } - -set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase -set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } - -set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase -set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } +set_mi_defaults val = set_mi_public (\iface -> iface { mi_defaults_ = val }) set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase -set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } +set_mi_trust val = set_mi_public (\iface -> iface { mi_trust_ = val }) set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase -set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } +set_mi_trust_pkg val = set_mi_public (\iface -> iface { mi_trust_pkg_ = val }) set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase -set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } +set_mi_complete_matches val = set_mi_public (\iface -> iface { mi_complete_matches_ = val }) + +set_mi_abi_hashes :: IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_abi_hashes val = set_mi_public (\iface -> iface { mi_abi_hashes_ = val }) + +{- Setters for mi_caches interface fields -} + +set_mi_decl_warn_fn :: (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_decl_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_decl_warn_fn = val } }) + +set_mi_export_warn_fn :: (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_export_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_export_warn_fn = val } }) + +set_mi_fix_fn :: (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase +set_mi_fix_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_fix_fn = val } }) + +set_mi_hash_fn :: (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase +set_mi_hash_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_hash_fn = val } }) + +set_mi_caches :: IfaceCache -> ModIface_ phase -> ModIface_ phase +set_mi_caches val = set_mi_public (\iface -> iface { mi_caches_ = val }) + +{- + +-} + +{- Setters for mi_mod_info interface fields -} + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val = set_mi_mod_info_field (\info -> info { mi_mod_info_module = val }) + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val = set_mi_mod_info_field (\info -> info { mi_mod_info_sig_of = val }) + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val = set_mi_mod_info_field (\info -> info { mi_mod_info_hsc_src = val }) + +-- | Helper function for setting fields in mi_mod_info_ +set_mi_mod_info_field :: (IfaceModInfo -> IfaceModInfo) -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info_field f iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = f (mi_mod_info_ iface) } -set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase -set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } -set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase -set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } -set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase -set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } -- | Invalidate any byte array buffer we might have. clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase @@ -887,18 +1125,20 @@ However, with the pragma, the correct core is generated: -- See Note [Inline Pattern synonym of ModIface] for why we have all these -- inline pragmas. -{-# INLINE ModIface #-} +{-# INLINE mi_mod_info #-} +{-# INLINE mi_iface_hash #-} {-# INLINE mi_module #-} {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} +{-# INLINE mi_public #-} {-# INLINE mi_exports #-} {-# INLINE mi_fixities #-} {-# INLINE mi_warns #-} {-# INLINE mi_anns #-} {-# INLINE mi_decls #-} -{-# INLINE mi_extra_decls #-} -{-# INLINE mi_foreign #-} +{-# INLINE mi_simplified_core #-} +{-# INLINE mi_defaults #-} {-# INLINE mi_top_env #-} {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} @@ -907,32 +1147,63 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} {-# INLINE mi_docs #-} -{-# INLINE mi_final_exts #-} +{-# INLINE mi_abi_hashes #-} {-# INLINE mi_ext_fields #-} {-# INLINE mi_hi_bytes #-} +{-# INLINE mi_self_recomp_info #-} +{-# INLINE mi_fix_fn #-} +{-# INLINE mi_hash_fn #-} +{-# INLINE mi_decl_warn_fn #-} +{-# INLINE mi_export_warn_fn #-} +{-# INLINE ModIface #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> - [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> - [IfaceAnnotation] -> [IfaceDeclExts phase] -> - Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> + IfaceModInfo + -> Module + -> Maybe Module + -> HscSource + -> Fingerprint + -> Dependencies + -> IfacePublic_ phase + -> [IfaceExport] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDeclExts phase] + -> Maybe IfaceSimplifiedCore + -> [IfaceDefault] + -> IfaceTopEnv + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> Maybe Docs + -> IfaceAbiHashesExts phase + -> ExtensibleFields + -> IfaceBinHandle phase + -> Maybe IfaceSelfRecomp + -> (OccName -> Maybe Fixity) + -> (OccName -> Maybe (OccName, Fingerprint)) + -> (OccName -> Maybe (WarningTxt GhcRn)) + -> (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase pattern ModIface - { mi_module + { mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_defaults , mi_top_env , mi_insts @@ -942,33 +1213,45 @@ pattern ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_hash_fn + , mi_decl_warn_fn + , mi_export_warn_fn } <- PrivateModIface - { mi_module_ = mi_module - , mi_sig_of_ = mi_sig_of - , mi_hsc_src_ = mi_hsc_src + { mi_mod_info_ = mi_mod_info at IfaceModInfo { mi_mod_info_module = mi_module + , mi_mod_info_sig_of = mi_sig_of + , mi_mod_info_hsc_src = mi_hsc_src } + , mi_iface_hash_ = mi_iface_hash , mi_deps_ = mi_deps - , mi_exports_ = mi_exports - , mi_fixities_ = mi_fixities - , mi_warns_ = mi_warns - , mi_anns_ = mi_anns - , mi_decls_ = mi_decls - , mi_extra_decls_ = mi_extra_decls - , mi_foreign_ = mi_foreign - , mi_defaults_ = mi_defaults - , mi_top_env_ = mi_top_env - , mi_insts_ = mi_insts - , mi_fam_insts_ = mi_fam_insts - , mi_rules_ = mi_rules - , mi_trust_ = mi_trust - , mi_trust_pkg_ = mi_trust_pkg - , mi_complete_matches_ = mi_complete_matches + , mi_public_ = mi_public at IfacePublic { + mi_exports_ = mi_exports + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_defaults_ = mi_defaults + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mi_decl_warn_fn, + mi_cache_export_warn_fn = mi_export_warn_fn, + mi_cache_fix_fn = mi_fix_fn, + mi_cache_hash_fn = mi_hash_fn + } + , mi_abi_hashes_ = mi_abi_hashes + } , mi_docs_ = mi_docs - , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields , mi_hi_bytes_ = mi_hi_bytes - , mi_self_recomp_info_ = mi_self_recomp_info + , mi_self_recomp_ = mi_self_recomp_info + , mi_simplified_core_ = mi_simplified_core + , mi_top_env_ = mi_top_env } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -107,6 +107,9 @@ module GHC.Utils.Binary simpleBindingNameReader, FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, BinArray, + + -- * FingerprintWithValue + FingerprintWithValue(..) ) where import GHC.Prelude @@ -2088,3 +2091,36 @@ source location as part of a larger structure. instance (Binary v) => Binary (IntMap v) where put_ bh m = put_ bh (IntMap.toAscList m) get bh = IntMap.fromAscList <$> get bh + + +{- Note [FingerprintWithValue] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +FingerprintWithValue is a wrapper which allows us to store a fingerprint and +optionally the value which was used to create the fingerprint. + +This is useful for storing information in interface files, where we want to +store the fingerprint of the interface file, but also the value which was used +to create the fingerprint (e.g. the DynFlags). + +The wrapper is useful to ensure that the fingerprint can be read quickly without +having to deserialise the value itself. +-} + +-- | A wrapper which allows us to store a fingerprint and optionally the value which +-- was used to create the fingerprint. +data FingerprintWithValue a = FingerprintWithValue !Fingerprint (Maybe a) + deriving Functor + +instance Binary a => Binary (FingerprintWithValue a) where + put_ bh (FingerprintWithValue fp val) = do + put_ bh fp + lazyPutMaybe bh val + + get bh = do + fp <- get bh + val <- lazyGetMaybe bh + return $ FingerprintWithValue fp val + +instance NFData a => NFData (FingerprintWithValue a) where + rnf (FingerprintWithValue fp mflags) + = rnf fp `seq` rnf mflags `seq` () \ No newline at end of file ===================================== ghc/Main.hs ===================================== @@ -1133,6 +1133,8 @@ abiHash strs = do mods <- mapM find_it strs + -- MP: loadUserInterface is inefficient here since we will never find a cached + -- interface. computeInterface is probably better. let get_iface modl = loadUserInterface NotBoot (text "abiHash") modl ifaces <- initIfaceCheck (text "abiHash") hsc_env $ mapM get_iface mods @@ -1140,7 +1142,7 @@ abiHash strs = do put_ bh hiVersion -- package hashes change when the compiler version changes (for now) -- see #5328 - mapM_ (put_ bh . mi_mod_hash . mi_final_exts) ifaces + mapM_ (put_ bh . mi_mod_hash) ifaces f <- fingerprintBinMem bh putStrLn (showPpr dflags f) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d391272edc30bf7773b72f56f21b7d51c65b079a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d391272edc30bf7773b72f56f21b7d51c65b079a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/0c33e92f/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 14:33:27 2025 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Fri, 14 Mar 2025 10:33:27 -0400 Subject: [Git][ghc/ghc][wip/T24603] 27 commits: users guide: Fix typo Message-ID: <67d43e37b984f_256967268b1c637e4@gitlab.mail> Serge S. Gulin pushed to branch wip/T24603 at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 77ce847c by Serge S. Gulin at 2025-03-14T18:33:09+04:00 Support for ARM64 Windows (LLVM-enabled) (fixes #24603) submodule Co-authored-by: Cheng Shao <terrorjack at type.dance> Co-authored-by: Dmitrii Egorov <egorov.d.i at icloud.com> Co-authored-by: Andrei Borzenkov <root at sandwitch.dev> - - - - - 20c60806 by Serge S. Gulin at 2025-03-14T18:33:09+04:00 Basic NCG support for HelloWorld - - - - - c50c09a8 by Serge S. Gulin at 2025-03-14T18:33:09+04:00 Remove trailing whtespace to make CI greener - - - - - 161 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/using-concurrent.rst - libraries/Cabal - libraries/Win32 - libraries/base/src/System/CPUTime/Windows.hsc - libraries/base/tests/perf/encodingAllocations.hs - libraries/directory - libraries/ghc-boot/GHC/Serialized.hs - libraries/haskeline - libraries/process - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - libraries/unix - llvm-targets - m4/ghc_tables_next_to_code.m4 - rts/HeapStackCheck.cmm - rts/PrimOps.cmm - rts/StgCRun.c - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/win32/veh_excn.c - testsuite/driver/junit.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/dump-decls/Main.hs - utils/ghc-toolchain/exe/Main.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/hsc2hs - utils/llvm-targets/gen-data-layout.sh The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d4f0dd9f6e6e8f0fd0fe64db86a5432a2517aad...c50c09a82dd5253415ce9a32214b074086aca232 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d4f0dd9f6e6e8f0fd0fe64db86a5432a2517aad...c50c09a82dd5253415ce9a32214b074086aca232 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/c14ec43d/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 14:48:30 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Mar 2025 10:48:30 -0400 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Specialising expressions -- at last Message-ID: <67d441be4385c_263570de8a04624c@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 31938b43 by Simon Peyton Jones at 2025-03-14T15:48:18+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - 34076b64 by Simon Peyton Jones at 2025-03-14T15:48:18+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 155 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/23a14c10d080648574722240a2b6647d1a3cdf86...34076b64d133bae38e147f5a5a0646c7a79546d2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/23a14c10d080648574722240a2b6647d1a3cdf86...34076b64d133bae38e147f5a5a0646c7a79546d2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/f0a677b0/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 14:49:30 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Mar 2025 10:49:30 -0400 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Specialising expressions -- at last Message-ID: <67d441fa9a8b8_2635701ba6d44725@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: fd597fb0 by Simon Peyton Jones at 2025-03-14T15:49:19+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - 14c4be0e by Simon Peyton Jones at 2025-03-14T15:49:20+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 155 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/34076b64d133bae38e147f5a5a0646c7a79546d2...14c4be0e66840d26515ed23db012cb6944f94f2b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/34076b64d133bae38e147f5a5a0646c7a79546d2...14c4be0e66840d26515ed23db012cb6944f94f2b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/475d4796/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 14:51:30 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Mar 2025 10:51:30 -0400 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Specialising expressions -- at last Message-ID: <67d44272596b8_26357029fb444822a@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 4ed8e1a5 by Simon Peyton Jones at 2025-03-14T15:51:20+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - c294adfb by Simon Peyton Jones at 2025-03-14T15:51:20+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 155 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/14c4be0e66840d26515ed23db012cb6944f94f2b...c294adfb20237d8b83691e3405bc76d3929b703a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/14c4be0e66840d26515ed23db012cb6944f94f2b...c294adfb20237d8b83691e3405bc76d3929b703a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/815c0585/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 14:54:12 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Mar 2025 10:54:12 -0400 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Specialising expressions -- at last Message-ID: <67d44314cc99c_2635701ba634510f3@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 07bcf59a by Simon Peyton Jones at 2025-03-14T15:54:05+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - 02c29590 by Simon Peyton Jones at 2025-03-14T15:54:05+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 155 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c294adfb20237d8b83691e3405bc76d3929b703a...02c295907910b4ed25c391f2894cd77191fcaff5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c294adfb20237d8b83691e3405bc76d3929b703a...02c295907910b4ed25c391f2894cd77191fcaff5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/016ec836/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 14:55:38 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Mar 2025 10:55:38 -0400 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Specialising expressions -- at last Message-ID: <67d4436ab3bf9_263570c5c605204f@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: a0005f87 by Simon Peyton Jones at 2025-03-14T15:55:31+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - 0b42199a by Simon Peyton Jones at 2025-03-14T15:55:31+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 155 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/02c295907910b4ed25c391f2894cd77191fcaff5...0b42199ad08488221d3a0ea88b3f1eef36c23104 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/02c295907910b4ed25c391f2894cd77191fcaff5...0b42199ad08488221d3a0ea88b3f1eef36c23104 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/ed48646b/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 14:57:01 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Mar 2025 10:57:01 -0400 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Specialising expressions -- at last Message-ID: <67d443bde5051_2635702db9b453020@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 01a60f86 by Simon Peyton Jones at 2025-03-14T15:56:52+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - 5d2b3a2a by Simon Peyton Jones at 2025-03-14T15:56:53+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 155 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b42199ad08488221d3a0ea88b3f1eef36c23104...5d2b3a2a09859046eb3ba1e742683f3affe51d58 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b42199ad08488221d3a0ea88b3f1eef36c23104...5d2b3a2a09859046eb3ba1e742683f3affe51d58 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/43d634b7/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 14:57:27 2025 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Mar 2025 10:57:27 -0400 Subject: [Git][ghc/ghc][wip/T24359] 2 commits: Specialising expressions -- at last Message-ID: <67d443d72a3a2_2635701ba634540de@gitlab.mail> sheaf pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 161454de by Simon Peyton Jones at 2025-03-14T15:57:19+01:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - 5c9d38c1 by Simon Peyton Jones at 2025-03-14T15:57:19+01:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - 155 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Var.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/using-warnings.rst - libraries/array - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/changelog.md - + testsuite/tests/deSugar/should_compile/T10251.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_fail/T7848.stderr - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - utils/check-exact/ExactPrint.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5d2b3a2a09859046eb3ba1e742683f3affe51d58...5c9d38c1625eb92928f28c387a71f40d871a68d6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5d2b3a2a09859046eb3ba1e742683f3affe51d58...5c9d38c1625eb92928f28c387a71f40d871a68d6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/e4e0f17d/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 15:34:15 2025 From: gitlab at gitlab.haskell.org (Oleg Grenrus (@phadej)) Date: Fri, 14 Mar 2025 11:34:15 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/squash-multiple-empty-lines Message-ID: <67d44c7766a98_263570a54b505877f@gitlab.mail> Oleg Grenrus pushed new branch wip/squash-multiple-empty-lines at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/squash-multiple-empty-lines You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/de373ad4/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 14 15:37:19 2025 From: gitlab at gitlab.haskell.org (Oleg Grenrus (@phadej)) Date: Fri, 14 Mar 2025 11:37:19 -0400 Subject: [Git][ghc/ghc][wip/squash-multiple-empty-lines] Squash consecutive empty lines Message-ID: <67d44d2f5e8e7_272d96c5c4c90922@gitlab.mail> Oleg Grenrus pushed to branch wip/squash-multiple-empty-lines at Glasgow Haskell Compiler / GHC Commits: b47378bd by Oleg Grenrus at 2025-03-14T17:35:10+02:00 Squash consecutive empty lines So we have at most two. While I think that only objective amount is a single empty line, that squash touches virtually everything (536 out of 799 files in `compiler` vs 156 in this patch) - - - - - 156 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Dominators.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reducibility.hs - compiler/GHC/Cmm/Switch.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Class.hs - compiler/GHC/Core/ConLike.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/FloatOut.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Inline.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/PatSyn.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/RecWalk.hs - compiler/GHC/Core/TyCon/Set.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Base.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Inductive/PatriciaTree.hs - compiler/GHC/Data/Graph/Ops.hs - compiler/GHC/Data/Graph/Ppr.hs - compiler/GHC/Data/List/SetOps.hs - compiler/GHC/Data/Word64Map/Internal.hs - compiler/GHC/Data/Word64Map/Strict/Internal.hs - compiler/GHC/Data/Word64Set/Internal.hs - compiler/GHC/Driver/Backend.hs - compiler/GHC/Driver/Backend/Internal.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Pmc/Check.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Iface/Errors/Types.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/JS/Make.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Platform.hs - compiler/GHC/Platform/Ways.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Env.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToJS/CodeGen.hs - compiler/GHC/StgToJS/Linker/Opt.hs - compiler/GHC/StgToJS/Monad.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/LclEnv.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Error.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Name/Shape.hs - compiler/GHC/Types/RepType.hs - compiler/GHC/Types/TyThing.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Set.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/GlobalVars.hs - compiler/GHC/Utils/Logger.hs - compiler/GHC/Wasm/ControlFlow.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Extension.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b47378bd1db289f7e0a2c5690bdedb73a05f6b11 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b47378bd1db289f7e0a2c5690bdedb73a05f6b11 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/5f3fa398/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 16:13:46 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Mar 2025 12:13:46 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] Try rules a bit more: yes if it's not a primop id Message-ID: <67d455baa81a4_272d96530214942b2@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: 46312f3e by Simon Peyton Jones at 2025-03-14T16:13:13+00:00 Try rules a bit more: yes if it's not a primop id - ; mb_match <- if isClassOpId fun + ; mb_match <- if not (isPrimOpId fun) - - - - - 1 changed file: - compiler/GHC/Core/Opt/Simplify/Iteration.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -2328,7 +2328,7 @@ simplOutId env fun cont ; rule_base <- getSimplRules ; let rules_for_me = getRules rule_base fun out_args = contOutArgs env cont1 :: [OutExpr] - ; mb_match <- if isClassOpId fun + ; mb_match <- if not (isPrimOpId fun) then tryRules zapped_env rules_for_me fun out_args else return Nothing ; case mb_match of { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/46312f3ef5f5c74f483cb63a5f2b62ff6a23c51f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/46312f3ef5f5c74f483cb63a5f2b62ff6a23c51f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/9ba2dc2d/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 14 16:38:04 2025 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 14 Mar 2025 12:38:04 -0400 Subject: [Git][ghc/ghc][wip/andreask/interpreter_primops] 105 commits: hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc Message-ID: <67d45b6c4c671_286200c5c74728c0@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/interpreter_primops at Glasgow Haskell Compiler / GHC Commits: 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 94a8c70f by Andreas Klebinger at 2025-03-14T17:15:54+01:00 Initial PoC for primop support in the Interpreter. This commit adds support for a very small number of primops directly to the interpreter. Code decently heavy on those primops like code involving IntSet runs about 25% faster with optimized core and these changes. For core without breakpoints this can go up to close to 50%. testsuite: Run foundation test in ghci and ghci-opt ways Running this test using optimised core is a good test for implementing numeric primops in the interpreter. This test currently fails in `ghci-opt` way when breakpoints are enabled so they are disabled for now. Compare compiled primop vs interpreted primop test - - - - - 469 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Serialized.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - m4/fp_settings.m4 - rts/Disassembler.c - rts/HeapStackCheck.cmm - rts/Interpreter.c - rts/PrimOps.cmm - rts/include/RtsAPI.h - rts/include/rts/Bytecodes.h - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/numeric/should_run/all.T - testsuite/tests/numeric/should_run/foundation.hs - testsuite/tests/numeric/should_run/foundation.stdout - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T21003.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - utils/genprimopcode/Main.hs - − utils/genprimopcode/Makefile - utils/genprimopcode/Syntax.hs - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/41256981ab5348698207e2d1d59f548f7331e293...94a8c70f7b991452ae465b5c5b9cffac2e385b35 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/41256981ab5348698207e2d1d59f548f7331e293...94a8c70f7b991452ae465b5c5b9cffac2e385b35 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/99bfa204/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 17:10:02 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Mar 2025 13:10:02 -0400 Subject: [Git][ghc/ghc][wip/T23109] 29 commits: users guide: Fix typo Message-ID: <67d462ead57d4_28f4a6c6c78-192@gitlab.mail> Simon Peyton Jones pushed to branch wip/T23109 at Glasgow Haskell Compiler / GHC Commits: cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 63d24264 by Simon Peyton Jones at 2025-03-14T17:09:51+00:00 Make newtype instances opaque I think this will help with #23109 Wibbles Allow SelCo for newtype classes Experimental change Wibble Furher wibbles Further improvments Further wibbles esp exprIsConLike Run classop rule first Newtype classops are small needs comments Wibble imports Wibbles Notably: define and use mkNewTypeDictApp Make newtype-class data constructors not inline This variant tries * Making the data constructor for a newtype class not inline * exprIsConApp_maybe treats it like a normal data constructor * CoreToStg discards it (perhaps CorePrep should do that instead) * Some as-it-turns-out unforced changes to corePrepPgm that makes it pass all TyCons, not just the data tycons * Significantly simpler story in mkNewTypeDictApp Wibble Get rid of newtype classes in CorePrep not CoreToStg Comment out bits that I think are no longer necessary * Extra field in ClassOpId, and classOpDictApp_maybe in Simplify.Iteration * Newtype classes being injective * Don't preInlineUnconditionally Dfuns * mkNewTypeDictApp * Zonking of unfoldings (only necessary for those local dfuns) Wibble Allow pushDataCon on ClassTyCon newtypes The fact that there is no *actual* data constructor in the end i kind-of-irrelevant, and we turn out to get quite a lot of class-op (d |> co) where co : C t1 ~R C t2 Wibbles to merge Make newtype classes pretend to be injective Make class datacons be have-no-unfolding Fixes the problem reported in #20689 @Mikolaj wibble Don't make a closure table for type data decls Make UanaryClass a new AlgTyConRhs work in progress, won't compile More wibbles More wibbbles More wibbles Unused bindings Unused import Wibbles Wibbles Wibble Wibbles Remove tyConAlgDataCons_maybe, and tyConSingleAlgDataCon_maybe Rename dontUnbox to canUnboxType (flippping sign) Rebase wibbles More rebase wibbles Yet more rebase wibbles Wibble imports Import wibble Adjust type of evCast ..to avoid gratuitous breakage Re-add mkEvCast, but DEPRECATED - - - - - 600777ba by Simon Peyton Jones at 2025-03-14T17:09:52+00:00 Wibbles - - - - - d800d1cd by Simon Peyton Jones at 2025-03-14T17:09:52+00:00 Revert ConLike change I'm not sure why I made this change - - - - - 5a727a5e by Simon Peyton Jones at 2025-03-14T17:09:52+00:00 No newtype axioms for unary type classes - - - - - a3112c2d by Simon Peyton Jones at 2025-03-14T17:09:52+00:00 Inline unary-class dfuns df d1 ... dn = MkD (op d1 .. dn) remembering that the MkD will disappear in the end This makes a big difference to compile time for tests WWRec T15164 - - - - - 194 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm.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/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - − compiler/GHC/Tc/Types/EvTerm.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/RepType.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/TyThing.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - compiler/ghc.cabal.in - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/using-concurrent.rst - libraries/ghc-boot/GHC/Serialized.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - rts/HeapStackCheck.cmm - rts/PrimOps.cmm - rts/linker/MachO.c - rts/linker/MachOTypes.h - testsuite/driver/junit.py - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/dmdanal/sigs/T21888.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/numeric/should_compile/T15547.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/simplCore/should_compile/T17366.stderr - testsuite/tests/simplCore/should_compile/T17966.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - testsuite/tests/tcplugins/CtIdPlugin.hs - testsuite/tests/typecheck/should_compile/T12763.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs - utils/check-exact/ExactPrint.hs - utils/dump-decls/Main.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ef8709e3fc15a55702e88b09971af1d20d0b8a95...a3112c2d507d07bdab98c1b2f7bb96dd052a3729 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ef8709e3fc15a55702e88b09971af1d20d0b8a95...a3112c2d507d07bdab98c1b2f7bb96dd052a3729 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/d0da636a/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 17:12:17 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Mar 2025 13:12:17 -0400 Subject: [Git][ghc/ghc][master] Don't report used duplicate record fields as unused Message-ID: <67d463714f1d3_28f4a6fa514482a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 0cb1db92 by sheaf at 2025-03-14T13:11:44-04:00 Don't report used duplicate record fields as unused This commit fixes the bug reported in #24035 in which the import of a duplicate record field could be erroneously reported as unused. The issue is that an import of the form "import M (fld)" can import several different 'Name's, and we should only report an error if ALL of those 'Name's are unused, not if ANY are. Note [Reporting unused imported duplicate record fields] in GHC.Rename.Names explains the solution to this problem. Fixes #24035 - - - - - 12 changed files: - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Rename/Names.hs - testsuite/tests/deriving/should_compile/T17324.stderr - testsuite/tests/module/T11970A.stderr - testsuite/tests/module/mod176.stderr - testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr - testsuite/tests/rename/should_compile/T14881.stderr - + testsuite/tests/rename/should_compile/T24035.hs - + testsuite/tests/rename/should_compile/T24035_aux.hs - + testsuite/tests/rename/should_compile/T24035b.hs - + testsuite/tests/rename/should_compile/T24035b.stderr - testsuite/tests/rename/should_compile/all.T Changes: ===================================== compiler/GHC/Hs/ImpExp.hs ===================================== @@ -259,7 +259,6 @@ ieNames (IEVar _ (L _ n) _) = [ieWrappedName n] ieNames (IEThingAbs _ (L _ n) _) = [ieWrappedName n] ieNames (IEThingAll _ (L _ n) _) = [ieWrappedName n] ieNames (IEThingWith _ (L _ n) _ ns _) = ieWrappedName n : map (ieWrappedName . unLoc) ns --- NB the above case does not include names of field selectors ieNames (IEModuleContents {}) = [] ieNames (IEGroup {}) = [] ieNames (IEDoc {}) = [] ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -93,6 +93,7 @@ import GHC.Data.FastString.Env import GHC.Data.Maybe import GHC.Data.List.SetOps ( removeDups ) +import Control.Arrow ( second ) import Control.Monad import Data.Foldable ( for_ ) import Data.IntMap ( IntMap ) @@ -100,6 +101,8 @@ import qualified Data.IntMap as IntMap import Data.Map ( Map ) import qualified Data.Map as Map import Data.Ord ( comparing ) +import Data.Semigroup ( Any(..) ) +import qualified Data.Semigroup as S import Data.List ( partition, find, sortBy ) import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.List.NonEmpty as NE @@ -108,6 +111,7 @@ import qualified Data.Set as S import System.FilePath ((</>)) import System.IO + {- ************************************************************************ * * @@ -1842,21 +1846,21 @@ findImportUsage imports used_gres -- srcSpanEnd: see Note [The ImportMap] `orElse` [] - used_names = mkNameSet (map greName used_gres) + used_gre_env = mkGlobalRdrEnv used_gres used_parents = mkNameSet (mapMaybe greParent_maybe used_gres) unused_imps -- Not trivial; see eg #7454 = case imps of Just (Exactly, L _ imp_ies) -> - foldr (add_unused . unLoc) emptyNameSet imp_ies + let unused = foldr (add_unused . unLoc) (UnusedNames emptyNameSet emptyFsEnv) imp_ies + in collectUnusedNames unused _other -> emptyNameSet -- No explicit import list => no unused-name list - add_unused :: IE GhcRn -> NameSet -> NameSet - add_unused (IEVar _ n _) acc = add_unused_name (lieWrappedName n) acc - add_unused (IEThingAbs _ n _) acc = add_unused_name (lieWrappedName n) acc + add_unused :: IE GhcRn -> UnusedNames -> UnusedNames + add_unused (IEVar _ n _) acc = add_unused_name (lieWrappedName n) True acc + add_unused (IEThingAbs _ n _) acc = add_unused_name (lieWrappedName n) False acc add_unused (IEThingAll _ n _) acc = add_unused_all (lieWrappedName n) acc - add_unused (IEThingWith _ p wc ns _) acc = - add_wc_all (add_unused_with pn xs acc) + add_unused (IEThingWith _ p wc ns _) acc = add_wc_all (add_unused_with pn xs acc) where pn = lieWrappedName p xs = map lieWrappedName ns add_wc_all = case wc of @@ -1864,21 +1868,115 @@ findImportUsage imports used_gres IEWildcard _ -> add_unused_all pn add_unused _ acc = acc - add_unused_name n acc - | n `elemNameSet` used_names = acc - | otherwise = acc `extendNameSet` n - add_unused_all n acc - | n `elemNameSet` used_names = acc - | n `elemNameSet` used_parents = acc - | otherwise = acc `extendNameSet` n + add_unused_name :: Name -> Bool -> UnusedNames -> UnusedNames + add_unused_name n is_ie_var acc@(UnusedNames acc_ns acc_fs) + | is_ie_var + , isFieldName n + -- See Note [Reporting unused imported duplicate record fields] + = let + fs = getOccFS n + (flds, flds_used) = lookupFsEnv acc_fs fs `orElse` (emptyNameSet, Any False) + acc_fs' = extendFsEnv acc_fs fs (extendNameSet flds n, Any used S.<> flds_used) + in UnusedNames acc_ns acc_fs' + | used + = acc + | otherwise + = UnusedNames (acc_ns `extendNameSet` n) acc_fs + where + used = isJust $ lookupGRE_Name used_gre_env n + + add_unused_all :: Name -> UnusedNames -> UnusedNames + add_unused_all n (UnusedNames acc_ns acc_fs) + | Just {} <- lookupGRE_Name used_gre_env n = UnusedNames acc_ns acc_fs + | n `elemNameSet` used_parents = UnusedNames acc_ns acc_fs + | otherwise = UnusedNames (acc_ns `extendNameSet` n) acc_fs + + add_unused_with :: Name -> [Name] -> UnusedNames -> UnusedNames add_unused_with p ns acc - | all (`elemNameSet` acc1) ns = add_unused_name p acc1 - | otherwise = acc1 + | all (`elemNameSet` acc1_ns) ns = add_unused_name p False acc1 + | otherwise = acc1 where - acc1 = foldr add_unused_name acc ns - -- If you use 'signum' from Num, then the user may well have - -- imported Num(signum). We don't want to complain that - -- Num is not itself mentioned. Hence the two cases in add_unused_with. + acc1@(UnusedNames acc1_ns _acc1_fs) = foldr (\n acc' -> add_unused_name n False acc') acc ns + -- If you use 'signum' from Num, then the user may well have + -- imported Num(signum). We don't want to complain that + -- Num is not itself mentioned. Hence the two cases in add_unused_with. + + +-- | An accumulator for unused names in an import list. +-- +-- See Note [Reporting unused imported duplicate record fields]. +data UnusedNames = + UnusedNames + { unused_names :: NameSet + -- ^ Unused 'Name's in an import list, not including record fields + -- that are plain 'IEVar' imports + , rec_fld_uses :: FastStringEnv (NameSet, Any) + -- ^ Record fields imported without a parent (i.e. an 'IEVar' import). + -- + -- The 'Any' value records whether any of the record fields + -- sharing the same underlying 'FastString' have been used. + } +instance Outputable UnusedNames where + ppr (UnusedNames nms flds) = + text "UnusedNames" <+> + braces (ppr nms <+> ppr (fmap (second getAny) flds)) + +-- | Collect all unused names from a 'UnusedNames' value. +collectUnusedNames :: UnusedNames -> NameSet +collectUnusedNames (UnusedNames { unused_names = nms, rec_fld_uses = flds }) + = nms S.<> unused_flds + where + unused_flds = nonDetFoldFsEnv collect_unused emptyNameSet flds + collect_unused :: (NameSet, Any) -> NameSet -> NameSet + collect_unused (nms, Any at_least_one_name_is_used) acc + | at_least_one_name_is_used = acc + | otherwise = unionNameSet nms acc + +{- Note [Reporting unused imported duplicate record fields] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we have (#24035): + + {-# LANGUAGE DuplicateRecordFields #-} + module M1 (R1(..), R2(..)) where + data R1 = MkR1 { fld :: Int } + data R2 = MkR2 { fld :: Int } + + {-# LANGUAGE DuplicateRecordFields #-} + module M2 where + import M1 (R1(MkR1), R2, fld) + f :: R1 -> Int + f (MkR1 { fld = x }) = x + g :: R2 -> Int + g _ = 3 + +In the import of 'M1' in 'M2', the 'fld' import resolves to two separate GREs, +namely R1(fld) and R2(fld). From the perspective of the renamer, and in particular +the 'findImportUsage' function, it's as if the user had imported the two names +separately (even though no source syntax allows that). + +This means that we need to be careful when reporting unused imports: the R2(fld) +import is indeed unused, but because R1(fld) is used, we should not report +fld as unused altogether. + +To achieve this, we keep track of record field imports without a parent (i.e. +using the IEVar constructor) separately from other import items, using the +UnusedNames datatype. +Once we have accumulated usages, we emit warnings for unused record fields +without parents one whole group (of record fields sharing the same textual name) +at a time, and only if *all* of the record fields in the group are unused; +see 'collectUnusedNames'. + +Note that this only applies to record fields imported without a parent. If we +had: + + import M1 (R1(MkR1, fld), R2(fld)) + f :: R1 -> Int + f (MkR1 { fld = x }) = x + g :: R2 -> Int + g _ = 3 + +then of course we should report the second 'fld' as unused. +-} {- Note [The ImportMap] @@ -1945,12 +2043,15 @@ warnUnusedImport rdr_env (L loc decl, used, unused) | null unused = return () - -- Only one import is unused, with `SrcSpan` covering only the unused item instead of - -- the whole import statement + -- Some imports are unused: make the `SrcSpan` cover only the unused + -- items instead of the whole import statement | Just (_, L _ imports) <- ideclImportList decl - , length unused == 1 - , Just (L loc _) <- find (\(L _ ie) -> ((ieName ie) :: Name) `elem` unused) imports - = addDiagnosticAt (locA loc) (TcRnUnusedImport decl (UnusedImportSome sort_unused)) + , let unused_locs = [ locA loc | L loc ie <- imports + , name <- ieNames ie + , name `elem` unused ] + , loc1 : locs <- unused_locs + , let span = foldr1 combineSrcSpans ( loc1 NE.:| locs ) + = addDiagnosticAt span (TcRnUnusedImport decl (UnusedImportSome sort_unused)) -- Some imports are unused | otherwise @@ -2263,3 +2364,4 @@ addDupDeclErr gres@(gre :| _) checkConName :: RdrName -> TcRn () checkConName name = checkErr (isRdrDataCon name || isRdrTc name) (TcRnIllegalDataCon name) + ===================================== testsuite/tests/deriving/should_compile/T17324.stderr ===================================== @@ -1,4 +1,4 @@ - -T17324.hs:8:1: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] +T17324.hs:8:21: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] The import of ‘Dual, Product, Sum’ from module ‘Data.Monoid’ is redundant + ===================================== testsuite/tests/module/T11970A.stderr ===================================== @@ -1,5 +1,5 @@ [1 of 2] Compiling T11970A1 ( T11970A1.hs, T11970A1.o ) [2 of 2] Compiling T11970A ( T11970A.hs, T11970A.o ) - -T11970A.hs:3:1: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] +T11970A.hs:3:19: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] The import of ‘Fail(b)’ from module ‘T11970A1’ is redundant + ===================================== testsuite/tests/module/mod176.stderr ===================================== @@ -1,4 +1,4 @@ - -mod176.hs:4:1: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] +mod176.hs:4:23: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] The import of ‘Monad, return’ from module ‘Control.Monad’ is redundant + ===================================== testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr ===================================== @@ -1,5 +1,4 @@ [1 of 3] Compiling OverloadedRecFldsFail06_A ( OverloadedRecFldsFail06_A.hs, OverloadedRecFldsFail06_A.o ) - OverloadedRecFldsFail06_A.hs:9:15: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: data constructor ‘MkUnused’ @@ -8,9 +7,9 @@ OverloadedRecFldsFail06_A.hs:9:42: warning: [GHC-40910] [-Wunused-top-binds (in OverloadedRecFldsFail06_A.hs:9:59: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: record field of MkUnused ‘used_locally’ -[2 of 3] Compiling Main ( overloadedrecfldsfail06.hs, overloadedrecfldsfail06.o ) -overloadedrecfldsfail06.hs:7:1: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] +[2 of 3] Compiling Main ( overloadedrecfldsfail06.hs, overloadedrecfldsfail06.o ) +overloadedrecfldsfail06.hs:7:35: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] The import of ‘MkV, Unused, Unused(unused), V(x), U(y)’ from module ‘OverloadedRecFldsFail06_A’ is redundant @@ -19,11 +18,11 @@ overloadedrecfldsfail06.hs:8:1: error: [GHC-66111] [-Wunused-imports (in -Wextra except perhaps to import instances from ‘OverloadedRecFldsFail06_A’ To import instances alone, use: import OverloadedRecFldsFail06_A() -overloadedrecfldsfail06.hs:9:1: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] +overloadedrecfldsfail06.hs:9:50: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] The qualified import of ‘V(y)’ from module ‘OverloadedRecFldsFail06_A’ is redundant -overloadedrecfldsfail06.hs:10:1: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] +overloadedrecfldsfail06.hs:10:50: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] The qualified import of ‘U, U(x)’ from module ‘OverloadedRecFldsFail06_A’ is redundant @@ -36,3 +35,4 @@ overloadedrecfldsfail06.hs:18:28: error: [GHC-02256] [-Wambiguous-fields (in -Wd Ambiguous record update with parent type constructor ‘V’. This type-directed disambiguation mechanism will not be supported by -XDuplicateRecordFields in future releases of GHC. Consider disambiguating using module qualification instead. + ===================================== testsuite/tests/rename/should_compile/T14881.stderr ===================================== @@ -1,6 +1,6 @@ [1 of 2] Compiling T14881Aux ( T14881Aux.hs, T14881Aux.o ) [2 of 2] Compiling T14881 ( T14881.hs, T14881.o ) - -T14881.hs:3:1: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] +T14881.hs:3:45: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] The qualified import of ‘adjust, length, L(tail), L(x)’ from module ‘T14881Aux’ is redundant + ===================================== testsuite/tests/rename/should_compile/T24035.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE DuplicateRecordFields #-} +module T24035 where +import T24035_aux (R1 (MkR1, ra), rb) + +x :: R1 -> Bool +x (MkR1 { rb = x0 }) = x0 + +y :: R1 -> Int +y (MkR1 { ra = y0 }) = y0 ===================================== testsuite/tests/rename/should_compile/T24035_aux.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE DuplicateRecordFields #-} +module T24035_aux (R1(..), R2(..)) where + +data R1 = MkR1 {ra :: Int, rb :: Bool} +data R2 = MkR2 {ra :: Int, rb :: Bool} ===================================== testsuite/tests/rename/should_compile/T24035b.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE DuplicateRecordFields #-} + +module T24035b where +import T24035_aux (R1 (MkR1, ra, rb), R2(rb)) + +x :: R1 -> Bool +x (MkR1 { rb = x0 }) = x0 + +y :: R1 -> Int +y (MkR1 { ra = y0 }) = y0 + +-- Use R2 to avoid unused import warning for R2 +useR2 :: R2 -> Int +useR2 _ = 42 ===================================== testsuite/tests/rename/should_compile/T24035b.stderr ===================================== @@ -0,0 +1,3 @@ +T24035b.hs:4:39: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] + The import of ‘R2(rb)’ from module ‘T24035_aux’ is redundant + ===================================== testsuite/tests/rename/should_compile/all.T ===================================== @@ -210,6 +210,8 @@ test('T23434', normal, compile, ['']) test('T23510b', normal, compile, ['']) test('T23512b', normal, compile, ['']) test('T23664', normal, compile, ['']) +test('T24035', [extra_files(['T24035_aux.hs'])], multimod_compile, ['T24035', '-v0 -Wunused-imports']) +test('T24035b', [extra_files(['T24035_aux.hs'])], multimod_compile, ['T24035b', '-v0 -Wunused-imports']) test('T24037', normal, compile, ['']) test('T24084', [extra_files(['T24084_A.hs', 'T24084_B.hs'])], multimod_compile, ['T24084', '-v0']) test('ExportWarnings1', extra_files(['ExportWarnings_base.hs', 'ExportWarnings_aux.hs']), multimod_compile, ['ExportWarnings1', '-v0 -Wno-duplicate-exports -Wx-custom']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0cb1db9270e11469f11a2ccf323219e032c2a312 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0cb1db9270e11469f11a2ccf323219e032c2a312 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/efc53e6e/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 17:12:47 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Mar 2025 13:12:47 -0400 Subject: [Git][ghc/ghc][master] binary: Directly copy ShortByteString to buffer rather than go via ByteString Message-ID: <67d4638f78757_28f4a63e7d088653@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: f1830d74 by Matthew Pickering at 2025-03-14T13:12:21-04:00 binary: Directly copy ShortByteString to buffer rather than go via ByteString This avoids allocating an intermediate bytestring. I just noticed on a profile that `putFS` was allocating, and it seemed strange to me why since it should just copy the contents of the FastString into the already allocated buffer. It turned out we were going indirectly via a ByteString. Fixes #25861 - - - - - 1 changed file: - compiler/GHC/Utils/Binary.hs Changes: ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -135,6 +135,7 @@ import Data.ByteString (ByteString, copy) import Data.Coerce import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS +import qualified Data.ByteString.Short.Internal as SBS import Data.IORef import Data.Char ( ord, chr ) import Data.List.NonEmpty ( NonEmpty(..)) @@ -1771,7 +1772,7 @@ type SymbolTable a = Array Int a --------------------------------------------------------- putFS :: WriteBinHandle -> FastString -> IO () -putFS bh fs = putBS bh $ bytesFS fs +putFS bh fs = putSBS bh $ fastStringToShortByteString fs getFS :: ReadBinHandle -> IO FastString getFS bh = do @@ -1791,6 +1792,18 @@ getByteString bh l = BS.create l $ \dest -> do getPrim bh l (\src -> copyBytes dest src l) +putSBS :: WriteBinHandle -> SBS.ShortByteString -> IO () +putSBS bh sbs = do + let l = SBS.length sbs + put_ bh l + putPrim bh l (\p -> SBS.copyToPtr sbs 0 p l) + + +getSBS :: ReadBinHandle -> IO SBS.ShortByteString +getSBS bh = do + l <- get bh :: IO Int + getPrim bh l (\src -> SBS.createFromPtr src l) + putBS :: WriteBinHandle -> ByteString -> IO () putBS bh bs = BS.unsafeUseAsCStringLen bs $ \(ptr, l) -> do @@ -1803,6 +1816,10 @@ getBS bh = do BS.create l $ \dest -> do getPrim bh l (\src -> copyBytes dest src l) +instance Binary SBS.ShortByteString where + put_ bh f = putSBS bh f + get bh = getSBS bh + instance Binary ByteString where put_ bh f = putBS bh f get bh = getBS bh View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f1830d74b41f125eb5154c203ae4450f592f1e18 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f1830d74b41f125eb5154c203ae4450f592f1e18 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/7834faea/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 17:40:49 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Mar 2025 13:40:49 -0400 Subject: [Git][ghc/ghc][wip/T20264] 147 commits: testsuite: Mark T23071 and T2047 as fragile on FreeBSD Message-ID: <67d46a21c267a_28f4a683bc9c15094@gitlab.mail> Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC Commits: ef0e6cfc by Ben Gamari at 2025-02-17T19:20:09-05:00 testsuite: Mark T23071 and T2047 as fragile on FreeBSD These inexplicably fail on FreeBSD on CI. Sadly I am unable to reproduce this locally but regardless this is holding up Marge so I will mark them as fragile for now. Addresses #25751. - - - - - 7596675e by Jens Petersen at 2025-02-18T08:53:08-05:00 hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc - - - - - 975d932c by Rodrigo Mesquita at 2025-02-18T08:53:45-05:00 Inline join points for rhs without free vars While investigating #25170, we ran into a program (T16473) that allocated 67% more because of a join point that failed to inline. Note [Duplicating join points] explains why we want to be conservative when inlining join points, using as an example a join point that captures a free variable `f` that becomes available in the continuation `blah` for further optimisations, as opposed to being lambda-abstracted. However, when the RHS of the join point has no free variables and is trivial, the same argument does not apply, and there's nothing to gain from preserving it. On the contrary, not inlining these trivial join points such as $j f x = K f x |> co can be actively harmful as they prevent useful optimisations from firing on the known constructor application. #25723 is such an example. Therefore, we've extended `uncondInlineJoin` to allow duplicating such closed trivial join points. See the updated Note [Duplicating join points] for further details. Additionally, merge the guards in uncondInlineJoin for point DJ3(b) anad DJ3(c) of Note [Duplicating join points] to avoid an unnecessary traversal in the call to `collectArgs`; it's also more uniform. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> Fixes #25723 - - - - - 78de1a55 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Scrub some partiality in `GHC.Tc.Gen.Match`. In particular, we construct a list of the same length as another list, then loop over both and panic if their lengths are unequal. We can avoid this. - - - - - 1dfe9325 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 Make list of `ParStmtBlock` in `ParStmt` `NonEmpty`. In the ParStmt constructor Language.Haskell.Syntax.Expr.StmtLR, the 2nd argument, the list of ParStmtBlocks, must be NonEmpty; make it so. - - - - - 0e3575b5 by M Farkas-Dyck at 2025-02-18T08:54:31-05:00 GHC.Tc.Gen.Match: Added type signatures for `loop` functions. - - - - - c9ffcfee by sternenseemann at 2025-02-18T08:55:14-05:00 GHC: fix reference to function in Note [Target code interpreter] As far as I could tell, setSessionDynFlags doesn't deal with hsc_interp. Also added a backreference so this will be updated in the future. - - - - - ab77fc8c by sheaf at 2025-02-18T08:55:57-05:00 Account for skolem escape in mightEqualLater This commit: 1. Refactors checkTyEqRhs to allow it be called in pure contexts, which means it skips doing any on-the-fly promotion. 2. Calls checkTyEqRhs in mightEqualLater to check whether it a MetaTv can unify with a RHS or whether that would cause e.g. skolem escape errors or concreteness errors. Fixes #25744 - - - - - cb8a06a4 by Sylvain Henry at 2025-02-18T08:56:52-05:00 Remove a bunch of Makefiles from old build system - - - - - e12d6b39 by M Farkas-Dyck at 2025-02-18T08:57:37-05:00 Totalize `GHC.HsToCore.Match.matchWrappers.initNablasGRHSs`. Converting from `NonEmpty` to `[]` and back is totally needless. - - - - - cd2be3be by Matthew Pickering at 2025-02-18T08:58:14-05:00 interpreter: Always print uniques for BCO_NAME labels In the previous commit I omitted to include the unique, which still makes it very difficult to trace back where the BCO came from. - - - - - c4e112fc by Matthew Pickering at 2025-02-18T08:58:51-05:00 interpreter: Fix overflows and reentrancy in statistics calculation 1. Use unsigned long for counter, as they can easily overflow if you are running a long benchmark. 2. Make interp_shutdown reentrant by copying the command frequency table into an array. Fixes #25756 - - - - - 70ac6222 by M Farkas-Dyck at 2025-02-18T14:22:06-08:00 Use `Foldable1` where appropriate, avoiding much needless panicking. In some cases, where not readily feasible to modify code to use `NonEmpty`, merely use `expectNonEmpty` to make explicit we are panicking if we have an empty list. - - - - - a3f0a506 by Sylvain Henry at 2025-02-19T05:27:30-05:00 Testsuite: fix deprecation warning > DeprecationWarning: 'count' is passed as positional argument - - - - - ef5470a2 by Ben Gamari at 2025-02-19T16:30:53+00:00 Cmm/Parser: Add surface syntax for Mul2 MachOps These are otherwise very hard to test in isolation. - - - - - 59b9307b by Cheng Shao at 2025-02-19T20:24:40-05:00 testsuite: fix InternalCounters test with +debug_ghc The `InternalCounters` test case fails when ghc is built with `+debug_ghc`. This patch skips it in that case and allows the testsuite to pass for the `+debug_ghc` flavour transformer. - - - - - aa69187d by M Farkas-Dyck at 2025-02-19T20:25:31-05:00 Scrub a use of `head` in `GHC.Driver.Make.downsweep_imports.checkDuplicates`. - - - - - 1c8e608a by Cheng Shao at 2025-02-21T20:18:41-05:00 compiler: use fromAscList when applicable This patch uses fromAscList (with O(n) complexity) instead of fromList (with O(nlogn) complexity) in certain Binary instances. It's safe to do so since the corresponding serialization logic is based on toList (same as toAscList). - - - - - 549e0aff by Ben Gamari at 2025-02-21T20:19:18-05:00 rts/linker/MachO: Mark internal symbols as static There is no reason why these should have external linkage. - - - - - fbf3d020 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: bump dyld v8 heap size limit This patch sets `--max-old-space-size=65536` as wasm dyld shebang arguments to lessen v8 heap pressure in certain workloads that load the full ghc package. It doesn't really commit 64G memory but it does help reduce v8 gc overhead. - - - - - cb60da24 by Cheng Shao at 2025-02-22T07:41:01-05:00 wasm: fix dyld for shared libraries created by llvm 20.x This patch fixes wasm dyld script for shared libraries created by llvm 20.x. The __wasm_apply_data_relocs function is now optional and may be omitted for shared libraries without any runtime relocatable data segments, so only call __wasm_apply_data_relocs when it's present. - - - - - 7eea38c8 by Cheng Shao at 2025-02-22T07:41:37-05:00 driver: fix wasm backend sysroot lookup logic when -flto is passed For the wasm target, the driver calls `wasm32-wasi-clang --print-search-dirs` and finds the sysroot directory that contains libc.so etc, then passes the directory path to dyld. However, when GHC is configured with -flto as a part of C/C++ compiler flags, the clang driver would insert a llvm-lto specific directory in the --print-search-dirs output and the driver didn't take that into account. This patch fixes it and always selects the non-lto sysroot directory to be passed to dyld. This is one small step towards supporting building all cbits with lto for wasm. - - - - - f3bfe31e by Cheng Shao at 2025-02-23T14:06:25-05:00 wasm: add Note [Variable passing in JSFFI] as !13583 follow up This patch adds a note to explain how the magic variables like `__ghc_wasm_jsffi_dyld` are brought into scope of JSFFI code snippets, as follow up work of !13583. - - - - - c318be56 by Cheng Shao at 2025-02-23T14:07:02-05:00 libffi: update to 3.4.7 Bumps libffi submodule. - - - - - 33aca30f by sheaf at 2025-02-25T08:58:46-05:00 LLVM: account for register type in funPrologue We were not properly accounting for the live register type of global registers in GHC.CmmToLlvm.CodeGen.funPrologue. This meant that we could allocated a register at type <4 x i32> but try to write to it at type <8 x i16>, which LLVM doesn't much like. This patch fixes that by inserting intermerdiate casts when necessary. Fixes #25730 - - - - - 0eb58b0e by sheaf at 2025-02-25T08:59:29-05:00 base: make Data.List.NonEmpty.unzip match Data.List This commit makes Data.List.NonEmpty.unzip match the implementation of Data.List, as was suggested in approved CLC proposal #107. - - - - - f4da90f1 by Matthew Pickering at 2025-02-25T14:11:21-05:00 interpreter: Fix underflow frame lookups BCOs can be nested, resulting in nested BCO stack frames where the inner most stack frame can refer to variables stored on earlier stack frames via the PUSH_L instruction. |---------| | BCO_1 | -<-┠|---------| ......... | |---------| | PUSH_L <n> | BCO_N | ->-┘ |---------| Here BCO_N is syntactically nested within the code for BCO_1 and will result in code that references the prior stack frame of BCO_1 for some of it's local variables. If a stack overflow happens between the creation of the stack frame for BCO_1 and BCO_N the RTS might move BCO_N to a new stack chunk while leaving BCO_1 in place, invalidating a simple offset based reference to the outer stack frames. Therefore `ReadSpW` first performs a bounds check to ensure that accesses onto the stack will succeed. If the target address would not be a valid location for the current stack chunk then `slow_spw` function is called, which dereferences the underflow frame to adjust the offset before performing the lookup. ┌->--x | CHK_1 | | CHK_2 | | | |---------| |---------| | └-> | BCO_1 | | UD_FLOW | -- x |---------| |---------| | | ...... | | |---------| | PUSH_L <n> | BCO_ N | ->-┘ |---------| Fixes #25750 - - - - - c3f2d284 by Vladislav Zavialov at 2025-02-25T14:11:58-05:00 Remove ArgPatBuilder ArgPatBuilder in Parser/PostProcess.hs became redundant with the introduction of InvisPat (36a75b80eb). This small refactoring removes it. - - - - - 0f2241e9 by sheaf at 2025-02-25T19:23:21-05:00 Propagate long distance info to guarded let binds This commit ensures that we propagate the enclosing long distance information to let bindings inside guards, in order to get accurate pattern-match checking warnings, in particular incomplete record selector warnings. Example: data D = K0 | K1 { fld :: Int } f :: D -> Int f d@(K1 {}) | let i = fld d = i f _ = 3 We now correctly recognise that the field selector 'fld' cannot fail, due to the outer pattern match which guarantees that the value 'd' has the field 'fld'. Fixes #25749 - - - - - 64b0d4d0 by Fangyi Zhou at 2025-02-25T19:24:07-05:00 wasm: use primitive opcodes for fabs and sqrt - Add new `WasmInstr` constructor `WasmSqrt` for sqrt, corresponding to primitivie operations in wasm. - When lowering CallishMachOp, use `WasmAbs` and `WasmSqrt` for F32 and F64 fabs and sqrt. - - - - - 272eaef0 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building stage1 haddock for cross ghc This commit enables building stage1 haddock for cross ghc. Without this change, hadrian would panic with "Unknown program" error when building the _build/stage1/bin/cross-prefix-haddock program needed by the docs-haddock target, even if it only needs to copy from _build/stage0/bin/cross-prefix-haddock. - - - - - a794e733 by Cheng Shao at 2025-02-25T19:24:43-05:00 hadrian: enable building docs for cross targets Hadrian used to omit the docs target as a part of binary-dist-dir for cross targets. This commit enables docs to be built as a part of cross bindists and it works just fine in CI. - - - - - 6dba56e1 by Cheng Shao at 2025-02-25T19:24:43-05:00 ci: build haddock/sphinx-html for wasm jobs This commit enables building haddock & sphinx-html documentation for wasm targets. The docs are useful for end users and should be tested in CI. I've omitted pdf & manpage generation for the wasm target; I've never found the pdf version of docs to be useful, and the manpage only contains `ghc.1` where we really want `wasm32-wasi-ghc.1` but that should be a separate issue to fix. - - - - - 2d6a63ab by Cheng Shao at 2025-02-25T19:25:20-05:00 ghci: remove unused showBreakArray function GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning. - - - - - b228fcb5 by Cheng Shao at 2025-02-25T19:25:57-05:00 ghc-heap: fix HalfWord incompatible Binary instances for cross GHC ghc-heap defines HalfWord as Word32/Word16 depending on host word size. For cross GHC with different host/target word sizes, the Binary instances are incompatible and breaks iserv serialization of any message type that involves HalfWord, breaking the ghci debugger. This patch fixes the issue and has been tested to fix ghci debugger functionality of the wasm backend. Fixes #25420 #25781. - - - - - ec02f8c2 by Rodrigo Mesquita at 2025-02-26T11:03:38-05:00 ghci-debugger: display thunks provenance if avail Improves reporting on ghci breakpoints when IPE information is available by printing, next to the thunk, the source file and src span where the thunk originated. Closes #25746 - - - - - 6acaff2b by Vladislav Zavialov at 2025-02-26T11:04:15-05:00 Tidy up error messages for TypeAbstractions 1. Print the '@' symbol before invisible patterns and improve phrasing: T24557c.hs:8:4: error: [GHC-11983] - Invisible type pattern pat is not allowed here + Illegal invisible type pattern: @pat + An invisible type pattern must occur in an argument position. 2. Use a single error code for all type abstractions deemed illegal due to the TypeAbstractions extension being disabled. Before this change: * [GHC-78249] was used in function equations, lambdas * [GHC-17916] was used in constructor patterns After this change: * [GHC-78249] is used to report all illegal type abstractions * [GHC-17916] is no longer used There was no reason for both error codes to exist and this distinction was a source of complexity in GHC/Tc/Errors/* and GHC/Rename/Pat.hs 3. Group the different "invisible type pattern" error constructors under a single parent constructor, TcRnIllegalInvisibleTypePattern containing BadInvisPatReason - - - - - 1ce9502e by Ben Gamari at 2025-02-27T04:48:29-05:00 haddock/doc: Drop version and release We currently have no way of keeping this up-to-date with the project version - - - - - 7f358f25 by Matthew Pickering at 2025-02-27T04:49:06-05:00 testsuite: Add test for :steplocal performance This adds a simple test which exercises #25779 - - - - - a6a3ffa6 by Sven Tennie at 2025-02-27T23:34:47-05:00 Do not deallocate stack for jump/switch table jumps Though the name is misleading, we consider them to be branching. For branch instructions we do not deallocate (parts of) the stack, but keep the stack pointer (sp) intact. - - - - - 39e51ddb by Sven Tennie at 2025-02-27T23:34:47-05:00 Add reproducer for dealloc instructions in switch table jump expressions (#25733) Measures taken to make the test stable: - Use 'a' as variable prefix, because X86 32bit stumbled over the variable name 'i386' - Flush stdout to make test output deterministic - Use type annotations to support 32bit archs - - - - - d427df93 by Sylvain Henry at 2025-02-27T23:35:30-05:00 Remove redundant location strings in expectJust and friends (#25743) Now we can use HasDebugCallStack instead to avoid cluttering the code with strings and to avoid maintaining those strings (e.g. renaming them when functions are renamed...). - - - - - 90f1190e by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Add export list to GHC.SysTools.Tasks - - - - - ec826009 by Ben Gamari at 2025-02-28T20:53:53-05:00 compiler: Pass --target to llvm-as As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta. - - - - - 9c1647d1 by Andreas Klebinger at 2025-02-28T20:54:30-05:00 cmmMachOpFoldM: Add missing pattern matches for bitcasts. Fixes #25771 - - - - - 3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00 Remove most of `GHC.Internal.Pack` Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS. - - - - - b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci: Don't set virtualCWD on every iteration The calls to withVirtualCWD were introduced to fix #2973, but this bug is no longer reproducible, even when `withVirtualCWD` is dropped. This cleanup was originally motivated by the performance of :steplocal, but the performance problem has now been fixed at its root in the next commit. Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and removing it simplifies the interpreter with no apparent drawbacks (testsuite is also happy with this change) - - - - - 73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00 ghci debugger: improve break/resume control flow After interpreting bytecode (`evalStmt`), we may want to hand off control to "GHCi.UI" in order to display an interactive break prompt: 1. When an /active/ breakpoint (one set with :break ...) is hit 2. At any breakpoint, when using :step from a breakpoint 3. At any breakpoint in the same function f, when :steplocal is called from a breakpoint in f 4. At any breakpoint in the same module, when :stepmodule is used Whether to pass control to the UI is now fully determined by `handleRunStatus` which transforms an `EvalStatus_` into an `ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to GHCi, it always means GHCi breaks. `handleRunStatus` determines whether to loop and resume evaluation right away, or when to return to GHCi (by returning `ExecBreak` or `ExecComplete`). - (1) is queried using the `BreakpointStatus` message (the `breakpointStatus` call) - (2,3,4) are determined by the predicate `breakHere step span`, which inspects the improved `SingleStep` type to determine whether we care about this breakpoint even if it is not active. This refactor solves two big performance problems with the previous control flow: - We no longer call `withArgs/withProgram` repeatedly in the break/resume loop, but rather just once "at the top". - We now avoid computing the expensive `bindLocalsAtBreakpoint` for breakpoints we'd never inspect. In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25` now takes 12 seconds rather than 49 seconds on my machine. ``` interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD ``` Fixes #25779 ------------------------- Metric Decrease: interpreter_steplocal ------------------------- - - - - - c78d8f55 by Cheng Shao at 2025-03-03T20:54:41+00:00 rts: fix top handler closure type signatures This commit fixes the runIO/runNonIO closure type signatures in the RTS which should be extern StgClosure. This allows us to remove an unnecessary type cast in the C foreign desugaring logic, as well as unneeded complications of JSFFI desugaring logic that also needs to generate C stubs that may refer to those top handler closures. Otherwise, we'll have to take special care to avoid generating "extern StgClosure" declarations for them as we would for other closures, just to avoid conflicting type signature error at stub compile time. - - - - - a204df3a by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: allow arbitrary label string for JSFFI exports This commit allows arbitrary label string to appear in a foreign export declaration, as long as the calling convention is javascript. Well, doesn't make sense to enforce it's a C function symbol for a JSFFI declaration anyway, and it gets in the way of implementing the "sync" flavour of exports. - - - - - 03ebab52 by Cheng Shao at 2025-03-03T20:54:41+00:00 compiler: wasm backend JSFFI sync exports This commit implements the synchronous flavour of the wasm backend JSFFI exports: - `foreign export javascript "foo sync"` exports a top-level Haskell binding as a synchronous JS function - `foreign import javascript "wrapper sync"` dynamically exports a Haskell function closure as a synchronous JS function - `foreign import javascript unsafe` is now re-entrant by lowering to a safe ccall - Also fix the issue that JSFFI dynamic exports didn't really work in TH & ghci (#25473) - - - - - b6ae908b by Cheng Shao at 2025-03-03T20:54:41+00:00 testsuite: test wasm backend JSFFI sync exports This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well. - - - - - edae2874 by Cheng Shao at 2025-03-03T20:54:41+00:00 docs: document wasm backend JSFFI sync exports This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature. - - - - - 9b54eecb by Cheng Shao at 2025-03-03T20:56:21+00:00 wasm: add error message to WouldBlockException This commit attaches an error message to WouldBlockException, for now the error message consists of the JS async import code snippet that thunk is trying to block for. This is useful for debugging synchronous callbacks that accidentally call an async JS function. - - - - - c331eebf by Cheng Shao at 2025-03-04T09:11:45-05:00 compiler: avoid overwriting existing writers in putWithTables This patch makes `putWithTables` avoid overwriting all existing UserData writers in the handle. This is crucial for GHC API users that use putWithUserData/getWithUserData for serialization logic that involve Names. - - - - - e9b7802b by Matthew Pickering at 2025-03-04T09:12:21-05:00 ghci: Serialise mi_top_env When loading core from interface files (or from a bytecode object in future) it's important to store what the top-level context of a module is. Otherwise, when you load the module into GHCi from the interface files, only exported identifiers from the top-level module are in scope on the repl. See the added test which demonstrates what this enables. The context at the GHCi prompt is everything that's in-scope in the TopEnvIface module. Since TopEnvIface imports identifier "a", we can evaluate "a" in the repl. In addition to all this, we can use this information in order to implement reifyModule in a more principled manner. This becomes even more important when you're debugging and what to set break-points on functions which are not imported. - - - - - 73e02068 by Matthew Pickering at 2025-03-04T09:12:21-05:00 Implement reifyModule in terms of mi_top_env mi_top_env provides precisely the information that reifyModule needs, the user written imports. This is important as it unblocks !9604 and #22188 Fixes #8489 - - - - - 0a99825d by Ben Gamari at 2025-03-04T09:12:57-05:00 hadrian: Refactor handling of test suite environment Previously we would set the environment variables used to run the testsuite driver using `setEnv` to set them in the Hadrian process. While looking into failures of a fix to #25752 I noticed this and took the opportunity to refactor. - - - - - 7ca72844 by Alan Zimmerman at 2025-03-04T09:13:34-05:00 [EPA] Sync with the ghc-exactprint repo This brings it into line with the changes in https://hackage.haskell.org/package/ghc-exactprint-1.12.0.0 But also keeps the latest changes from master. - - - - - 8f6cc90c by Matthew Pickering at 2025-03-05T04:48:02-05:00 perf: Speed up the bytecode assembler This commit contains a number of optimisations to the bytecode assembler. In programs which generate a large amount of bytecode, the assembler is called a lot of times on many instructions. 1. Specialise the assembleI function for the two intepreters to avoid having to materialise the intermediate free-monad like structure. 2. Directly compute the UArray and SmallArray needed rather than going via the intermediate SizedSeq 3. Use optimised monads 4. Define unrolled "any" and "mapM6" functions which can be inlined and avoid calling recursive functions. The resulting generated code is much more direct. Before: ./ByteCodeAsm /home/matt/ghc-profiling-light/_build/stage1/lib/ +RTS -s 48,923,125,664 bytes allocated in the heap 678,221,152 bytes copied during GC 395,648 bytes maximum residency (2 sample(s)) 50,040 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 11731 colls, 0 par 0.419s 0.425s 0.0000s 0.0004s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.000s ( 0.000s elapsed) MUT time 6.466s ( 6.484s elapsed) GC time 0.421s ( 0.426s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 6.887s ( 6.910s elapsed) After: 1,518,321,200 bytes allocated in the heap 4,299,552 bytes copied during GC 322,288 bytes maximum residency (2 sample(s)) 50,280 bytes maximum slop 6 MiB total memory in use (0 MiB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 369 colls, 0 par 0.003s 0.003s 0.0000s 0.0002s Gen 1 2 colls, 0 par 0.001s 0.001s 0.0007s 0.0012s INIT time 0.001s ( 0.001s elapsed) MUT time 0.465s ( 0.466s elapsed) GC time 0.004s ( 0.004s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.470s ( 0.471s elapsed) - - - - - f2d43e11 by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: expose all TH packages from proper GHC.Boot.* modules Previously we defined some modules here in the GHC.Internal namespace. Others were merely re-exposed from GHC.Internal. Re-exposed modules weren't handled correctly by Haddock, so the Haddocks for the `template-haskell` library couldn't see them. This change also makes the home package of these modules a bit clearer. Work towards #25705 - - - - - 91ef82df by Teo Camarasu at 2025-03-05T04:48:40-05:00 ghc-boot-th: fix synopsis formatting `@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim. - - - - - eb9fe1ec by Brandon Chinn at 2025-03-05T04:49:17-05:00 Collapse string gaps as \& (#25784) In 9.10, "\65\ \0" would result in "A0", but in 9.12, it results in "\650", due to the string refactoring I did in !13128. Previously, we were resolving escape codes and collapsing string gaps as we come across them, but after the refactor, string processing is broken out into phases, which is both more readable and useful for multiline strings. - - - - - 8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: make JSVal abstract in GHC.Wasm.Prim This commit makes JSVal an abstract type in the export list of GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non user facing implementation detail subject to change at any time. We should only expose things that are newtypes of JSVal, not JSVal itself. - - - - - 4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00 wasm: make JSVal internal Weak# point to lifted JSVal JSVal has an internal Weak# with the unlifted JSVal# object as key to arrange its builtin finalization logic. The Weak# used to designate Unit_closure as a dummy value; now this commit designates the lifted JSVal closure as the Weak# value. This allows the implementation of mkWeakJSVal which can be used to observe the liveliness of a JSVal and attach a user-specified finalizer. - - - - - 55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00 ghc-experimental: add mkWeakJSVal This commit adds a mkWeakJSVal function that can be used to set up a Weak pointer with a JSVal key to observe the key's lifetime and optionally attach a finalizer. - - - - - 8273d7d1 by Matthew Pickering at 2025-03-05T04:50:30-05:00 simplifier: Zap Id unfoldings before constructing InScopeSet in simpleOptExpr Care must be taken to remove unfoldings from `Var`s collected by exprFreeVars before using them to construct an in-scope set hence `zapIdUnfolding` in `init_subst`. Consider calling `simpleOptExpr` on an expression like ``` case x of (a,b) -> (x,a) ``` * One of those two occurrences of x has an unfolding (the one in (x,a), with unfolding x = (a,b)) and the other does not. (Inside a case GHC adds unfolding-info to the scrutinee's Id.) * But exprFreeVars just builds a set, so it's a bit random which occurrence is collected. * Then simpleOptExpr replaces each occurrence of x with the one in the in-scope set. * Bad bad bad: then the x in case x of ... may be replaced with a version that has an unfolding. Fixes #25790 - - - - - 07fe6d1d by Rodrigo Mesquita at 2025-03-05T04:51:07-05:00 docs: Fix ghci :doc documentation Fixes #25799 - - - - - a510b861 by Matthew Pickering at 2025-03-06T11:43:23+00:00 Add flag to control whether self-recompilation information is written to interface This patch adds the flag -fwrite-if-self-recomp which controls whether interface files contain the information necessary to answer the question: Do I need to recompile myself or is this current interface file suitable? Why? Most packages are only built once either by a distribution or cabal and then placed into an immutable store, after which we will never ask this question. Therefore we can derive two benefits from omitting this information. * Primary motivation: It vastly reduces the surface area for creating non-deterministic interface files. See issue #10424 which motivated a proper fix to that issue. Distributions have long contained versions of GHC which just have broken self-recompilation checking (in order to get deterministic interface files). * Secondary motivation: This reduces the size of interface files slightly.. the `mi_usages` field can be quite big but probably this isn't such a great benefit. * Third motivation: Conceptually clarity about which parts of an interface file are used in order to **communicate** with subsequent packages about the **interface** for a module. And which parts are used to self-communicate during recompilation checking. The main tracking issue is #22188 but fixes issues such as #10424 in a proper way. - - - - - 5b05c27b by Matthew Pickering at 2025-03-06T11:43:23+00:00 Disable self recomp in release flavour The interface files that we distribute should not contain any information which is used by the recompilation checking logic since source file will never be compiled again. I am not 100% sure this won't cause unexpected issues, there many be downstream consumers which are incorrectly using the information from interfaces, but this commit can be reverted if we detect issues. - - - - - 1d4c9824 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add surface syntax for Word/Float bitcast ops - - - - - 25c4a2a2 by Matthew Craven at 2025-03-06T18:11:59-05:00 Cmm: Add constant-folding for Word->Float bitcasts - - - - - 30bdea67 by Matthew Craven at 2025-03-06T18:11:59-05:00 Add tests for #25771 - - - - - 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 39c167f1 by Joseph Fourment at 2025-03-14T17:33:39+00:00 compiler: introduce type variable unfoldings The plan for #20264 is to introduce let-bound types to have observable sharing in types. To avoid the need to carry an environment when dealing with occurrences of these type variables, we embed the types they're bound to (if any) in a `tv_unfolding :: Maybe Type` attribute. This way, one can look through let-bound type variables using `coreView` and friends. In particular, definitional equality looks through unfoldings. - - - - - 39586e07 by Joseph Fourment at 2025-03-14T17:33:39+00:00 simple-opt: don't inline type-lets - - - - - ed0a3a44 by Joseph Fourment at 2025-03-14T17:33:39+00:00 specialise: fix type-lets in DFun unfoldings During specialisation, a dictionary being specialised gets a new unfolding by turning `DFun \ bndrs -> MkD @<T1> ... @<Tm> <op1> ... <opn>` into `DFun \ spec_bndrs -> MkD @((\ bndrs -> TYPE: <T1>) spec_args) ... ((\ bndrs -> <opn>) spec_args)` which in turns gets beta-reduced into `DFun \ spec_bndrs -> MkD (let { bndrs = spec_args } in TYPE: <T1>) ... (let { bndrs = spec_args } in <opn>)`. Previously, such let binders would immediately be substituted into the type so it didn't cause any issue, but now we want to avoid inlining. Arguments of the form `let { bndrs = spec_args } in TYPE: <T1>` are not considered as type arguments since they're not of the canonical form `TYPE: something`. This commit restores the previous behavior of substituting the specialised type arguments. Alternatively, we could attach some floated type bindings to `DFun`s. - - - - - 3ac72ef3 by Joseph Fourment at 2025-03-14T17:33:39+00:00 occur-anal: implement occurence analysis for type variables In order to find out let-bound type variables that are used only once, in the hope of inlining them, we need to track type variables as well in the occurrence analiser. Just like Id's, we attach an `OccInfo` to each (immutable) type variable, and we walk into types and coercions to accurately gather occurrences. - - - - - c4258f8f by Joseph Fourment at 2025-03-14T17:33:40+00:00 simplifier: don't inline type-lets Keep propagating type-lets further down the pipeline, in the simplifier. We also update CallArity, CprAnal, DmdAnal, WorkWrap, and Specialise to ignore type-lets. - - - - - 5a5d16f3 by Joseph Fourment at 2025-03-14T17:33:40+00:00 prep: make type-lets pass through CorePrep As a first attempt, ignore type-lets in CorePrep to avoid crashes. However, this is not enough: CorePrep also does some let-floating. If we don't float type-lets along with value-level let-bindings, the latter can float out of the scope of a type variable in use. - - - - - 45fa8abf by Joseph Fourment at 2025-03-14T17:33:40+00:00 simple-opt: fix simple_type_bind Also: - Inline small types using a new typeIsSmallEnoughToInline predicate - Inline single-occurrence variables - - - - - 1e21b8e7 by Joseph Fourment at 2025-03-14T17:33:40+00:00 simple-opt: make beta-reduction use simple_bind_type - - - - - d8267a23 by Joseph Fourment at 2025-03-14T17:33:40+00:00 iface: add IfaceTypeLetBndr to represent non-top-level type-let binders IfaceLetBndr isn't fit to represent type-let binders, as it includes a bunch of vacuous flags for Ids only. Instead of putting squares in circles, I added a new constructor for type binders. The downside is that it breaks existing iface files, so since we can't bootstrap yet so we have to bootstrap a cherry-picked branch and then checkout again to build with --freeze1. To avoid similar issues in the future, IfaceTyVarInfoItem serialises with a tag despite there being only one constructor for now. - - - - - d6f2523c by Joseph Fourment at 2025-03-14T17:33:40+00:00 dmd-anal: prefix unused variable with _ to avoid warning - - - - - 8b84d581 by Joseph Fourment at 2025-03-14T17:33:40+00:00 type: inline unfoldView in sORTKind_maybe - - - - - 068698a6 by Joseph Fourment at 2025-03-14T17:33:40+00:00 tidy: deal with type-lets - - - - - 34b71483 by Joseph Fourment at 2025-03-14T17:33:40+00:00 notes: add Note [Type and coercion lets] - - - - - e8e5411d by Joseph Fourment at 2025-03-14T17:33:40+00:00 notes: update Note [Comparing nullary type synonyms] to account for type variables While updating backlinks, I noticed the optimisation for type variables could be performed in more places. - - - - - 89bc871c by Joseph Fourment at 2025-03-14T17:33:40+00:00 simplifier: inline single-occurring type-lets - - - - - 42d560e9 by Joseph Fourment at 2025-03-14T17:33:40+00:00 cleanup: remove NOINLINE on tyVarOccInfo - - - - - 0b7a0ca0 by Simon Peyton Jones at 2025-03-14T17:33:40+00:00 Wibbles - - - - - f4897bcd by Simon Peyton Jones at 2025-03-14T17:33:40+00:00 Wibbles - - - - - 11bfb9d8 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 Progress - - - - - bc7ba8c1 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 Progress - - - - - b5d72390 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 More progress - - - - - be4633c6 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 Progress ...doesn't compile though - - - - - dcaaef3e by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 Mostly working now - - - - - c314fa19 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 Aggressively create type-lets - - - - - 97155906 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 more progress - - - - - 94db73a4 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 More progress - - - - - 212be850 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 Temp debug printing - - - - - d8c43f3f by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 Remove bogus assert - - - - - 5b210581 by Simon Peyton Jones at 2025-03-14T17:34:29+00:00 Fix anoher couple of bugs in SimpleOpt and exprIsTrivial - - - - - c0e5d9ef by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Improve zonking of foreign decls to avoid TcTyVars escaping - - - - - ea604125 by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Wibbles - - - - - 6b6166fc by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Some small wibbles - - - - - ffcc6bb5 by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Improvements - - - - - 7b249272 by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Rmmove trace - - - - - b6b69db5 by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Wibbles - - - - - 986b2608 by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Use lambda, not let, in WorkWrap Using type let did not work right with type lets and shadowing Requires Lint to be OK join points under beta redexes -- but it is! Needs better documentation - - - - - 3a4d620d by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Wibbles - - - - - 362041fa by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 More improvements - - - - - a7040f14 by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 More improvements * Less cloning in SpecConstr * Lint checks RULES for imported binders - - - - - c4a05bb4 by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Comments only - - - - - d22f974d by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Wibble - - - - - ee4f01fd by Simon Peyton Jones at 2025-03-14T17:34:30+00:00 Wibbles - - - - - 500 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload_ghc_libs.py - compiler/GHC.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Base.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FVs.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallArity.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Monad.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Ppr.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/Seq.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Ppr.hs-boot - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unfold.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/FastString/Env.hs - compiler/GHC/Data/FlatBag.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Graph/Directed.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Data/Graph/Inductive/Graph.hs - + compiler/GHC/Data/List.hs - compiler/GHC/Data/List/NonEmpty.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Pair.hs - compiler/GHC/Data/SmallArray.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Pmc/Utils.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - + compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/JS/Ppr.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Llvm/Types.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Plugins.hs - compiler/GHC/Prelude/Basic.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/EnforceEpt.hs - compiler/GHC/Stg/EnforceEpt/Rewrite.hs - compiler/GHC/Stg/EnforceEpt/Types.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.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/Solver/Rewrite.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Monad.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/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Env.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/Env.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/Graph.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/GHC/Unit/State.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Misc.hs - compiler/GHC/Utils/Outputable.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Trace.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - compiler/ghc.cabal.in - distrib/configure.ac.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/poly_kinds.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/wasm.rst - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - hadrian/bindist/Makefile - hadrian/cfg/system.config.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libffi-tarballs - libraries/base/src/Data/List/NonEmpty.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lib.hs - libraries/ghc-boot-th/GHC/Internal/TH/Lib/Map.hs → libraries/ghc-boot-th/GHC/Boot/TH/Lib/Map.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Lift.hs - libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs → libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot-th/GHC/Internal/TH/PprLib.hs → libraries/ghc-boot-th/GHC/Boot/TH/PprLib.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Quote.hs - + libraries/ghc-boot-th/GHC/Boot/TH/Syntax.hs - libraries/ghc-boot-th/ghc-boot-th.cabal.in - libraries/ghc-boot/GHC/Serialized.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc - libraries/ghc-internal/src/GHC/Internal/Pack.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/GHCi/TH/Binary.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Quote.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/template-haskell.cabal.in - m4/fp_settings.m4 - rts/HeapStackCheck.cmm - rts/Interpreter.c - rts/PrimOps.cmm - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/jsval.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - testsuite/driver/testlib.py - + testsuite/tests/cmm/opt/T25771.cmm - + testsuite/tests/cmm/opt/T25771.stderr - testsuite/tests/cmm/opt/all.T - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc.stdout - + testsuite/tests/cmm/should_run/JumpTableNoStackDeallocGen.hs - + testsuite/tests/cmm/should_run/JumpTableNoStackDealloc_cmm.cmm - testsuite/tests/cmm/should_run/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - + testsuite/tests/driver/self-recomp/Makefile - + testsuite/tests/driver/self-recomp/SelfRecomp01.hs - + testsuite/tests/driver/self-recomp/SelfRecomp02.hs - + testsuite/tests/driver/self-recomp/SelfRecomp03.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.hs - + testsuite/tests/driver/self-recomp/SelfRecomp04.stdout - + testsuite/tests/driver/self-recomp/all.T - testsuite/tests/ghc-api/Makefile - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghci/should_run/Makefile - + testsuite/tests/ghci/should_run/T25790.hs - + testsuite/tests/ghci/should_run/T25790.script - + testsuite/tests/ghci/should_run/TopEnvIface.hs - + testsuite/tests/ghci/should_run/TopEnvIface.stdout - + testsuite/tests/ghci/should_run/TopEnvIface2.hs - testsuite/tests/ghci/should_run/all.T - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/jsffigc.hs - testsuite/tests/jsffi/jsffigc.mjs - testsuite/tests/jsffi/jsffisleep.hs - testsuite/tests/jsffi/jsffisleep.stdout - testsuite/tests/jsffi/textconv.hs - testsuite/tests/jsffi/textconv.mjs - + testsuite/tests/llvm/should_run/T25730.hs - + testsuite/tests/llvm/should_run/T25730.stdout - + testsuite/tests/llvm/should_run/T25730C.c - testsuite/tests/llvm/should_run/all.T - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T20452.stderr - + testsuite/tests/parser/should_run/T25784.hs - + testsuite/tests/parser/should_run/T25784.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/perf/compiler/T25723.hs - + testsuite/tests/perf/compiler/T25723.stdout - testsuite/tests/perf/compiler/all.T - + testsuite/tests/perf/compiler/interpreter_steplocal.hs - + testsuite/tests/perf/compiler/interpreter_steplocal.script - + testsuite/tests/perf/compiler/interpreter_steplocal.stdout - + testsuite/tests/perf/should_run/ByteCodeAsm.hs - testsuite/tests/perf/should_run/all.T - + testsuite/tests/pmcheck/should_compile/T25749.hs - testsuite/tests/pmcheck/should_compile/all.T - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Test24533.stdout - testsuite/tests/rename/should_fail/T17594b.hs - testsuite/tests/rename/should_fail/T17594b.stderr - + testsuite/tests/rename/should_fail/T17594b_th.hs - + testsuite/tests/rename/should_fail/T17594b_th.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/rts/all.T - testsuite/tests/simplCore/should_compile/T24229a.stderr - testsuite/tests/simplCore/should_compile/T24229b.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/th/EmptyParStmt.hs - + testsuite/tests/th/EmptyParStmt.stderr - testsuite/tests/th/T24557a.stderr - testsuite/tests/th/T24557b.stderr - testsuite/tests/th/T24557c.stderr - testsuite/tests/th/T24557d.stderr - testsuite/tests/th/all.T - + testsuite/tests/typecheck/should_compile/T21003.hs - + testsuite/tests/typecheck/should_compile/T25744.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T17594c.stderr - testsuite/tests/typecheck/should_fail/T17594d.stderr - testsuite/tests/typecheck/should_fail/T17594g.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/check-exact/Main.hs - utils/check-exact/Transform.hs - utils/check-exact/Utils.hs - − utils/deriveConstants/Makefile - utils/dump-decls/Main.hs - − utils/genprimopcode/Makefile - − utils/ghc-pkg/Makefile - utils/haddock/doc/conf.py - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - − utils/hp2ps/Makefile - utils/hp2ps/Utilities.c - − utils/iserv/Makefile - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs - − utils/remote-iserv/Makefile - − utils/runghc/Makefile - − utils/unlit/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a8c7938c435a685eec712163cffde23696008dba...ee4f01fd578178a4688dd531e1422887fe25c0aa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a8c7938c435a685eec712163cffde23696008dba...ee4f01fd578178a4688dd531e1422887fe25c0aa You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/5a77369c/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 22:01:52 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Mar 2025 18:01:52 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] Another setting for tryRules Message-ID: <67d4a7506a0f2_2f40eaf81c4-393@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: 66d9037b by Simon Peyton Jones at 2025-03-14T22:01:05+00:00 Another setting for tryRules This time a) isClassOpId, or b) has active unfolding - - - - - 1 changed file: - compiler/GHC/Core/Opt/Simplify/Iteration.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -2261,7 +2261,10 @@ simplInId env var cont where env' = setSubstEnv env tvs cvs ids - DoneId out_id -> simplOutId env out_id cont + DoneId out_id -> simplOutId env' out_id cont' + where + cont' = trimJoinCont var (idJoinPointHood var) cont + env' = zapSubstEnv env -- See Note [zapSubstEnv] DoneEx e mb_join -> simplExprF env' e cont' where @@ -2269,7 +2272,7 @@ simplInId env var cont env' = zapSubstEnv env -- See Note [zapSubstEnv] --------------------------------------------------------- -simplOutId :: SimplEnv -> OutId -> SimplCont -> SimplM (SimplFloats, OutExpr) +simplOutId :: SimplEnvIS -> OutId -> SimplCont -> SimplM (SimplFloats, OutExpr) ---------- The runRW# rule ------ -- See Note [Simplification of runRW#] in GHC.CoreToSTG.Prep. @@ -2320,36 +2323,32 @@ simplOutId env fun cont call' = mkApps (Var fun) [mkTyArg rr', mkTyArg new_runrw_res_ty, arg'] ; rebuild env call' outer_cont } - +-- Normal case for (f e1 .. en) simplOutId env fun cont - = do { let cont1 = trimJoinCont fun (idJoinPointHood fun) cont - - -- Try rewrite rules - ; rule_base <- getSimplRules + = -- Try rewrite rules + do { rule_base <- getSimplRules ; let rules_for_me = getRules rule_base fun - out_args = contOutArgs env cont1 :: [OutExpr] - ; mb_match <- if not (isPrimOpId fun) - then tryRules zapped_env rules_for_me fun out_args + out_args = contOutArgs env cont :: [OutExpr] + ; mb_match <- if isClassOpId fun || activeUnfolding (seMode env) fun + then tryRules env rules_for_me fun out_args else return Nothing ; case mb_match of { - Just (rule_arity, rhs) -> simplExprF zapped_env rhs $ - dropContArgs rule_arity cont1 ; + Just (rule_arity, rhs) -> simplExprF env rhs $ + dropContArgs rule_arity cont ; Nothing -> - -- Try inlining + -- Try inlining do { logger <- getLogger - ; mb_inline <- tryInlining env logger fun cont1 + ; mb_inline <- tryInlining env logger fun cont ; case mb_inline of{ Just expr -> do { checkedTick (UnfoldingDone fun) - ; simplExprF zapped_env expr cont1 } ; + ; simplExprF env expr cont } ; Nothing -> - -- Neither worked, so just rebuild - do { let arg_info = mkArgInfo env fun rules_for_me cont1 - ; rebuildCall zapped_env arg_info cont1 + -- Neither worked, so just rebuild + do { let arg_info = mkArgInfo env fun rules_for_me cont + ; rebuildCall env arg_info cont } } } } } - where - zapped_env = zapSubstEnv env -- See Note [zapSubstEnv] --------------------------------------------------------- -- Dealing with a call site View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/66d9037b694906f793f6ba278bbc491815319390 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/66d9037b694906f793f6ba278bbc491815319390 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/aa006294/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 22:03:09 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Fri, 14 Mar 2025 18:03:09 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/cleanup-systools Message-ID: <67d4a79df0be6_2f40eaf83e028b@gitlab.mail> Ben Gamari pushed new branch wip/cleanup-systools at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/cleanup-systools You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/e7487a6e/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 14 22:06:58 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Fri, 14 Mar 2025 18:06:58 -0400 Subject: [Git][ghc/ghc] Deleted branch wip/backports-9.10 Message-ID: <67d4a882b649d_2f40eaf76ac5737@gitlab.mail> Ben Gamari deleted branch wip/backports-9.10 at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/a5f4efb9/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 14 22:07:15 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Fri, 14 Mar 2025 18:07:15 -0400 Subject: [Git][ghc/ghc][ghc-9.10] 12 commits: Bump text submodule to current `master` Message-ID: <67d4a893e87ec_2f40ea27ee94597f@gitlab.mail> Ben Gamari pushed to branch ghc-9.10 at Glasgow Haskell Compiler / GHC Commits: 877895d2 by Ben Gamari at 2025-03-03T14:31:03-05:00 Bump text submodule to current `master` This will be a revision of 2.1.2. - - - - - 457055f8 by Ben Gamari at 2025-03-04T17:02:00-05:00 Partially revert "testsuite: expand size testing infrastructure" This reverts the size testing infrastructure from commit a15b3383c95864eb1ca9df4f7065ef6f6fe84393 as it has broken the testsuite. - - - - - 400cfabe by Ben Gamari at 2025-03-05T10:05:55-05:00 Revert "hadrian: Bump directory bound to >=1.3.9" This reverts commit 15ca7b2c06f9727b7a8c5ca663c3b6779489daa6 as it breaks bootstrapping with 9.8 and 9.6, where `directory-1.3.9` is not shipped. - - - - - 3057ebc4 by Ben Gamari at 2025-03-05T10:53:57-05:00 gitlab-ci: Drop CentOS 7 binary distributions CentOS 7 is EoL and moreover we cannot even build images for it. See #25061. - - - - - 09d005eb by Ben Gamari at 2025-03-06T17:49:23-05:00 ghcup-metadata: Update for loss of CentOS 7 - - - - - b88f239e by Ben Gamari at 2025-03-07T10:31:13-05:00 mk-ghcup-metadata: Fix incorrect use of alpine() - - - - - ade5ae4f by Ben Gamari at 2025-03-10T12:08:07-04:00 mk-ghcup-metadata: Fix misnamed identifiers - - - - - 291860da by Matthew Pickering at 2025-03-11T09:35:06-04:00 Expand LLVM version matching regex for compability with bsd systems 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 (cherry picked from commit 77ce65a5e9b14c29f8f47bfbe452b1d6296c45e8) - - - - - cac7c45d by Ben Gamari at 2025-03-11T09:35:06-04:00 ghc-internal: Update CHANGELOG to reflect current version (cherry picked from commit 580fef7b1be1ea7247e9c7bc7ce0e3150b03fc36) - - - - - 04cf8504 by Ben Gamari at 2025-03-11T09:35:06-04:00 ghc-internal: Update prologue.txt to reflect package description (cherry picked from commit 391ecff5ced86e52089c5a5c46158a22755312a9) - - - - - 7348dfc2 by Matthew Pickering at 2025-03-11T09:35:06-04:00 Remove accidentally committed test.hs (cherry picked from commit e8724327d995a67d3eb066dfe4f9ee03e64dd6b5) - - - - - f2e63a12 by Matthew Pickering at 2025-03-11T09:35:06-04:00 libraries: Update os-string to 2.0.4 This updates the os-string submodule to 2.0.4 which removes the usage of `TemplateHaskell` pragma. (cherry picked from commit 37139b17f44cc489cc42cdac4e1b5b04b502d1b4) - - - - - 18 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/flake.lock - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - hadrian/cabal.project - hadrian/hadrian.cabal - hadrian/stack.yaml - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/prologue.txt - libraries/os-string - libraries/text - m4/find_llvm_prog.m4 - − test.hs - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/tests/perf/size/all.T Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1143,8 +1143,6 @@ ghcup-metadata-nightly: needs: - job: nightly-x86_64-linux-fedora33-release artifacts: false - - job: nightly-x86_64-linux-centos7-validate - artifacts: false - job: nightly-x86_64-linux-ubuntu20_04-validate artifacts: false - job: nightly-x86_64-linux-ubuntu18_04-validate ===================================== .gitlab/ci.sh ===================================== @@ -7,8 +7,7 @@ set -Eeuo pipefail # Configuration: -# N.B. You may want to also update the index-state in hadrian/cabal.project. -HACKAGE_INDEX_STATE="2025-02-03T15:14:19Z" +HACKAGE_INDEX_STATE="2024-05-13T15:04:38Z" MIN_HAPPY_VERSION="1.20" MAX_HAPPY_VERSION="1.21" # Exclusive upper bound MIN_ALEX_VERSION="3.2.6" ===================================== .gitlab/generate-ci/flake.lock ===================================== @@ -5,11 +5,11 @@ "systems": "systems" }, "locked": { - "lastModified": 1687709756, - "narHash": "sha256-Y5wKlQSkgEK2weWdOu4J3riRd+kV/VCgHsqLNTTWQ/0=", + "lastModified": 1731533236, + "narHash": "sha256-l0KFg5HjrsfsO/JpG+r7fRrqm12kzFHyUHqHCVpMMbI=", "owner": "numtide", "repo": "flake-utils", - "rev": "dbabf0ca0c0c4bce6ea5eaf65af5cb694d2082c7", + "rev": "11707dc2f618dd54ca8739b309ec4fc024de578b", "type": "github" }, "original": { @@ -20,12 +20,10 @@ }, "nixpkgs": { "locked": { - "lastModified": 1687886075, - "narHash": "sha256-PeayJDDDy+uw1Ats4moZnRdL1OFuZm1Tj+KiHlD67+o=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "a565059a348422af5af9026b5174dc5c0dcefdae", - "type": "github" + "lastModified": 0, + "narHash": "sha256-OnSAY7XDSx7CtDoqNh8jwVwh4xNL/2HaJxGjryLWzX8=", + "path": "/nix/store/lv9bmgm6v1wc3fiz00v29gi4rk13ja6l-source", + "type": "path" }, "original": { "id": "nixpkgs", ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -113,7 +113,6 @@ data LinuxDistro | Fedora38 | Ubuntu2004 | Ubuntu1804 - | Centos7 | Alpine312 | Alpine318 | AlpineWasm @@ -293,7 +292,6 @@ distroName Fedora33 = "fedora33" distroName Fedora38 = "fedora38" distroName Ubuntu1804 = "ubuntu18_04" distroName Ubuntu2004 = "ubuntu20_04" -distroName Centos7 = "centos7" distroName Alpine312 = "alpine3_12" distroName Alpine318 = "alpine3_18" distroName AlpineWasm = "alpine3_18-wasm" @@ -445,10 +443,6 @@ alpineVariables = mconcat distroVariables :: LinuxDistro -> Variables distroVariables Alpine312 = alpineVariables distroVariables Alpine318 = alpineVariables -distroVariables Centos7 = mconcat [ - "HADRIAN_ARGS" =: "--docs=no-sphinx" - , "BROKEN_TESTS" =: "T22012" -- due to #23979 - ] distroVariables Fedora33 = mconcat -- LLC/OPT do not work for some reason in our fedora images -- These tests fail with this error: T11649 T5681 T7571 T8131b @@ -984,7 +978,6 @@ job_groups = , disableValidate (standardBuilds Amd64 (Linux Ubuntu1804)) , disableValidate (standardBuilds Amd64 (Linux Ubuntu2004)) , disableValidate (standardBuilds Amd64 (Linux Rocky8)) - , disableValidate (standardBuildsWithConfig Amd64 (Linux Centos7) (splitSectionsBroken vanilla)) -- Fedora33 job is always built with perf so there's one job in the normal -- validate pipeline which is built with perf. , fastCI (standardBuildsWithConfig Amd64 (Linux Fedora33) releaseConfig) ===================================== .gitlab/jobs.yaml ===================================== @@ -1207,70 +1207,6 @@ "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-centos7-validate": { - "after_script": [ - ".gitlab/ci.sh save_cache", - ".gitlab/ci.sh save_test_output", - ".gitlab/ci.sh clean", - "cat ci_timings" - ], - "allow_failure": false, - "artifacts": { - "expire_in": "8 weeks", - "paths": [ - "ghc-x86_64-linux-centos7-validate.tar.xz", - "junit.xml", - "unexpected-test-output.tar.gz" - ], - "reports": { - "junit": "junit.xml" - }, - "when": "always" - }, - "cache": { - "key": "x86_64-linux-centos7-$CACHE_REV", - "paths": [ - "cabal-cache", - "toolchain" - ] - }, - "dependencies": [], - "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV", - "needs": [ - { - "artifacts": false, - "job": "hadrian-ghc-in-ghci" - } - ], - "rules": [ - { - "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)", - "when": "on_success" - } - ], - "script": [ - "sudo chown ghc:ghc -R .", - ".gitlab/ci.sh setup", - ".gitlab/ci.sh configure", - ".gitlab/ci.sh build_hadrian", - ".gitlab/ci.sh test_hadrian" - ], - "stage": "full-build", - "tags": [ - "x86_64-linux" - ], - "variables": { - "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-validate", - "BROKEN_TESTS": "T22012", - "BUILD_FLAVOUR": "validate", - "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "HADRIAN_ARGS": "--docs=no-sphinx", - "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-centos7-validate", - "XZ_OPT": "-9" - } - }, "nightly-x86_64-linux-deb10-int_native-validate": { "after_script": [ ".gitlab/ci.sh save_cache", @@ -3433,71 +3369,6 @@ "XZ_OPT": "-9" } }, - "release-x86_64-linux-centos7-release+no_split_sections": { - "after_script": [ - ".gitlab/ci.sh save_cache", - ".gitlab/ci.sh save_test_output", - ".gitlab/ci.sh clean", - "cat ci_timings" - ], - "allow_failure": false, - "artifacts": { - "expire_in": "1 year", - "paths": [ - "ghc-x86_64-linux-centos7-release+no_split_sections.tar.xz", - "junit.xml", - "unexpected-test-output.tar.gz" - ], - "reports": { - "junit": "junit.xml" - }, - "when": "always" - }, - "cache": { - "key": "x86_64-linux-centos7-$CACHE_REV", - "paths": [ - "cabal-cache", - "toolchain" - ] - }, - "dependencies": [], - "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV", - "needs": [ - { - "artifacts": false, - "job": "hadrian-ghc-in-ghci" - } - ], - "rules": [ - { - "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)", - "when": "on_success" - } - ], - "script": [ - "sudo chown ghc:ghc -R .", - ".gitlab/ci.sh setup", - ".gitlab/ci.sh configure", - ".gitlab/ci.sh build_hadrian", - ".gitlab/ci.sh test_hadrian" - ], - "stage": "full-build", - "tags": [ - "x86_64-linux" - ], - "variables": { - "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-release+no_split_sections", - "BROKEN_TESTS": "T22012", - "BUILD_FLAVOUR": "release+no_split_sections", - "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "HADRIAN_ARGS": "--hash-unit-ids --docs=no-sphinx", - "IGNORE_PERF_FAILURES": "all", - "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-centos7-release+no_split_sections", - "XZ_OPT": "-9" - } - }, "release-x86_64-linux-deb10-release": { "after_script": [ ".gitlab/ci.sh save_cache", ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -96,9 +96,6 @@ def darwin(arch): windowsArtifact = PlatformSpec ( 'x86_64-windows' , 'ghc-{version}-x86_64-unknown-mingw32' ) -def centos(n, arch='x86_64'): - return linux_platform(arch, "x86_64-linux-centos{n}".format(n=n)) - def fedora(n, arch='x86_64'): return linux_platform(arch, "x86_64-linux-fedora{n}".format(n=n)) @@ -186,7 +183,7 @@ def mk_from_platform(release_mode, pipeline_type, platform): , f"ghc{{version}}-{platform.name}") # Generate the new metadata for a specific GHC mode etc -def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): +def mk_new_yaml(release_mode, version, date, pipeline_type, job_map) -> object: def mk(platform): eprint("\n=== " + platform.name + " " + ('=' * (75 - len(platform.name)))) return mk_one_metadata(release_mode, version, job_map, mk_from_platform(release_mode, pipeline_type, platform)) @@ -195,14 +192,13 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): ubuntu1804 = mk(ubuntu("18_04")) ubuntu2004 = mk(ubuntu("20_04")) rocky8 = mk(rocky("8")) - centos7 = mk(centos(7)) fedora33 = mk(fedora(33)) darwin_x86 = mk(darwin("x86_64")) darwin_arm64 = mk(darwin("aarch64")) windows = mk(windowsArtifact) alpine3_12 = mk(alpine("3_12")) alpine3_18 = mk(alpine("3_18")) - alpine3_18_arm64 = mk(alpine("3_18"), arch='aarch64') + alpine3_18_arm64 = mk(alpine("3_18", arch='aarch64')) deb9 = mk(debian(9, "x86_64")) deb10 = mk(debian(10, "x86_64")) deb11 = mk(debian(11, "x86_64")) @@ -228,18 +224,15 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): , "Linux_Mint" : { "< 20": ubuntu1804 , ">= 20": ubuntu2004 , "unknown_versioning": ubuntu2004 } - , "Linux_CentOS" : { "( >= 7 && < 8 )" : centos7 - , "unknown_versioning" : centos7 } - , "Linux_Fedora" : { ">= 33": fedora33 - , "unknown_versioning": centos7 } - , "Linux_RedHat" : { "< 9": centos7 + , "Linux_Fedora" : { ">= 33": fedora33 } + , "Linux_RedHat" : { "< 9": rocky8 , ">= 9": fedora33 , "unknown_versioning": fedora33 } , "Linux_UnknownLinux" : { "unknown_versioning": rocky8 } , "Darwin" : { "unknown_versioning" : darwin_x86 } , "Windows" : { "unknown_versioning" : windows } - , "Linux_Alpine" : { "( >= 3.12 && < 3.18 )": alpine_3_12 - , ">= 3.18": alpine_3_18 + , "Linux_Alpine" : { "( >= 3.12 && < 3.18 )": alpine3_12 + , ">= 3.18": alpine3_18 , "unknown_versioning": alpine3_12 } } ===================================== hadrian/cabal.project ===================================== @@ -3,7 +3,7 @@ packages: ./ ../libraries/ghc-platform/ -- This essentially freezes the build plan for hadrian --- It would be wise to keep this up to date with the state set in .gitlab/ci.sh. +-- It would be wise to keep this up to date with the state set in ci.sh index-state: 2025-02-03T15:14:19Z -- unordered-containers-0.2.20-r1 requires template-haskell < 2.22 ===================================== hadrian/hadrian.cabal ===================================== @@ -156,10 +156,7 @@ executable hadrian , base >= 4.11 && < 5 , bytestring >= 0.10 && < 0.13 , containers >= 0.5 && < 0.8 - - -- N.B. directory >=1.3.9 as earlier versions are - -- afflicted by #24382. - , directory >= 1.3.9.0 && < 1.4 + , directory >= 1.3.1.0 && < 1.4 , extra >= 1.4.7 , filepath , time ===================================== hadrian/stack.yaml ===================================== @@ -21,10 +21,3 @@ nix: extra-deps: - Cabal-3.10.1.0 - Cabal-syntax-3.10.1.0 - -# needed due to Hadrian's lower bound on directory - - directory-1.3.9.0 - - file-io-0.1.4 - - filepath-1.4.300.2 - - process-1.6.25.0 - - unix-2.8.5.1 \ No newline at end of file ===================================== libraries/ghc-internal/CHANGELOG.md ===================================== @@ -1,5 +1,5 @@ # Revision history for `ghc-internal` -## 0.1.0.0 -- YYYY-mm-dd +## 9.1001.0 -- 2024-05-01 -* First version. Released on an unsuspecting world. +* Package created containing implementation moved from `base`. ===================================== libraries/ghc-internal/prologue.txt ===================================== @@ -1,3 +1,2 @@ -This package contains the @Prelude@ and its support libraries, and a large -collection of useful libraries ranging from data structures to parsing -combinators and debugging utilities. +This package contains the implementation of GHC's standard libraries and is +not intended for use by end-users. ===================================== libraries/os-string ===================================== @@ -1 +1 @@ -Subproject commit e1dd3bcfab56a6616c73ee9220de425d55545bc8 +Subproject commit 6d31aafde2f7b8c3050ffee7dd9f658225cfd1a4 ===================================== libraries/text ===================================== @@ -1 +1 @@ -Subproject commit 991b7e34efacc44a8a8b60e28ae737c45bc5942e +Subproject commit a721bf58a3b9591473ceae938ac916cb9b0de2c0 ===================================== m4/find_llvm_prog.m4 ===================================== @@ -14,7 +14,7 @@ AC_DEFUN([FIND_LLVM_PROG],[ PROG_VERSION_CANDIDATES=$(for llvmVersion in `seq $(($4-1)) -1 $3`; do echo "$2-$llvmVersion $2-$llvmVersion.0 $2$llvmVersion"; done) AC_CHECK_TOOLS([$1], [$PROG_VERSION_CANDIDATES $2], []) AS_IF([test x"$$1" != x],[ - PROG_VERSION=`$$1 --version | sed -n -e 's/.*version \(\([[0-9]]\+\.\)\+[[0-9]]\+\).*/\1/gp'` + PROG_VERSION=`$$1 --version | sed -n -e 's/.*version \(\([[0-9]][[0-9]]*\.\)\([[0-9]][[0-9]]*\.\)*[[0-9]][[0-9]]*\).*/\1/gp'` AS_IF([test x"$PROG_VERSION" = x], [AC_MSG_RESULT(no) $1="" ===================================== test.hs deleted ===================================== @@ -1,14 +0,0 @@ -import Data.Char -import Data.Foldable --- | Just like 'GHC.ResponseFile.escapeArg', but it is not exposed from base. -escapeArg :: String -> String -escapeArg = reverse . foldl' escape [] - -escape :: String -> Char -> String -escape cs c - | isSpace c - || '\\' == c - || '\'' == c - || '"' == c = c:'\\':cs -- n.b., our caller must reverse the result - | otherwise = c:cs - ===================================== testsuite/driver/testglobals.py ===================================== @@ -223,10 +223,6 @@ class TestConfig: # I have no idea what this does self.package_conf_cache_file = None # type: Optional[Path] - # the libdir for the test compiler. Set by hadrian, see - # Setting.Builders.RunTest - self.libdir = '' - # The extra hadrian dependencies we need for all configured tests self.hadrian_deps = set() # type: Set[str] ===================================== testsuite/driver/testlib.py ===================================== @@ -628,24 +628,15 @@ def collect_size ( deviation, path ): def get_dir_size(path): total = 0 - try: - with os.scandir(path) as it: - for entry in it: - if entry.is_file(): - total += entry.stat().st_size - elif entry.is_dir(): - total += get_dir_size(entry.path) - return total - except FileNotFoundError: - print("Exception: Could not find: " + path) + with os.scandir(path) as it: + for entry in it: + if entry.is_file(): + total += entry.stat().st_size + elif entry.is_dir(): + total += get_dir_size(entry.path) + return total def collect_size_dir ( deviation, path ): - - ## os.path.join joins the path with slashes (not backslashes) on windows - ## CI...for some reason, so we manually detect it here - sep = r"/" - if on_windows(): - sep = r"\\" return collect_generic_stat ( 'size', deviation, lambda way: get_dir_size(path) ) # Read a number from a specific file @@ -662,92 +653,7 @@ def collect_generic_stats ( metric_info ): return _collect_generic_stat(name, opts, metric_info) return f -# wrap the call to collect_size_dir with path_from_ghcPkg in a function. Python -# is call-by-value so if we placed the call in an all.T file then the python -# interpreter would evaluate the call to path_from_ghcPkg -def collect_size_ghc_pkg (deviation, library): - return collect_size_dir(deviation, path_from_ghcPkg(library, "library-dirs")) - -# same for collect_size and find_so -def collect_object_size (deviation, library, use_non_inplace=False): - if use_non_inplace: - return collect_size(deviation, find_non_inplace_so(library)) - else: - return collect_size(deviation, find_so(library)) - -def path_from_ghcPkg (library, field): - """Find the field as a path for a library via a call to ghc-pkg. This is a - testsuite wrapper around a call to ghc-pkg field {library} {field}. - """ - - ### example output from ghc-pkg: - ### $ ./ghc-pkg field Cabal library-dirs - ### library-dirs: /home/doyougnu/programming/haskell/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240424/Cabal-3.11.0.0-inplace - ### so we split the string and drop the 'library-dirs' - ghcPkgCmd = fr"{config.ghc_pkg} field {library} {field}" - - try: - result = subprocess.run(ghcPkgCmd, capture_output=True, shell=True) - - # check_returncode throws an exception if the return code is not 0. - result.check_returncode() - - # if we get here then the call worked and we have the path we split by - # whitespace and then return the path which becomes the second element - # in the array - return re.split(r'\s+', result.stdout.decode("utf-8"))[1] - except Exception as e: - message = f""" - Attempt to find {field} of {library} using ghc-pkg failed. - ghc-pkg path: {config.ghc_pkg} - error" {e} - """ - print(message) - - -def _find_so(lib, directory, in_place): - """Find a shared object file (.so) for lib in directory. We deliberately - keep the regex simple, just removing the ghc version and project version. - Example: - - _find_so("Cabal-syntax-3.11.0.0", path-from-ghc-pkg, True) ==> - /builds/ghc/ghc/_build/install/lib/ghc-9.11.20240410/lib/x86_64-linux-ghc-9.11.20240410/libHSCabal-syntax-3.11.0.0-inplace-ghc9.11.20240410.so - """ - - # produce the suffix for the CI operating system - suffix = "so" - if config.os == "mingw32": - suffix = "dll" - elif config.os == "darwin": - suffix = "dylib" - - # Most artfacts are of the form foo-inplace, except for the rts. - if in_place: - to_match = r'libHS{}-\d+(\.\d+)+-inplace-\S+\.' + suffix - else: - to_match = r'libHS{}-\d+(\.\d+)+\S+\.' + suffix - - matches = [] - # wrap this in some exception handling, hadrian test will error out because - # these files don't exist yet, so we pass when this occurs - try: - for f in os.listdir(directory): - if f.endswith(suffix): - pattern = re.compile(to_match.format(re.escape(lib))) - match = re.match(pattern, f) - if match: - matches.append(match.group()) - return os.path.join(directory, matches[0]) - except: - failBecause('Could not find shared object file: ' + lib) - -def find_so(lib): - return _find_so(lib,path_from_ghcPkg(lib, "dynamic-library-dirs"),True) - -def find_non_inplace_so(lib): - return _find_so(lib,path_from_ghcPkg(lib, "dynamic-library-dirs"),False) - -# Define a generic stat test, which computes the statistic by calling the function +# Define the a generic stat test, which computes the statistic by calling the function # given as the third argument. def collect_generic_stat ( metric, deviation, get_stat ): return collect_generic_stats ( { metric: { 'deviation': deviation, 'current': get_stat } } ) ===================================== testsuite/tests/perf/size/all.T ===================================== @@ -3,80 +3,4 @@ test('size_hello_obj', [collect_size(5, 'size_hello_obj.o')], compile, ['']) test('size_hello_artifact', [collect_size(5, 'size_hello_artifact' + exe_extension())], compile_artifact, ['']) -size_acceptance_threshold = 100 - -test('array_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'array')] , static_stats , [] ) -test('base_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'base')] , static_stats , [] ) -test('binary_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'binary')] , static_stats , [] ) -test('bytestring_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'bytestring')] , static_stats , [] ) -test('cabal_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'Cabal')] , static_stats , [] ) -test('cabal_syntax_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'Cabal-syntax')] , static_stats , [] ) -test('containers_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'containers')] , static_stats , [] ) -test('deepseq_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'deepseq')] , static_stats , [] ) -test('directory_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'directory')] , static_stats , [] ) -test('exceptions_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'exceptions')] , static_stats , [] ) -test('ghc_bignum_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-bignum')] , static_stats , [] ) -test('ghc_boot_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-boot')] , static_stats , [] ) -test('ghc_boot_th_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-boot-th')] , static_stats , [] ) -test('ghc_compact_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-compact')] , static_stats , [] ) -test('ghc_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc')] , static_stats , [] ) -test('ghc_experimental_dir',[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-experimental')], static_stats , [] ) -test('ghc_heap_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-heap')] , static_stats , [] ) -test('ghc_internal_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-internal')] , static_stats , [] ) -test('ghc_platform_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-platform')] , static_stats , [] ) -test('ghc_prim_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-prim')] , static_stats , [] ) -test('ghc_toolchain_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'ghc-toolchain')] , static_stats , [] ) -test('haskeline_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'haskeline')] , static_stats , [] ) -test('hpc_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'hpc')] , static_stats , [] ) -test('integer_gmp_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'integer-gmp')] , static_stats , [] ) -test('mtl_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'mtl')] , static_stats , [] ) -test('os_string_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'os-string')] , static_stats , [] ) -test('parsec_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'parsec')] , static_stats , [] ) -test('pretty_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'pretty')] , static_stats , [] ) -test('process_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'process')] , static_stats , [] ) -test('time_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'time')] , static_stats , [] ) -test('xhtml_dir' ,[collect_size_ghc_pkg(size_acceptance_threshold , 'xhtml')] , static_stats , [] ) - -# size of the entire libdir -test('libdir' ,[collect_size_dir(10, config.libdir)] , static_stats , [] ) - -# skip these on windows -test('unix_dir' ,[windows_skip, collect_size_ghc_pkg(size_acceptance_threshold, 'unix')] , static_stats, [] ) -test('terminfo_dir' ,[windows_skip, js_skip, collect_size_ghc_pkg(size_acceptance_threshold, 'terminfo')], static_stats, [] ) - -# skip the shared object file tests on windows -test('array_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "array")] , static_stats, [] ) -test('base_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "base")] , static_stats, [] ) -test('binary_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "binary")] , static_stats, [] ) -test('bytestring_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "bytestring")] , static_stats, [] ) -test('cabal_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "Cabal")] , static_stats, [] ) -test('cabal_syntax_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "Cabal-syntax")] , static_stats, [] ) -test('containers_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "containers")] , static_stats, [] ) -test('deepseq_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "deepseq")] , static_stats, [] ) -test('directory_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "directory")] , static_stats, [] ) -test('exceptions_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "exceptions")] , static_stats, [] ) -test('filepath_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "filepath")] , static_stats, [] ) -test('ghc_bignum_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-bignum")] , static_stats, [] ) -test('ghc_boot_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-boot")] , static_stats, [] ) -test('ghc_boot_th_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-boot-th")] , static_stats, [] ) -test('ghc_experimental_so',[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-experimental")] , static_stats, [] ) -test('ghc_heap_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-heap")] , static_stats, [] ) -test('ghc_platform_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-platform")] , static_stats, [] ) -test('ghc_prim_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-prim")] , static_stats, [] ) -test('ghc_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc")] , static_stats, [] ) -test('ghc_toolchain_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghc-toolchain")] , static_stats, [] ) -test('ghci_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "ghci")] , static_stats, [] ) -test('haskeline_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "haskeline")] , static_stats, [] ) -test('hpc_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "hpc")] , static_stats, [] ) -test('mtl_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "mtl")] , static_stats, [] ) -test('os_string_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "os-string")] , static_stats, [] ) -test('parsec_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "parsec")] , static_stats, [] ) -test('process_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "process")] , static_stats, [] ) -# Disabled as extremely unstable -#test('rts_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "rts", True)] , static_stats, [] ) -test('template_haskell_so',[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "template-haskell")] , static_stats, [] ) -test('terminfo_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "terminfo")] , static_stats, [] ) -test('text_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "text")] , static_stats, [] ) -test('time_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "time")] , static_stats, [] ) -test('transformers_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "transformers")] , static_stats, [] ) -test('xhtml_so' ,[req_dynamic_ghc, js_skip, windows_skip, collect_object_size(size_acceptance_threshold, "xhtml")] , static_stats, [] ) +test('libdir',[collect_size_dir(10, config.libdir)], static_stats, [] ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9968ac074d4d55f8611e241a089dea5b4ce9303b...f2e63a12313687e3aaeb052aa80ee8d7817052ec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9968ac074d4d55f8611e241a089dea5b4ce9303b...f2e63a12313687e3aaeb052aa80ee8d7817052ec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/f04bf3b4/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 22:09:18 2025 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Fri, 14 Mar 2025 18:09:18 -0400 Subject: [Git][ghc/ghc] Pushed new tag ghc-9.12.2-release Message-ID: <67d4a90ebed3_2f40ea3aebe888d@gitlab.mail> Ben Gamari pushed new tag ghc-9.12.2-release at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/ghc-9.12.2-release You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/86d26fbf/attachment.html> From gitlab at gitlab.haskell.org Fri Mar 14 22:17:15 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Mar 2025 18:17:15 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Don't report used duplicate record fields as unused Message-ID: <67d4aaea6cbfb_2f40ea53cf64116ad@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 0cb1db92 by sheaf at 2025-03-14T13:11:44-04:00 Don't report used duplicate record fields as unused This commit fixes the bug reported in #24035 in which the import of a duplicate record field could be erroneously reported as unused. The issue is that an import of the form "import M (fld)" can import several different 'Name's, and we should only report an error if ALL of those 'Name's are unused, not if ANY are. Note [Reporting unused imported duplicate record fields] in GHC.Rename.Names explains the solution to this problem. Fixes #24035 - - - - - f1830d74 by Matthew Pickering at 2025-03-14T13:12:21-04:00 binary: Directly copy ShortByteString to buffer rather than go via ByteString This avoids allocating an intermediate bytestring. I just noticed on a profile that `putFS` was allocating, and it seemed strange to me why since it should just copy the contents of the FastString into the already allocated buffer. It turned out we were going indirectly via a ByteString. Fixes #25861 - - - - - b5a4abc3 by Matthew Pickering at 2025-03-14T18:16:25-04:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore ------------------------- - - - - - a3794d93 by Ben Gamari at 2025-03-14T18:16:25-04:00 configure: Fix incorrect SettingsLlvmAsFlags value Previously this was set to `LlvmAsCmd` rather than `LlvmAsFlags`, resulting in #25856. - - - - - 29 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - ghc/Main.hs - m4/fp_settings.m4 - testsuite/tests/deriving/should_compile/T17324.stderr - testsuite/tests/module/T11970A.stderr - testsuite/tests/module/mod176.stderr - testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr - testsuite/tests/rename/should_compile/T14881.stderr - + testsuite/tests/rename/should_compile/T24035.hs - + testsuite/tests/rename/should_compile/T24035_aux.hs - + testsuite/tests/rename/should_compile/T24035b.hs - + testsuite/tests/rename/should_compile/T24035b.stderr - testsuite/tests/rename/should_compile/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -100,29 +100,37 @@ module GHC ( findGlobalAnns, mkNamePprCtxForModule, ModIface, - ModIface_( - mi_module, - mi_sig_of, - mi_hsc_src, - mi_hi_bytes, - mi_deps, - mi_exports, - mi_fixities, - mi_warns, - mi_anns, - mi_insts, - mi_fam_insts, - mi_rules, - mi_decls, - mi_extra_decls, - mi_top_env, - mi_trust, - mi_trust_pkg, - mi_complete_matches, - mi_docs, - mi_final_exts, - mi_ext_fields - ), + ModIface_( mi_mod_info + , mi_module + , mi_sig_of + , mi_hsc_src + , mi_iface_hash + , mi_deps + , mi_public + , mi_exports + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_defaults + , mi_simplified_core + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_abi_hashes + , mi_ext_fields + , mi_hi_bytes + , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn + ), pattern ModIface, SafeHaskellMode(..), ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -844,7 +844,7 @@ hscRecompStatus case recomp_if_result of OutOfDateItem reason mb_checked_iface -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ fmap (mi_iface_hash . mi_final_exts) mb_checked_iface + return $ HscRecompNeeded $ fmap mi_iface_hash mb_checked_iface UpToDateItem checked_iface -> do let lcl_dflags = ms_hspp_opts mod_summary if | not (backendGeneratesCode (backend lcl_dflags)) -> do @@ -862,7 +862,7 @@ hscRecompStatus , xopt LangExt.TemplateHaskell lcl_dflags -> do msg $ needsRecompileBecause THWithJS - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface | otherwise -> do -- Do need linkable @@ -918,7 +918,7 @@ hscRecompStatus return $ HscUpToDate checked_iface $ linkable OutOfDateItem reason _ -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface -- | Check that the .o files produced by compilation are already up-to-date -- or not. @@ -968,10 +968,8 @@ loadByteCode iface mod_sum = do let this_mod = ms_mod mod_sum if_date = fromJust $ ms_iface_date mod_sum - case mi_extra_decls iface of - Just extra_decls -> do - let fi = WholeCoreBindings extra_decls this_mod (ms_location mod_sum) - (mi_foreign iface) + case iface_core_bindings iface (ms_location mod_sum) of + Just fi -> do return (UpToDateItem (Linkable if_date this_mod (NE.singleton (CoreBindings fi)))) _ -> return $ outOfDateItemBecause MissingBytecode Nothing @@ -1019,15 +1017,15 @@ compile_for_interpreter hsc_env use = -- | Assemble 'WholeCoreBindings' if the interface contains Core bindings. iface_core_bindings :: ModIface -> ModLocation -> Maybe WholeCoreBindings iface_core_bindings iface wcb_mod_location = - mi_extra_decls <&> \ wcb_bindings -> + mi_simplified_core <&> \(IfaceSimplifiedCore bindings foreign') -> WholeCoreBindings { - wcb_bindings, + wcb_bindings = bindings, wcb_module = mi_module, wcb_mod_location, - wcb_foreign = mi_foreign + wcb_foreign = foreign' } where - ModIface {mi_module, mi_extra_decls, mi_foreign} = iface + ModIface {mi_module, mi_simplified_core} = iface -- | Return an 'IO' that hydrates Core bindings and compiles them to bytecode if -- the interface contains any, using the supplied type env for typechecking. @@ -1376,7 +1374,7 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do -- dynamic interfaces. Hopefully both the dynamic and the non-dynamic -- interfaces stay in sync... -- - let change = old_iface /= Just (mi_iface_hash (mi_final_exts iface)) + let change = old_iface /= Just (mi_iface_hash iface) let dt = dynamicTooState dflags ===================================== compiler/GHC/Hs/ImpExp.hs ===================================== @@ -259,7 +259,6 @@ ieNames (IEVar _ (L _ n) _) = [ieWrappedName n] ieNames (IEThingAbs _ (L _ n) _) = [ieWrappedName n] ieNames (IEThingAll _ (L _ n) _) = [ieWrappedName n] ieNames (IEThingWith _ (L _ n) _ ns _) = ieWrappedName n : map (ieWrappedName . unLoc) ns --- NB the above case does not include names of field selectors ieNames (IEModuleContents {}) = [] ieNames (IEGroup {}) = [] ieNames (IEDoc {}) = [] ===================================== compiler/GHC/HsToCore/Usage.hs ===================================== @@ -185,7 +185,7 @@ mkObjectUsage pit plugins fc hug th_links_needed th_pkgs_needed = do case miface of Nothing -> pprPanic "mkObjectUsage" (ppr m) Just iface -> - return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash (mi_final_exts iface)) + return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash iface) librarySpecToUsage :: LibrarySpec -> IO [Usage] librarySpecToUsage (Objects os) = traverse (fing Nothing) os @@ -278,10 +278,10 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names usg_entities = Map.toList ent_hashs, usg_safe = imp_safe } where - finsts_mod = mi_finsts (mi_final_exts iface) - hash_env = mi_hash_fn (mi_final_exts iface) - mod_hash = mi_mod_hash (mi_final_exts iface) - export_hash | depend_on_exports = Just (mi_exp_hash (mi_final_exts iface)) + finsts_mod = mi_finsts iface + hash_env = mi_hash_fn iface + mod_hash = mi_mod_hash iface + export_hash | depend_on_exports = Just (mi_exp_hash iface) | otherwise = Nothing by_is_safe (ImportedByUser imv) = imv_is_safe imv ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -41,34 +41,28 @@ data IfaceDynFlags = IfaceDynFlags , ifaceCallerCCFilters :: [CallerCcFilter] } -pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc -pprIfaceDynFlags (f, mflags) = - vcat $ - [ text "fingerprint:" <+> (ppr f) - ] - ++ case mflags of - Nothing -> [missingExtraFlagInfo] - Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> - [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) - , text "safe-mode:" <+> ppr a2 - , text "lang:" <+> ppr a3 - , text "exts:" <+> ppr a4 - , text "cpp-options:" - , nest 2 $ ppr a5 - , text "js-options:" - , nest 2 $ ppr a6 - , text "cmm-options:" - , nest 2 $ ppr a7 - , text "paths:" <+> hcat (map text a8) - , text "prof:" <+> ppr a9 - , text "ticky:" - , nest 2 $ vcat (map ppr a10) - , text "codegen:" - , nest 2 $ vcat (map ppr a11) - , text "fat-iface:" <+> ppr a12 - , text "debug-level:" <+> ppr a13 - , text "caller-cc-filters:" <+> ppr a14 - ] +pprIfaceDynFlags :: IfaceDynFlags -> SDoc +pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + vcat [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] missingExtraFlagInfo :: SDoc missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,7 +59,6 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields -import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -74,7 +73,6 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Logger -import GHC.Utils.Fingerprint( Fingerprint ) import GHC.Settings.Constants @@ -644,7 +642,7 @@ loadInterface doc_str mod from & set_mi_fam_insts (panic "No mi_fam_insts in PIT") & set_mi_rules (panic "No mi_rules in PIT") & set_mi_anns (panic "No mi_anns in PIT") - & set_mi_extra_decls (panic "No mi_extra_decls in PIT") + & set_mi_simplified_core (panic "No mi_simplified_core in PIT") bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1083,7 +1081,7 @@ load_dynamic_too :: Logger -> NameCache -> UnitState -> DynFlags load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do read_file logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case Succeeded (dynIface, _) - | mi_mod_hash (mi_final_exts iface) == mi_mod_hash (mi_final_exts dynIface) + | mi_mod_hash iface == mi_mod_hash dynIface -> return (Succeeded ()) | otherwise -> do return $ (Failed $ DynamicHashMismatchError wanted_mod loc) @@ -1174,11 +1172,10 @@ ghcPrimIface & set_mi_exports ghcPrimExports & set_mi_decls [] & set_mi_fixities ghcPrimFixities - & set_mi_final_exts ((mi_final_exts empty_iface) - { mi_fix_fn = mkIfaceFixCache ghcPrimFixities - , mi_decl_warn_fn = mkIfaceDeclWarnCache ghcPrimWarns - , mi_export_warn_fn = mkIfaceExportWarnCache ghcPrimWarns - }) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) + & set_mi_decl_warn_fn (mkIfaceDeclWarnCache ghcPrimWarns) + & set_mi_export_warn_fn (mkIfaceExportWarnCache ghcPrimWarns) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] in GHC.Builtin.Utils & set_mi_warns (toIfaceWarnings ghcPrimWarns) -- See Note [GHC.Prim Deprecations] in GHC.Builtin.Utils @@ -1263,21 +1260,14 @@ pprModIface unit_state iface = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") - <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) - <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) + <+> (if mi_orphan iface then text "[orphan module]" else Outputable.empty) + <+> (if mi_finsts iface then text "[family instance module]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) - , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) - , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat - [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) - , nest 2 (text "opt_hash:" <+> ppr opt_hash) - , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) - , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) - , vcat (map pprUsage usages) - ] - , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) + , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash iface)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash iface)) + , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash iface)) + , withSelfRecomp iface empty ppr + , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "where") , text "exports:" @@ -1288,10 +1278,14 @@ pprModIface unit_state iface , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] - , case mi_extra_decls iface of + , case mi_simplified_core iface of Nothing -> empty - Just eds -> text "extra decls:" - $$ nest 2 (vcat ([ppr bs | bs <- eds])) + Just (IfaceSimplifiedCore eds fs) -> + vcat [ text "extra decls:" + $$ nest 2 (vcat ([ppr bs | bs <- eds])) + , text "foreign stubs:" + $$ nest 2 (ppr fs) + ] , vcat (map ppr (mi_insts iface)) , vcat (map ppr (mi_fam_insts iface)) , vcat (map ppr (mi_rules iface)) @@ -1303,7 +1297,6 @@ pprModIface unit_state iface , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where - exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" @@ -1329,35 +1322,6 @@ pprExport avail@(AvailTC n _) = pp_export [] = Outputable.empty pp_export names = braces (hsep (map ppr names)) -pprUsage :: Usage -> SDoc -pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } - = pprUsageImport mod hash safe -pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name - , usg_mod_hash = hash, usg_safe = safe - , usg_exports = exports, usg_entities = entities } - = pprUsageImport (mkModule unit_id mod_name) hash safe $$ - nest 2 ( - maybe Outputable.empty (\v -> text "exports: " <> ppr v) exports $$ - vcat [ ppr n <+> ppr v | (n,v) <- entities ] - ) -pprUsage usage at UsageFile{} - = hsep [text "addDependentFile", - doubleQuotes (ftext (usg_file_path usage)), - ppr (usg_file_hash usage)] -pprUsage usage at UsageMergedRequirement{} - = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] -pprUsage usage at UsageHomeModuleInterface{} - = hsep [text "implementation", ppr (usg_mod_name usage) - , ppr (usg_unit_id usage) - , ppr (usg_iface_hash usage)] - -pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc -pprUsageImport mod hash safe - = hsep [ text "import", pp_safe, ppr mod - , ppr hash ] - where - pp_safe | safe = text "safe" - | otherwise = text " -/ " pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -88,13 +88,13 @@ import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModSummary import GHC.Unit.Module.Deps -import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign, emptyIfaceForeign) import Data.Function import Data.List ( sortBy ) import Data.Ord import Data.IORef - +import Data.Traversable {- ************************************************************************ @@ -143,11 +143,13 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos stubs foreign_files = updateDecl (mi_decls partial_iface) mb_stg_infos mb_cmm_infos -- See Note [Foreign stubs and TH bytecode linking] - foreign_ <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + mi_simplified_core <- for (mi_simplified_core partial_iface) $ \simpl_core -> do + fs <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + return $ (simpl_core { mi_sc_foreign = fs }) full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env $ set_mi_foreign foreign_ $ set_mi_decls decls partial_iface + addFingerprints hsc_env $ set_mi_simplified_core mi_simplified_core $ set_mi_decls decls partial_iface -- Debug printing let unit_state = hsc_units hsc_env @@ -289,7 +291,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode - -> Maybe ModIfaceSelfRecomp + -> Maybe IfaceSelfRecomp -> Maybe Docs -> ModDetails -> PartialModIface @@ -316,8 +318,8 @@ mkIface_ hsc_env entities = typeEnvElts type_env show_linear_types = xopt LangExt.LinearTypes (hsc_dflags hsc_env) - extra_decls = if gopt Opt_WriteIfSimplifiedCore dflags then Just [ toIfaceTopBind b | b <- core_prog ] - else Nothing + simplified_core = if gopt Opt_WriteIfSimplifiedCore dflags then Just (IfaceSimplifiedCore [ toIfaceTopBind b | b <- core_prog ] emptyIfaceForeign) + else Nothing decls = [ tyThingToIfaceDecl show_linear_types entity | entity <- entities, let name = getName entity, @@ -370,12 +372,12 @@ mkIface_ hsc_env & set_mi_anns annotations & set_mi_top_env rdrs & set_mi_decls decls - & set_mi_extra_decls extra_decls + & set_mi_simplified_core simplified_core & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) & set_mi_docs docs - & set_mi_final_exts () + & set_mi_abi_hashes () & set_mi_ext_fields emptyExtensibleFields & set_mi_hi_bytes PartialIfaceBinHandle ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -88,6 +88,7 @@ import Data.Ord import Data.Containers.ListUtils import Data.Bifunctor import GHC.Iface.Errors.Ppr +import Data.Functor {- ----------------------------------------------- @@ -325,8 +326,8 @@ check_old_iface hsc_env mod_summary maybe_iface maybe_dyn_iface <- liftIO $ loadIface (setDynamicNow dflags) (msDynHiFilePath mod_summary) case maybe_dyn_iface of Nothing -> return $ outOfDateItemBecause MissingDynHiFile Nothing - Just dyn_iface | mi_iface_hash (mi_final_exts dyn_iface) - /= mi_iface_hash (mi_final_exts normal_iface) + Just dyn_iface | mi_iface_hash dyn_iface + /= mi_iface_hash normal_iface -> return $ outOfDateItemBecause MismatchedDynHiFile Nothing Just {} -> return res _ -> return res @@ -382,7 +383,7 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface - -> ModIfaceSelfRecomp + -> IfaceSelfRecomp -> IfG (MaybeValidated ModIface) checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger @@ -435,7 +436,7 @@ checkVersions hsc_env mod_summary iface self_recomp -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins :: Plugins -> IfaceSelfRecomp -> IfG RecompileRequired checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp @@ -528,10 +529,10 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash :: HscEnv -> Module -> IfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + let FingerprintWithValue old_fp old_flags = mi_sr_flag_hash self_recomp (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally if old_fp == new_fp then up_to_date logger (text "Module flags unchanged") @@ -573,7 +574,7 @@ checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkOptimHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env let old_hash = mi_sr_opt_hash iface @@ -589,7 +590,7 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env let old_hash = mi_sr_hpc_hash self_recomp @@ -606,7 +607,7 @@ checkHpcHash hsc_env self_recomp = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures :: HscEnv -> ModSummary -> IfaceSelfRecomp -> IO RecompileRequired checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env @@ -748,7 +749,7 @@ checkModUsage _ UsagePackageModule{ logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChanged (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) -- We only track the ABI hash of package modules, rather than -- individual entity usages, so if the ABI hash changes we must -- recompile. This is safe but may entail more recompilation when @@ -758,7 +759,7 @@ checkModUsage _ UsageMergedRequirement{ usg_mod = mod, usg_mod_hash = old_mod_ha logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedRaw (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name , usg_unit_id = uid , usg_iface_hash = old_mod_hash } = do @@ -766,7 +767,7 @@ checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedIface mod_name - checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash (mi_final_exts iface)) + checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash iface) checkModUsage _ UsageHomeModule{ usg_mod_name = mod_name, @@ -779,9 +780,9 @@ checkModUsage _ UsageHomeModule{ logger <- getLogger needInterface mod $ \iface -> do let - new_mod_hash = mi_mod_hash (mi_final_exts iface) - new_decl_hash = mi_hash_fn (mi_final_exts iface) - new_export_hash = mi_exp_hash (mi_final_exts iface) + new_mod_hash = mi_mod_hash iface + new_decl_hash = mi_hash_fn iface + new_export_hash = mi_exp_hash iface reason = ModuleChanged (moduleName mod) @@ -986,7 +987,7 @@ we use is: -- | Compute the information needed for self-recompilation checking. This -- information can be computed before the backend phase. -mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO IfaceSelfRecomp mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env @@ -1000,10 +1001,10 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do let include_detailed_flags (flag_hash, flags) = if gopt Opt_WriteSelfRecompFlags dflags - then (flag_hash, Just flags) - else (flag_hash, Nothing) + then FingerprintWithValue flag_hash (Just flags) + else FingerprintWithValue flag_hash Nothing - return (ModIfaceSelfRecomp + return (IfaceSelfRecomp { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash @@ -1018,28 +1019,92 @@ addFingerprints :: HscEnv -> PartialModIface -> IO ModIface -addFingerprints hsc_env iface0 - = do - eps <- hscEPS hsc_env - let - decls = mi_decls iface0 - decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings $ mi_warns iface0) - export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ mi_warns iface0) - fix_fn = mkIfaceFixCache (mi_fixities iface0) +addFingerprints hsc_env iface0 = do + (abiHashes, caches, decls_w_hashes) <- addAbiHashes hsc_env (mi_mod_info iface0) (mi_public iface0) (mi_deps iface0) + + -- put the declarations in a canonical order, sorted by OccName + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ + [(getOccName d, e) | e@(_, d) <- decls_w_hashes] + + -- This key is safe because mi_extra_decls contains tidied things. + getOcc (IfGblTopBndr b) = getOccName b + getOcc (IfLclTopBndr fs _ _ details) = + case details of + IfRecSelId { ifRecSelFirstCon = first_con } + -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) + _ -> mkVarOccFS (ifLclNameFS fs) + + binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () + binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) + + sorted_extra_decls :: Maybe IfaceSimplifiedCore + sorted_extra_decls = mi_simplified_core iface0 <&> \simpl_core -> + IfaceSimplifiedCore (sortOn binding_key (mi_sc_extra_decls simpl_core)) (mi_sc_foreign simpl_core) + + -- The interface hash depends on: + -- - the ABI hash, plus + -- - the things which can affect whether a module is recompiled + -- - the module level annotations, + -- - deps (home and external packages, dependent files) + iface_hash <- computeFingerprint putNameLiterally + (mi_abi_mod_hash abiHashes, + mi_self_recomp_info iface0, + mi_deps iface0) + + let final_iface = completePartialModIface iface0 iface_hash + sorted_decls sorted_extra_decls abiHashes caches + -- + return final_iface + + + +-- The ABI hash should depend on everything in IfacePublic +-- This is however computed in a very convoluted way, so be careful your +-- addition ends up in the right place. In essence all this function does is +-- compute a hash of the arguments. +-- +-- Why the convoluted way? Hashing individual declarations allows us to do fine-grained +-- recompilation checking for home package modules, which record precisely what they use +-- from each module. +addAbiHashes :: HscEnv -> IfaceModInfo -> PartialIfacePublic -> Dependencies -> IO (IfaceAbiHashes, IfaceCache, [(Fingerprint, IfaceDecl)]) +addAbiHashes hsc_env info iface_public deps = do + eps <- hscEPS hsc_env + let + -- If you have arrived here by accident then congratulations, + -- you have discovered the ABI hash. Your reward is to update the ABI hash to + -- account for your change to the interface file. Omitting your field using a + -- wildcard may lead to some unfortunate consequences. + + -- MP: TODO: Existing bug where defaults, trust_pkg and complete are not taken into account + -- when computing the ABI hash. + IfacePublic exports fixities warns anns decls _defaults insts fam_insts rules trust _trust_pkg _complete _cache () = iface_public + -- And these fields of deps should be in IfacePublic, but in good time. + Dependencies _ _ _ sig_mods trusted_pkgs boot_mods orph_mods fis_mods = deps + decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings warns) + export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ warns) + fix_fn = mkIfaceFixCache fixities + + this_mod = mi_mod_info_module info + semantic_mod = mi_mod_info_semantic_module info + (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph insts + (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph rules + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph fam_insts + ann_fn = mkIfaceAnnCache anns -- The ABI of a declaration represents everything that is made -- visible about the declaration that a client can depend on. -- see IfaceDeclABI below. - declABI :: IfaceDecl -> IfaceDeclABI + declABI :: IfaceDecl -> IfaceDeclABI -- TODO: I'm not sure if this should be semantic_mod or this_mod. -- See also Note [Identity versus semantic module] - declABI decl = (this_mod, decl, extras) + declABI decl = (this_mod, decl, extras) where extras = declExtras fix_fn ann_fn non_orph_rules non_orph_insts non_orph_fis top_lvl_name_env decl -- This is used for looking up the Name of a default method -- from its OccName. See Note [default method Name] - top_lvl_name_env = + top_lvl_name_env = mkOccEnv [ (nameOccName nm, nm) | IfaceId { ifName = nm } <- decls ] @@ -1047,15 +1112,15 @@ addFingerprints hsc_env iface0 -- This is computed by finding the free external names of each -- declaration, including IfaceDeclExtras (things that a -- declaration implicitly depends on). - edges :: [ Node OccName IfaceDeclABI ] - edges = [ DigraphNode abi (getOccName decl) out + edges :: [ Node OccName IfaceDeclABI ] + edges = [ DigraphNode abi (getOccName decl) out | decl <- decls , let abi = declABI decl , let out = localOccs $ freeNamesDeclABI abi ] - name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) - localOccs = + name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) + localOccs = map (getParent . getOccName) -- NB: names always use semantic module, so -- filtering must be on the semantic module! @@ -1073,17 +1138,17 @@ addFingerprints hsc_env iface0 -- maps OccNames to their parents in the current module. -- e.g. a reference to a constructor must be turned into a reference -- to the TyCon for the purposes of calculating dependencies. - parent_map :: OccEnv OccName - parent_map = foldl' extend emptyOccEnv decls + parent_map :: OccEnv OccName + parent_map = foldl' extend emptyOccEnv decls where extend env d = extendOccEnvList env [ (b,n) | b <- ifaceDeclImplicitBndrs d ] where n = getOccName d -- Strongly-connected groups of declarations, in dependency order - groups :: [SCC IfaceDeclABI] - groups = stronglyConnCompFromEdgedVerticesOrd edges + groups :: [SCC IfaceDeclABI] + groups = stronglyConnCompFromEdgedVerticesOrd edges - global_hash_fn = mkHashFun hsc_env eps + global_hash_fn = mkHashFun hsc_env eps -- How to output Names when generating the data to fingerprint. -- Here we want to output the fingerprint for each top-level @@ -1091,9 +1156,9 @@ addFingerprints hsc_env iface0 -- module. In this way, the fingerprint for a declaration will -- change if the fingerprint for anything it refers to (transitively) -- changes. - mk_put_name :: OccEnv (OccName,Fingerprint) + mk_put_name :: OccEnv (OccName,Fingerprint) -> WriteBinHandle -> Name -> IO () - mk_put_name local_env bh name + mk_put_name local_env bh name | isWiredInName name = putNameLiterally bh name -- wired-in names don't have fingerprints | otherwise @@ -1120,21 +1185,21 @@ addFingerprints hsc_env iface0 -- take a strongly-connected group of declarations and compute -- its fingerprint. - fingerprint_group :: (OccEnv (OccName,Fingerprint), + fingerprint_group :: (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) -> SCC IfaceDeclABI -> IO (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) - fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) - = do let hash_fn = mk_put_name local_env - decl = abiDecl abi + fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) + = do let hash_fn = mk_put_name local_env + decl = abiDecl abi --pprTrace "fingerprinting" (ppr (ifName decl) ) $ do - hash <- computeFingerprint hash_fn abi - env' <- extend_hash_env local_env (hash,decl) - return (env', (hash,decl) : decls_w_hashes) + hash <- computeFingerprint hash_fn abi + env' <- extend_hash_env local_env (hash,decl) + return (env', (hash,decl) : decls_w_hashes) - fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) + fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) = do let stable_abis = sortBy cmp_abiNames abis stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env @@ -1150,33 +1215,27 @@ addFingerprints hsc_env iface0 return (local_env2, pairs ++ decls_w_hashes) -- Make a fingerprint from the ordinal position of a binding in its group. - mkRecFingerprint :: Word64 -> Fingerprint - mkRecFingerprint i = Fingerprint 0 i + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i - bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint - bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. -- - extend_hash_env :: OccEnv (OccName,Fingerprint) + extend_hash_env :: OccEnv (OccName,Fingerprint) -> (Fingerprint,IfaceDecl) -> IO (OccEnv (OccName,Fingerprint)) - extend_hash_env env0 (hash,d) = + extend_hash_env env0 (hash,d) = return (foldr (\(b,fp) env -> extendOccEnv env b (b,fp)) env0 (ifaceDeclFingerprints hash d)) -- - (local_env, decls_w_hashes) <- + (local_env, decls_w_hashes) <- foldM fingerprint_group (emptyOccEnv, []) groups - -- when calculating fingerprints, we always need to use canonical ordering - -- for lists of things. The mi_deps has various lists of modules and - -- suchlike, which are stored in canonical order: - let sorted_deps :: Dependencies - sorted_deps = mi_deps iface0 - -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way -- that changes in orphans get propagated all the way up the @@ -1202,10 +1261,11 @@ addFingerprints hsc_env iface0 -- External. It's true that Home1 will get rebuilt if the orphans -- of External, but we also need to make sure Home2 gets rebuilt -- as well. See #12733 for more details. - let orph_mods - = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] - $ dep_orphs sorted_deps - dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods + let orph_mods_no_self + = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] + $ orph_mods + dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods_no_self + -- Note [Do not update EPS with your own hi-boot] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1216,26 +1276,26 @@ addFingerprints hsc_env iface0 -- instances yourself, no need to consult hs-boot; if you do load the -- interface into EPS, you will see a duplicate orphan instance. - orphan_hash <- computeFingerprint (mk_put_name local_env) + orphan_hash <- computeFingerprint (mk_put_name local_env) (map ifDFun orph_insts, orph_rules, orph_fis) - -- Hash of the transitive things in dependencies - dep_hash <- computeFingerprint putNameLiterally - (dep_sig_mods (mi_deps iface0), - dep_boot_mods (mi_deps iface0), - -- Trusted packages are like orphans - dep_trusted_pkgs (mi_deps iface0), + -- Hash of the transitive things in dependencies + dep_hash <- computeFingerprint putNameLiterally + (sig_mods, + boot_mods, + -- Trusted packages are like orphans + trusted_pkgs, -- See Note [Export hash depends on non-orphan family instances] - dep_finsts (mi_deps iface0) ) + fis_mods ) - -- the export list hash doesn't depend on the fingerprints of - -- the Names it mentions, only the Names themselves, hence putNameLiterally. - export_hash <- computeFingerprint putNameLiterally - (mi_exports iface0, + -- the export list hash doesn't depend on the fingerprints of + -- the Names it mentions, only the Names themselves, hence putNameLiterally. + export_hash <- computeFingerprint putNameLiterally + (exports, orphan_hash, dep_hash, dep_orphan_hashes, - mi_trust iface0) + trust) -- Make sure change of Safe Haskell mode causes recomp. -- Note [Export hash depends on non-orphan family instances] @@ -1266,79 +1326,44 @@ addFingerprints hsc_env iface0 -- (also we didn't store it anywhere!) -- - -- put the declarations in a canonical order, sorted by OccName - let sorted_decls :: [(Fingerprint, IfaceDecl)] - sorted_decls = Map.elems $ Map.fromList $ - [(getOccName d, e) | e@(_, d) <- decls_w_hashes] - -- This key is safe because mi_extra_decls contains tidied things. - getOcc (IfGblTopBndr b) = getOccName b - getOcc (IfLclTopBndr fs _ _ details) = - case details of - IfRecSelId { ifRecSelFirstCon = first_con } - -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) - _ -> mkVarOccFS (ifLclNameFS fs) - - binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () - binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) - - sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - - -- the ABI hash depends on: - -- - decls - -- - export list - -- - orphans - -- - deprecations - -- - flag abi hash - -- - foreign stubs and files - mod_hash <- computeFingerprint putNameLiterally - (map fst sorted_decls, + -- the ABI hash depends on: + -- - decls + -- - export list + -- - orphans + -- - deprecations + -- - flag abi hash + mod_hash <- computeFingerprint putNameLiterally + (sort (map fst decls_w_hashes), export_hash, -- includes orphan_hash - mi_warns iface0, - mi_foreign iface0) - - - -- The interface hash depends on: - -- - the ABI hash, plus - -- - the things which can affect whether a module is recompiled - -- - the module level annotations, - -- - deps (home and external packages, dependent files) - iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_self_recomp_info iface0, - sorted_deps ) + ann_fn AnnModule, + warns) - let - final_iface_exts = ModIfaceBackend - { mi_mod_hash = mod_hash - , mi_iface_hash = iface_hash - , mi_orphan = not ( all ifRuleAuto orph_rules + -- Surely the ABI depends on "module" annotations? + -- Also named defaults + + + + let + final_iface_exts = IfaceAbiHashes + { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts && null orph_fis) - , mi_finsts = not (null (mi_fam_insts iface0)) - , mi_exp_hash = export_hash - , mi_orphan_hash = orphan_hash - , mi_decl_warn_fn = decl_warn_fn - , mi_export_warn_fn = export_warn_fn - , mi_fix_fn = fix_fn - , mi_hash_fn = lookupOccEnv local_env + , mi_abi_finsts = not (null fam_insts) + , mi_abi_exp_hash = export_hash + , mi_abi_orphan_hash = orphan_hash } - final_iface = completePartialModIface iface0 - sorted_decls sorted_extra_decls final_iface_exts - -- - return final_iface + caches = IfaceCache + { mi_cache_decl_warn_fn = decl_warn_fn + , mi_cache_export_warn_fn = export_warn_fn + , mi_cache_fix_fn = fix_fn + , mi_cache_hash_fn = lookupOccEnv local_env + } + return (final_iface_exts, caches, decls_w_hashes) where - this_mod = mi_module iface0 - semantic_mod = mi_semantic_module iface0 - (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) - (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) - (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - ann_fn = mkIfaceAnnCache (mi_anns iface0) - -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the @@ -1378,7 +1403,7 @@ getOrphanHashes hsc_env mods = do get_orph_hash mod = do iface <- initIfaceLoad hsc_env . withIfaceErr ctx $ loadInterface (text "getOrphanHashes") mod ImportBySystem - return (mi_orphan_hash (mi_final_exts iface)) + return (mi_orphan_hash iface) mapM get_orph_hash mods @@ -1531,7 +1556,7 @@ instance Binary IfaceIdExtras where put_ bh (IdExtras fix rules anns)= do { put_ bh fix; put_ bh rules; put_ bh anns } declExtras :: (OccName -> Maybe Fixity) - -> (OccName -> [AnnPayload]) + -> (AnnCacheKey -> [AnnPayload]) -> OccEnv [IfaceRule] -> OccEnv [IfaceClsInst] -> OccEnv [IfaceFamInst] @@ -1546,10 +1571,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl IfaceDataExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n) ++ map ifDFun (lookupOccEnvL inst_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) (map (id_extras . occName . ifConName) (visibleIfConDecls cons)) IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} -> - IfaceClassExtras (fix_fn n) insts (ann_fn n) meths defms + IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms where insts = (map ifDFun $ (concatMap at_extras ats) ++ lookupOccEnvL inst_env n) @@ -1562,17 +1587,16 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl , let dmOcc = mkDefaultMethodOcc (nameOccName bndr) , Just dmName <- [lookupOccEnv dm_env dmOcc] ] IfaceSynonym{} -> IfaceSynonymExtras (fix_fn n) - (ann_fn n) + (ann_fn (AnnOccName n)) IfaceFamily{} -> IfaceFamilyExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) _other -> IfaceOtherDeclExtras where n = getOccName decl - id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn occ) + id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl) - {- Note [default method Name] (see also #15970) ~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1685,20 +1709,25 @@ mkHashFun hsc_env eps name -- just one of the many horrible hacks in the backpack -- implementation. $ loadInterface (text "lookupVers2") mod ImportBySystem - return $ snd (mi_hash_fn (mi_final_exts iface) occ `orElse` + return $ snd (mi_hash_fn iface occ `orElse` pprPanic "lookupVers1" (ppr mod <+> ppr occ)) +data AnnCacheKey = AnnModule | AnnOccName OccName + -- | Creates cached lookup for the 'mi_anns' field of ModIface -- Hackily, we use "module" as the OccName for any module-level annotations -mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload] +mkIfaceAnnCache :: [IfaceAnnotation] -> AnnCacheKey -> [AnnPayload] mkIfaceAnnCache anns - = \n -> lookupOccEnv env n `orElse` [] + = \n -> case n of + AnnModule -> module_anns + AnnOccName occn -> lookupOccEnv env occn `orElse` [] where - pair (IfaceAnnotation target value) = - (case target of - NamedTarget occn -> occn - ModuleTarget _ -> mkVarOccFS (fsLit "module") - , [value]) + (module_anns, occ_anns) = partitionEithers $ map classify anns + classify (IfaceAnnotation target value) = + case target of + NamedTarget occn -> Right (occn, [value]) + ModuleTarget _ -> Left value + -- flipping (++), so the first argument is always short - env = mkOccEnv_C (flip (++)) (map pair anns) + env = mkOccEnv_C (flip (++)) occ_anns ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,5 +1,5 @@ module GHC.Iface.Recomp.Types ( - ModIfaceSelfRecomp(..), + IfaceSelfRecomp(..), IfaceDynFlags(..), pprIfaceDynFlags, missingExtraFlagInfo, @@ -9,7 +9,9 @@ import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable import GHC.Iface.Flags +import GHC.Types.SafeHaskell import GHC.Unit.Module.Deps +import GHC.Unit.Module import GHC.Utils.Binary @@ -59,8 +61,8 @@ proper way. -- itself. -- -- See Note [Self recompilation information in interface files] -data ModIfaceSelfRecomp = - ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint +data IfaceSelfRecomp = + IfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint -- ^ Hash of the .hs source, used for recompilation checking. , mi_sr_usages :: [Usage] -- ^ Usages; kept sorted so that it's easy to decide @@ -69,7 +71,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) + , mi_sr_flag_hash :: !(FingerprintWithValue IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -81,8 +83,8 @@ data ModIfaceSelfRecomp = } -instance Binary ModIfaceSelfRecomp where - put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do +instance Binary IfaceSelfRecomp where + put_ bh (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do put_ bh mi_sr_src_hash lazyPut bh mi_sr_usages put_ bh mi_sr_flag_hash @@ -97,19 +99,58 @@ instance Binary ModIfaceSelfRecomp where opt_hash <- get bh hpc_hash <- get bh plugin_hash <- get bh - return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + return $ IfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } -instance Outputable ModIfaceSelfRecomp where - ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) +instance Outputable IfaceSelfRecomp where + ppr (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash - , text "usages:" <+> ppr (length mi_sr_usages) - , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash + , text "flags:" <+> pprFingerprintWithValue missingExtraFlagInfo (fmap pprIfaceDynFlags mi_sr_flag_hash) , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash + , text "usages:" <+> ppr (map pprUsage mi_sr_usages) ])] -instance NFData ModIfaceSelfRecomp where - rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file +instance NFData IfaceSelfRecomp where + rnf (IfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () + +pprFingerprintWithValue :: SDoc -> FingerprintWithValue SDoc -> SDoc +pprFingerprintWithValue missingInfo (FingerprintWithValue fp mflags) + = vcat $ + [ text "fingerprint:" <+> (ppr fp) + ] + ++ case mflags of + Nothing -> [missingInfo] + Just doc -> [doc] + +pprUsage :: Usage -> SDoc +pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } + = pprUsageImport mod hash safe +pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name + , usg_mod_hash = hash, usg_safe = safe + , usg_exports = exports, usg_entities = entities } + = pprUsageImport (mkModule unit_id mod_name) hash safe $$ + nest 2 ( + maybe empty (\v -> text "exports: " <> ppr v) exports $$ + vcat [ ppr n <+> ppr v | (n,v) <- entities ] + ) +pprUsage usage at UsageFile{} + = hsep [text "addDependentFile", + doubleQuotes (ftext (usg_file_path usage)), + ppr (usg_file_hash usage)] +pprUsage usage at UsageMergedRequirement{} + = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] +pprUsage usage at UsageHomeModuleInterface{} + = hsep [text "implementation", ppr (usg_mod_name usage) + , ppr (usg_unit_id usage) + , ppr (usg_iface_hash usage)] + +pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc +pprUsageImport mod hash safe + = hsep [ text "import", pp_safe, ppr mod + , ppr hash ] + where + pp_safe | safe = text "safe" + | otherwise = text " -/ " \ No newline at end of file ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -183,7 +183,7 @@ lookupFixityRn_help name -- loadInterfaceForName will find B.hi even if B is a hidden module, -- and that's what we want. = do { iface <- loadInterfaceForName doc name - ; let mb_fix = mi_fix_fn (mi_final_exts iface) occ + ; let mb_fix = mi_fix_fn iface occ ; let msg = case mb_fix of Nothing -> text "looking up name" <+> ppr name ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -93,6 +93,7 @@ import GHC.Data.FastString.Env import GHC.Data.Maybe import GHC.Data.List.SetOps ( removeDups ) +import Control.Arrow ( second ) import Control.Monad import Data.Foldable ( for_ ) import Data.IntMap ( IntMap ) @@ -100,6 +101,8 @@ import qualified Data.IntMap as IntMap import Data.Map ( Map ) import qualified Data.Map as Map import Data.Ord ( comparing ) +import Data.Semigroup ( Any(..) ) +import qualified Data.Semigroup as S import Data.List ( partition, find, sortBy ) import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.List.NonEmpty as NE @@ -108,6 +111,7 @@ import qualified Data.Set as S import System.FilePath ((</>)) import System.IO + {- ************************************************************************ * * @@ -485,8 +489,8 @@ calculateAvails :: HomeUnit calculateAvails home_unit other_home_units iface mod_safe' want_boot imported_by = let imp_mod = mi_module iface imp_sem_mod= mi_semantic_module iface - orph_iface = mi_orphan (mi_final_exts iface) - has_finsts = mi_finsts (mi_final_exts iface) + orph_iface = mi_orphan iface + has_finsts = mi_finsts iface deps = mi_deps iface trust = getSafeMode $ mi_trust iface trust_pkg = mi_trust_pkg iface @@ -1397,7 +1401,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) _ -> failLookupWith err mk_depr_export_warning gre - = DeprecatedExport name <$> mi_export_warn_fn (mi_final_exts iface) name + = DeprecatedExport name <$> mi_export_warn_fn iface name where name = greName gre @@ -1842,21 +1846,21 @@ findImportUsage imports used_gres -- srcSpanEnd: see Note [The ImportMap] `orElse` [] - used_names = mkNameSet (map greName used_gres) + used_gre_env = mkGlobalRdrEnv used_gres used_parents = mkNameSet (mapMaybe greParent_maybe used_gres) unused_imps -- Not trivial; see eg #7454 = case imps of Just (Exactly, L _ imp_ies) -> - foldr (add_unused . unLoc) emptyNameSet imp_ies + let unused = foldr (add_unused . unLoc) (UnusedNames emptyNameSet emptyFsEnv) imp_ies + in collectUnusedNames unused _other -> emptyNameSet -- No explicit import list => no unused-name list - add_unused :: IE GhcRn -> NameSet -> NameSet - add_unused (IEVar _ n _) acc = add_unused_name (lieWrappedName n) acc - add_unused (IEThingAbs _ n _) acc = add_unused_name (lieWrappedName n) acc + add_unused :: IE GhcRn -> UnusedNames -> UnusedNames + add_unused (IEVar _ n _) acc = add_unused_name (lieWrappedName n) True acc + add_unused (IEThingAbs _ n _) acc = add_unused_name (lieWrappedName n) False acc add_unused (IEThingAll _ n _) acc = add_unused_all (lieWrappedName n) acc - add_unused (IEThingWith _ p wc ns _) acc = - add_wc_all (add_unused_with pn xs acc) + add_unused (IEThingWith _ p wc ns _) acc = add_wc_all (add_unused_with pn xs acc) where pn = lieWrappedName p xs = map lieWrappedName ns add_wc_all = case wc of @@ -1864,21 +1868,115 @@ findImportUsage imports used_gres IEWildcard _ -> add_unused_all pn add_unused _ acc = acc - add_unused_name n acc - | n `elemNameSet` used_names = acc - | otherwise = acc `extendNameSet` n - add_unused_all n acc - | n `elemNameSet` used_names = acc - | n `elemNameSet` used_parents = acc - | otherwise = acc `extendNameSet` n + add_unused_name :: Name -> Bool -> UnusedNames -> UnusedNames + add_unused_name n is_ie_var acc@(UnusedNames acc_ns acc_fs) + | is_ie_var + , isFieldName n + -- See Note [Reporting unused imported duplicate record fields] + = let + fs = getOccFS n + (flds, flds_used) = lookupFsEnv acc_fs fs `orElse` (emptyNameSet, Any False) + acc_fs' = extendFsEnv acc_fs fs (extendNameSet flds n, Any used S.<> flds_used) + in UnusedNames acc_ns acc_fs' + | used + = acc + | otherwise + = UnusedNames (acc_ns `extendNameSet` n) acc_fs + where + used = isJust $ lookupGRE_Name used_gre_env n + + add_unused_all :: Name -> UnusedNames -> UnusedNames + add_unused_all n (UnusedNames acc_ns acc_fs) + | Just {} <- lookupGRE_Name used_gre_env n = UnusedNames acc_ns acc_fs + | n `elemNameSet` used_parents = UnusedNames acc_ns acc_fs + | otherwise = UnusedNames (acc_ns `extendNameSet` n) acc_fs + + add_unused_with :: Name -> [Name] -> UnusedNames -> UnusedNames add_unused_with p ns acc - | all (`elemNameSet` acc1) ns = add_unused_name p acc1 - | otherwise = acc1 + | all (`elemNameSet` acc1_ns) ns = add_unused_name p False acc1 + | otherwise = acc1 where - acc1 = foldr add_unused_name acc ns - -- If you use 'signum' from Num, then the user may well have - -- imported Num(signum). We don't want to complain that - -- Num is not itself mentioned. Hence the two cases in add_unused_with. + acc1@(UnusedNames acc1_ns _acc1_fs) = foldr (\n acc' -> add_unused_name n False acc') acc ns + -- If you use 'signum' from Num, then the user may well have + -- imported Num(signum). We don't want to complain that + -- Num is not itself mentioned. Hence the two cases in add_unused_with. + + +-- | An accumulator for unused names in an import list. +-- +-- See Note [Reporting unused imported duplicate record fields]. +data UnusedNames = + UnusedNames + { unused_names :: NameSet + -- ^ Unused 'Name's in an import list, not including record fields + -- that are plain 'IEVar' imports + , rec_fld_uses :: FastStringEnv (NameSet, Any) + -- ^ Record fields imported without a parent (i.e. an 'IEVar' import). + -- + -- The 'Any' value records whether any of the record fields + -- sharing the same underlying 'FastString' have been used. + } +instance Outputable UnusedNames where + ppr (UnusedNames nms flds) = + text "UnusedNames" <+> + braces (ppr nms <+> ppr (fmap (second getAny) flds)) + +-- | Collect all unused names from a 'UnusedNames' value. +collectUnusedNames :: UnusedNames -> NameSet +collectUnusedNames (UnusedNames { unused_names = nms, rec_fld_uses = flds }) + = nms S.<> unused_flds + where + unused_flds = nonDetFoldFsEnv collect_unused emptyNameSet flds + collect_unused :: (NameSet, Any) -> NameSet -> NameSet + collect_unused (nms, Any at_least_one_name_is_used) acc + | at_least_one_name_is_used = acc + | otherwise = unionNameSet nms acc + +{- Note [Reporting unused imported duplicate record fields] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we have (#24035): + + {-# LANGUAGE DuplicateRecordFields #-} + module M1 (R1(..), R2(..)) where + data R1 = MkR1 { fld :: Int } + data R2 = MkR2 { fld :: Int } + + {-# LANGUAGE DuplicateRecordFields #-} + module M2 where + import M1 (R1(MkR1), R2, fld) + f :: R1 -> Int + f (MkR1 { fld = x }) = x + g :: R2 -> Int + g _ = 3 + +In the import of 'M1' in 'M2', the 'fld' import resolves to two separate GREs, +namely R1(fld) and R2(fld). From the perspective of the renamer, and in particular +the 'findImportUsage' function, it's as if the user had imported the two names +separately (even though no source syntax allows that). + +This means that we need to be careful when reporting unused imports: the R2(fld) +import is indeed unused, but because R1(fld) is used, we should not report +fld as unused altogether. + +To achieve this, we keep track of record field imports without a parent (i.e. +using the IEVar constructor) separately from other import items, using the +UnusedNames datatype. +Once we have accumulated usages, we emit warnings for unused record fields +without parents one whole group (of record fields sharing the same textual name) +at a time, and only if *all* of the record fields in the group are unused; +see 'collectUnusedNames'. + +Note that this only applies to record fields imported without a parent. If we +had: + + import M1 (R1(MkR1, fld), R2(fld)) + f :: R1 -> Int + f (MkR1 { fld = x }) = x + g :: R2 -> Int + g _ = 3 + +then of course we should report the second 'fld' as unused. +-} {- Note [The ImportMap] @@ -1945,12 +2043,15 @@ warnUnusedImport rdr_env (L loc decl, used, unused) | null unused = return () - -- Only one import is unused, with `SrcSpan` covering only the unused item instead of - -- the whole import statement + -- Some imports are unused: make the `SrcSpan` cover only the unused + -- items instead of the whole import statement | Just (_, L _ imports) <- ideclImportList decl - , length unused == 1 - , Just (L loc _) <- find (\(L _ ie) -> ((ieName ie) :: Name) `elem` unused) imports - = addDiagnosticAt (locA loc) (TcRnUnusedImport decl (UnusedImportSome sort_unused)) + , let unused_locs = [ locA loc | L loc ie <- imports + , name <- ieNames ie + , name `elem` unused ] + , loc1 : locs <- unused_locs + , let span = foldr1 combineSrcSpans ( loc1 NE.:| locs ) + = addDiagnosticAt span (TcRnUnusedImport decl (UnusedImportSome sort_unused)) -- Some imports are unused | otherwise @@ -2263,3 +2364,4 @@ addDupDeclErr gres@(gre :| _) checkConName :: RdrName -> TcRn () checkConName name = checkErr (isRdrDataCon name || isRdrTc name) (TcRnIllegalDataCon name) + ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -539,9 +539,9 @@ warnIfDeclDeprecated gre@(GRE { gre_imp = iss }) lookupImpDeclDeprec :: ModIface -> GlobalRdrElt -> Maybe (WarningTxt GhcRn) lookupImpDeclDeprec iface gre -- Bleat if the thing, or its parent, is warn'd - = mi_decl_warn_fn (mi_final_exts iface) (greOccName gre) `mplus` + = mi_decl_warn_fn iface (greOccName gre) `mplus` case greParent gre of - ParentIs p -> mi_decl_warn_fn (mi_final_exts iface) (nameOccName p) + ParentIs p -> mi_decl_warn_fn iface (nameOccName p) NoParent -> Nothing warnIfExportDeprecated :: GlobalRdrElt -> RnM () @@ -562,7 +562,7 @@ warnIfExportDeprecated gre@(GRE { gre_imp = iss }) process_import_spec is = do let mod = is_mod $ is_decl is iface <- loadInterfaceForModule doc mod - let mb_warn_txt = mi_export_warn_fn (mi_final_exts iface) name + let mb_warn_txt = mi_export_warn_fn iface name return $ (moduleName mod, ) <$> mb_warn_txt ------------------------- ===================================== compiler/GHC/Tc/Instance/Family.hs ===================================== @@ -308,7 +308,7 @@ checkFamInstConsistency directlyImpMods ifc <- modIface mod deps <- dep_finsts . mi_deps <$> modIface mod pure $ - if mi_finsts (mi_final_exts ifc) + if mi_finsts ifc then mod:deps else deps ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -97,7 +97,7 @@ checkHsigDeclM sig_iface sig_thing real_thing = do -- implementation cases. checkBootDeclM Hsig sig_thing real_thing real_fixity <- lookupFixityRn name - let sig_fixity = case mi_fix_fn (mi_final_exts sig_iface) (occName name) of + let sig_fixity = case mi_fix_fn sig_iface (occName name) of Nothing -> defaultFixity Just f -> f when (real_fixity /= sig_fixity) $ @@ -850,7 +850,7 @@ mergeSignatures if outer_mod == mi_module iface -- Don't add ourselves! then tcg_merged tcg_env - else (mi_module iface, mi_mod_hash (mi_final_exts iface)) : tcg_merged tcg_env + else (mi_module iface, mi_mod_hash iface) : tcg_merged tcg_env } -- Note [Signature merging DFuns] ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -1,18 +1,20 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ExplicitNamespaces #-} -- | Dependencies and Usage of a module module GHC.Unit.Module.Deps - ( Dependencies - , mkDependencies - , noDependencies - , dep_direct_mods - , dep_direct_pkgs - , dep_sig_mods - , dep_trusted_pkgs - , dep_orphs - , dep_plugin_pkgs - , dep_finsts - , dep_boot_mods + ( Dependencies(dep_direct_mods + , dep_direct_pkgs + , dep_sig_mods + , dep_trusted_pkgs + , dep_orphs + , dep_plugin_pkgs + , dep_finsts + , dep_boot_mods + , Dependencies) , dep_orphs_update , dep_finsts_update + , mkDependencies + , noDependencies , pprDeps , Usage (..) , ImportAvails (..) @@ -52,38 +54,38 @@ import Control.DeepSeq -- -- See Note [Transitive Information in Dependencies] data Dependencies = Deps - { dep_direct_mods :: Set (UnitId, ModuleNameWithIsBoot) + { dep_direct_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All home-package modules which are directly imported by this one. -- This may include modules from other units when using multiple home units - , dep_direct_pkgs :: Set UnitId + , dep_direct_pkgs_ :: Set UnitId -- ^ All packages directly imported by this module -- I.e. packages to which this module's direct imports belong. -- Does not include other home units when using multiple home units. -- Modules from these units will go in `dep_direct_mods` - , dep_plugin_pkgs :: Set UnitId + , dep_plugin_pkgs_ :: Set UnitId -- ^ All units needed for plugins ------------------------------------ -- Transitive information below here - , dep_sig_mods :: ![ModuleName] + , dep_sig_mods_ :: ![ModuleName] -- ^ Transitive closure of hsig files in the home package - , dep_trusted_pkgs :: Set UnitId + , dep_trusted_pkgs_ :: Set UnitId -- Packages which we are required to trust -- when the module is imported as a safe import -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names - , dep_boot_mods :: Set (UnitId, ModuleNameWithIsBoot) + , dep_boot_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All modules which have boot files below this one, and whether we -- should use the boot file or not. -- This information is only used to populate the eps_is_boot field. -- See Note [Structure of dep_boot_mods] - , dep_orphs :: [Module] + , dep_orphs_ :: [Module] -- ^ Transitive closure of orphan modules (whether -- home or external pkg). -- @@ -93,7 +95,7 @@ data Dependencies = Deps -- which relies on dep_orphs having the complete list!) -- This does NOT include us, unlike 'imp_orphs'. - , dep_finsts :: [Module] + , dep_finsts_ :: [Module] -- ^ Transitive closure of depended upon modules which -- contain family instances (whether home or external). -- This is used by 'checkFamInstConsistency'. This @@ -105,6 +107,26 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +pattern Dependencies :: Set (UnitId, ModuleNameWithIsBoot) + -> Set UnitId + -> Set UnitId + -> [ModuleName] + -> Set UnitId + -> Set (UnitId, ModuleNameWithIsBoot) + -> [Module] + -> [Module] + -> Dependencies +pattern Dependencies {dep_direct_mods, dep_direct_pkgs, dep_plugin_pkgs, dep_sig_mods, dep_trusted_pkgs, dep_boot_mods, dep_orphs, dep_finsts} + <- Deps {dep_direct_mods_ = dep_direct_mods + , dep_direct_pkgs_ = dep_direct_pkgs + , dep_plugin_pkgs_ = dep_plugin_pkgs + , dep_sig_mods_ = dep_sig_mods + , dep_trusted_pkgs_ = dep_trusted_pkgs + , dep_boot_mods_ = dep_boot_mods + , dep_orphs_ = dep_orphs + , dep_finsts_ = dep_finsts} +{-# COMPLETE Dependencies #-} + instance NFData Dependencies where rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) = rnf dmods @@ -158,14 +180,14 @@ mkDependencies home_unit mod imports plugin_mods = sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports - in Deps { dep_direct_mods = direct_mods - , dep_direct_pkgs = direct_pkgs - , dep_plugin_pkgs = plugin_units - , dep_sig_mods = sort sig_mods - , dep_trusted_pkgs = trust_pkgs - , dep_boot_mods = source_mods - , dep_orphs = sortBy stableModuleCmp dep_orphs - , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) + in Deps { dep_direct_mods_ = direct_mods + , dep_direct_pkgs_ = direct_pkgs + , dep_plugin_pkgs_ = plugin_units + , dep_sig_mods_ = sort sig_mods + , dep_trusted_pkgs_ = trust_pkgs + , dep_boot_mods_ = source_mods + , dep_orphs_ = sortBy stableModuleCmp dep_orphs + , dep_finsts_ = sortBy stableModuleCmp (imp_finsts imports) -- sort to get into canonical order -- NB. remember to use lexicographic ordering } @@ -174,14 +196,13 @@ mkDependencies home_unit mod imports plugin_mods = dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_orphs_update deps f = do r <- f (dep_orphs deps) - pure (deps { dep_orphs = sortBy stableModuleCmp r }) + pure (deps { dep_orphs_ = sortBy stableModuleCmp r }) -- | Update module dependencies containing family instances (used by Backpack) dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_finsts_update deps f = do r <- f (dep_finsts deps) - pure (deps { dep_finsts = sortBy stableModuleCmp r }) - + pure (deps { dep_finsts_ = sortBy stableModuleCmp r }) instance Binary Dependencies where put_ bh deps = do put_ bh (dep_direct_mods deps) @@ -201,36 +222,36 @@ instance Binary Dependencies where sms <- get bh os <- get bh fis <- get bh - return (Deps { dep_direct_mods = dms - , dep_direct_pkgs = dps - , dep_plugin_pkgs = plugin_pkgs - , dep_sig_mods = hsigms - , dep_boot_mods = sms - , dep_trusted_pkgs = tps - , dep_orphs = os, - dep_finsts = fis }) + return (Deps { dep_direct_mods_ = dms + , dep_direct_pkgs_ = dps + , dep_plugin_pkgs_ = plugin_pkgs + , dep_sig_mods_ = hsigms + , dep_boot_mods_ = sms + , dep_trusted_pkgs_ = tps + , dep_orphs_ = os, + dep_finsts_ = fis }) noDependencies :: Dependencies noDependencies = Deps - { dep_direct_mods = Set.empty - , dep_direct_pkgs = Set.empty - , dep_plugin_pkgs = Set.empty - , dep_sig_mods = [] - , dep_boot_mods = Set.empty - , dep_trusted_pkgs = Set.empty - , dep_orphs = [] - , dep_finsts = [] + { dep_direct_mods_ = Set.empty + , dep_direct_pkgs_ = Set.empty + , dep_plugin_pkgs_ = Set.empty + , dep_sig_mods_ = [] + , dep_boot_mods_ = Set.empty + , dep_trusted_pkgs_ = Set.empty + , dep_orphs_ = [] + , dep_finsts_ = [] } -- | Pretty-print unit dependencies pprDeps :: UnitState -> Dependencies -> SDoc -pprDeps unit_state (Deps { dep_direct_mods = dmods - , dep_boot_mods = bmods - , dep_plugin_pkgs = plgns - , dep_orphs = orphs - , dep_direct_pkgs = pkgs - , dep_trusted_pkgs = tps - , dep_finsts = finsts +pprDeps unit_state (Deps { dep_direct_mods_ = dmods + , dep_boot_mods_ = bmods + , dep_plugin_pkgs_ = plgns + , dep_orphs_ = orphs + , dep_direct_pkgs_ = pkgs + , dep_trusted_pkgs_ = tps + , dep_finsts_ = finsts }) = pprWithUnitState unit_state $ vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -11,18 +11,20 @@ module GHC.Unit.Module.ModIface ( ModIface , ModIface_ - ( mi_module + ( mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls , mi_defaults - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_top_env , mi_insts , mi_fam_insts @@ -31,12 +33,17 @@ module GHC.Unit.Module.ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn ) , pattern ModIface + , set_mi_mod_info , set_mi_module , set_mi_sig_of , set_mi_hsc_src @@ -52,24 +59,34 @@ module GHC.Unit.Module.ModIface , set_mi_rules , set_mi_decls , set_mi_defaults - , set_mi_extra_decls - , set_mi_foreign + , set_mi_simplified_core , set_mi_top_env , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches , set_mi_docs - , set_mi_final_exts + , set_mi_abi_hashes , set_mi_ext_fields + , set_mi_caches + , set_mi_decl_warn_fn + , set_mi_export_warn_fn + , set_mi_fix_fn + , set_mi_hash_fn , completePartialModIface , IfaceBinHandle(..) , PartialModIface - , ModIfaceBackend (..) - , ModIfaceSelfRecomp (..) + , IfaceAbiHashes (..) + , IfaceSelfRecomp (..) + , IfaceCache (..) + , IfaceSimplifiedCore (..) , withSelfRecomp , IfaceDeclExts - , IfaceBackendExts + , IfaceAbiHashesExts , IfaceExport + , IfacePublic_(..) + , IfacePublic + , PartialIfacePublic + , IfaceModInfo(..) , WhetherHasOrphans , WhetherHasFamInst , IfaceTopEnv (..) @@ -77,6 +94,7 @@ module GHC.Unit.Module.ModIface , mi_boot , mi_fix , mi_semantic_module + , mi_mod_info_semantic_module , mi_free_holes , mi_mnwib , mi_flag_hash @@ -85,6 +103,11 @@ module GHC.Unit.Module.ModIface , mi_plugin_hash , mi_src_hash , mi_usages + , mi_mod_hash + , mi_orphan + , mi_finsts + , mi_exp_hash + , mi_orphan_hash , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,7 +129,7 @@ import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings -import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..)) import GHC.Types.Avail @@ -147,36 +170,36 @@ We can build a full interface file two ways: type PartialModIface = ModIface_ 'ModIfaceCore type ModIface = ModIface_ 'ModIfaceFinal --- | Extends a PartialModIface with information which is either: --- * Computed after codegen --- * Or computed just before writing the iface to disk. (Hashes) --- In order to fully instantiate it. -data ModIfaceBackend = ModIfaceBackend - { mi_mod_hash :: !Fingerprint +type PartialIfacePublic = IfacePublic_ 'ModIfaceCore +type IfacePublic = IfacePublic_ 'ModIfaceFinal + +-- | Extends a PartialModIface with hashes of the ABI. +-- +-- * The mi_mod_hash is the hash of the entire ABI +-- * THe other fields are more specific hashes of parts of the ABI +data IfaceAbiHashes = IfaceAbiHashes + { mi_abi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_orphan :: !WhetherHasOrphans + , mi_abi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans - , mi_finsts :: !WhetherHasFamInst + , mi_abi_finsts :: !WhetherHasFamInst -- ^ Whether this module has family instances. See Note [The type family -- instance consistency story]. - , mi_exp_hash :: !Fingerprint + , mi_abi_exp_hash :: !Fingerprint -- ^ Hash of export list - , mi_orphan_hash :: !Fingerprint + , mi_abi_orphan_hash :: !Fingerprint -- ^ Hash for orphan rules, class and family instances combined + -- NOT transitive + } - -- Cached environments for easy lookup. These are computed (lazily) from - -- other fields and are not put into the interface file. - -- Not really produced by the backend but there is no need to create them - -- any earlier. - , mi_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) +data IfaceCache = IfaceCache + { mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for declaration deprecations - , mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) + , mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for export deprecations - , mi_fix_fn :: !(OccName -> Maybe Fixity) + , mi_cache_fix_fn :: !(OccName -> Maybe Fixity) -- ^ Cached lookup for 'mi_fixities' - , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) + , mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that -- the thing isn't in decls. It's useful to know that when seeing if we are -- up to date wrt. the old interface. The 'OccName' is the parent of the @@ -195,9 +218,9 @@ type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where IfaceDeclExts 'ModIfaceCore = IfaceDecl IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) -type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where - IfaceBackendExts 'ModIfaceCore = () - IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend +type family IfaceAbiHashesExts (phase :: ModIfacePhase) = bk | bk -> phase where + IfaceAbiHashesExts 'ModIfaceCore = () + IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes -- | In-memory byte array representation of a 'ModIface'. -- @@ -212,7 +235,7 @@ data IfaceBinHandle (phase :: ModIfacePhase) where FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp :: ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r withSelfRecomp iface nk jk = case mi_self_recomp_info iface of Nothing -> nk @@ -220,34 +243,80 @@ withSelfRecomp iface nk jk = --- | A 'ModIface' plus a 'ModDetails' summarises everything we know --- about a compiled module. The 'ModIface' is the stuff *before* linking, --- and can be written out to an interface file. The 'ModDetails is after --- linking and can be completely recovered from just the 'ModIface'. +-- | A 'ModIface' summarises everything we know +-- about a compiled module. -- --- When we read an interface file, we also construct a 'ModIface' from it, --- except that we explicitly make the 'mi_decls' and a few other fields empty; --- as when reading we consolidate the declarations etc. into a number of indexed --- maps and environments in the 'ExternalPackageState'. +-- See Note [Structure of ModIface] for information about what belongs in each field. -- --- See Note [Strictness in ModIface] to learn about why some fields are --- strict and others are not. +-- See Note [Strictness in ModIface] to learn about why all the fields are lazy. -- -- See Note [Private fields in ModIface] to learn why we don't export any of the -- fields. data ModIface_ (phase :: ModIfacePhase) = PrivateModIface { - mi_module_ :: !Module, -- ^ Name of the module we are for - mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? + mi_hi_bytes_ :: !(IfaceBinHandle phase), + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. + mi_iface_hash_ :: Fingerprint, -- A hash of the whole interface - mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? + mi_mod_info_ :: IfaceModInfo, + -- ^ Meta information about the module the interface file is for mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) + -- MP: Needs to be refactored (#25844) + + mi_public_ :: IfacePublic_ phase, + -- ^ The parts of interface which are used by other modules when + -- importing this module. The main, original part of an interface. - mi_exports_ :: ![IfaceExport], + + mi_self_recomp_ :: Maybe IfaceSelfRecomp, + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] + + mi_simplified_core_ :: Maybe IfaceSimplifiedCore, + -- ^ The part of the interface written when `-fwrite-if-simplified-core` is enabled. + -- These parts are used to restart bytecode generation. + + mi_docs_ :: Maybe Docs, + -- ^ Docstrings and related data for use by haddock, the ghci + -- @:doc@ command, and other tools. + -- + -- @Just _@ @<=>@ the module was built with @-haddock at . + + mi_top_env_ :: IfaceTopEnv, + -- ^ Just enough information to reconstruct the top level environment in + -- the /original source/ code for this module. which + -- is NOT the same as mi_exports, nor mi_decls (which + -- may contains declarations for things not actually + -- defined by the user). Used for GHCi and for inspecting + -- the contents of modules via the GHC API only. + + mi_ext_fields_ :: ExtensibleFields + -- ^ Additional optional fields, where the Map key represents + -- the field name, resulting in a (size, serialized data) pair. + -- Because the data is intended to be serialized through the + -- internal `Binary` class (increasing compatibility with types + -- using `Name` and `FastString`, such as HIE), this format is + -- chosen over `ByteString`s. + } + +-- | Meta information about the module the interface file is for +data IfaceModInfo = IfaceModInfo { + mi_mod_info_module :: Module, -- ^ Name of the module we are for + mi_mod_info_sig_of :: Maybe Module, -- ^ Are we a sig of another mod? + mi_mod_info_hsc_src :: HscSource -- ^ Boot? Signature? +} + +-- | The public interface of a module which are used by other modules when importing this module. +-- The ABI of a module. +data IfacePublic_ phase = IfacePublic { + mi_exports_ :: [IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things @@ -273,25 +342,10 @@ data ModIface_ (phase :: ModIfacePhase) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], - -- ^ Extra variable definitions which are **NOT** exposed but when - -- combined with mi_decls allows us to restart code generation. - -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - - mi_foreign_ :: !IfaceForeign, - -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. - -- See Note [Foreign stubs and TH bytecode linking] mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: IfaceTopEnv, - -- ^ Just enough information to reconstruct the top level environment in - -- the /original source/ code for this module. which - -- is NOT the same as mi_exports, nor mi_decls (which - -- may contains declarations for things not actually - -- defined by the user). Used for GHCi and for inspecting - -- the contents of modules via the GHC API only. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -299,53 +353,81 @@ data ModIface_ (phase :: ModIfacePhase) mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_trust_ :: !IfaceTrustInfo, + mi_trust_ :: IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg_ :: !Bool, + mi_trust_pkg_ :: Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches_ :: ![IfaceCompleteMatch], + mi_complete_matches_ :: [IfaceCompleteMatch], + -- ^ {-# COMPLETE #-} declarations - mi_docs_ :: !(Maybe Docs), - -- ^ Docstrings and related data for use by haddock, the ghci - -- @:doc@ command, and other tools. - -- - -- @Just _@ @<=>@ the module was built with @-haddock at . + mi_caches_ :: IfaceCache, + -- ^ Cached lookups of some parts of mi_public - mi_final_exts_ :: !(IfaceBackendExts phase), - -- ^ Either `()` or `ModIfaceBackend` for + mi_abi_hashes_ :: (IfaceAbiHashesExts phase) + -- ^ Either `()` or `IfaceAbiHashes` for -- a fully instantiated interface. - - mi_ext_fields_ :: !ExtensibleFields, - -- ^ Additional optional fields, where the Map key represents - -- the field name, resulting in a (size, serialized data) pair. - -- Because the data is intended to be serialized through the - -- internal `Binary` class (increasing compatibility with types - -- using `Name` and `FastString`, such as HIE), this format is - -- chosen over `ByteString`s. - -- - - mi_hi_bytes_ :: !(IfaceBinHandle phase), - -- ^ A serialised in-memory buffer of this 'ModIface'. - -- If this handle is given, we can avoid serialising the 'ModIface' - -- when writing this 'ModIface' to disk, and write this buffer to disk instead. - -- See Note [Sharing of ModIface]. - - mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) - -- ^ Information needed for checking self-recompilation. - -- See Note [Self recompilation information in interface files] - } + -- These fields are hashes of different parts of the public interface. +} + +mkIfacePublic :: [IfaceExport] + -> [IfaceDeclExts 'ModIfaceFinal] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDefault] + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> IfaceAbiHashes + -> IfacePublic +mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes = IfacePublic { + mi_exports_ = exports, + mi_decls_ = decls, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_defaults_ = defaults, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, + mi_cache_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, + mi_cache_fix_fn = mkIfaceFixCache fixities, + mi_cache_hash_fn = mkIfaceHashCache decls + }, + mi_abi_hashes_ = abi_hashes +} + +-- | The information needed to restart bytecode generation. +-- Enabled by `-fwrite-if-simplified-core`. +data IfaceSimplifiedCore = IfaceSimplifiedCore { + mi_sc_extra_decls :: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -- ^ Extra variable definitions which are **NOT** exposed but when + -- combined with mi_decls allows us to restart code generation. + -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] + , mi_sc_foreign :: IfaceForeign + -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. + -- See Note [Foreign stubs and TH bytecode linking] +} -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff - , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module + { ifaceTopExports :: DetOrdAvails -- ^ all top level things in this module, including unexported stuff + , ifaceImports :: [IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where @@ -362,6 +444,35 @@ instance Binary IfaceTopEnv where {- +Note [Structure of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The ModIface structure is divided into several logical parts: + +1. mi_mod_info: Basic module metadata (name, version, etc.) + +2. mi_public: The public interface of the module, which includes: + - Exports, declarations, fixities, warnings, annotations + - Class and type family instances + - Rewrite rules and COMPLETE pragmas + - Safe Haskell and package trust information + - ABI hashes for recompilation checking + +4. mi_self_recomp: Information needed for self-recompilation checking + (see Note [Self recompilation information in interface files]) + +5. mi_simplified_core: Optional simplified Core for bytecode generation + (only present when -fwrite-if-simplified-core is enabled) + +6. mi_docs: Optional documentation (only present when -haddock is enabled) + +7. mi_top_env: Information about the top-level environment of the original source + +8. mi_ext_fields: Additional fields for extensibility + +This structure helps organize the interface data according to its purpose and usage +patterns. Different parts of the compiler use different fields. By separating them +logically in the interface we can arrange to only deserialize the fields that are needed. + Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -371,7 +482,7 @@ The ModIface is the Haskell representation of an interface (.hi) file. that we have just compiled * For packages that we depend on we load the ModIface from disk. -Some fields in the ModIface are deliberately lazy because when we read +All fields in the ModIface are deliberately lazy because when we read an interface file we don't always need all the parts. For example, an interface file contains information about documentation which is often not needed during compilation. This is achieved using the lazyPut/lazyGet pair. @@ -384,23 +495,43 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) -mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ +mi_flag_hash :: ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags) +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint -mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_ mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint -mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_ mi_src_hash :: ModIface_ phase -> Maybe Fingerprint -mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_ mi_usages :: ModIface_ phase -> Maybe [Usage] -mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ +mi_usages = fmap mi_sr_usages . mi_self_recomp_ mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint -mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_ + +-- | Accessor for the module hash of the ABI from a ModIface. +mi_mod_hash :: ModIface -> Fingerprint +mi_mod_hash iface = mi_abi_mod_hash (mi_abi_hashes iface) + +-- | Accessor for whether this module has orphans from a ModIface. +mi_orphan :: ModIface -> WhetherHasOrphans +mi_orphan iface = mi_abi_orphan (mi_abi_hashes iface) + +-- | Accessor for whether this module has family instances from a ModIface. +mi_finsts :: ModIface -> WhetherHasFamInst +mi_finsts iface = mi_abi_finsts (mi_abi_hashes iface) + +-- | Accessor for the hash of the export list from a ModIface. +mi_exp_hash :: ModIface -> Fingerprint +mi_exp_hash iface = mi_abi_exp_hash (mi_abi_hashes iface) + +-- | Accessor for the hash of orphan rules, class and family instances combined from a ModIface. +mi_orphan_hash :: ModIface -> Fingerprint +mi_orphan_hash iface = mi_abi_orphan_hash (mi_abi_hashes iface) -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. @@ -415,16 +546,19 @@ mi_mnwib iface = GWIB (moduleName $ mi_module iface) (mi_boot iface) -- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be -- found, 'defaultFixity' is returned instead. mi_fix :: ModIface -> OccName -> Fixity -mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity +mi_fix iface name = mi_fix_fn iface name `orElse` defaultFixity -- | The semantic module for this interface; e.g., if it's a interface -- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module' -- will be @<A>@. -mi_semantic_module :: ModIface_ a -> Module -mi_semantic_module iface = case mi_sig_of iface of - Nothing -> mi_module iface +mi_mod_info_semantic_module :: IfaceModInfo -> Module +mi_mod_info_semantic_module iface = case mi_mod_info_sig_of iface of + Nothing -> mi_mod_info_module iface Just mod -> mod +mi_semantic_module :: ModIface_ a -> Module +mi_semantic_module iface = mi_mod_info_semantic_module (mi_mod_info iface) + -- | The "precise" free holes, e.g., the signatures that this -- 'ModIface' depends on. mi_free_holes :: ModIface -> UniqDSet ModuleName @@ -455,191 +589,229 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + put_ bh (PrivateModIface + { mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then -- we likely have a good reason, and do not want to reuse -- the byte array. -- See Note [Private fields in ModIface] + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_anns_ = anns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - mi_complete_matches_ = complete_matches, + mi_public_ = public, mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_self_recomp_info_ = self_recomp, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash - }}) = do - put_ bh mod - put_ bh sig_of - put_ bh hsc_src - put_ bh self_recomp - put_ bh mod_hash + mi_self_recomp_ = self_recomp, + mi_simplified_core_ = simplified_core + }) = do + put_ bh mod_info put_ bh iface_hash - put_ bh orphan - put_ bh hasFamInsts lazyPut bh deps - put_ bh exports - put_ bh exp_hash - put_ bh fixities - lazyPut bh warns - lazyPut bh anns - put_ bh decls - put_ bh extra_decls - put_ bh defaults - put_ bh foreign_ - put_ bh insts - put_ bh fam_insts - lazyPut bh rules - put_ bh orphan_hash - put_ bh trust - put_ bh trust_pkg - put_ bh complete_matches + lazyPut bh public lazyPut bh top_env lazyPutMaybe bh docs + lazyPutMaybe bh self_recomp + lazyPutMaybe bh simplified_core get bh = do - mod <- get bh - sig_of <- get bh - hsc_src <- get bh - self_recomp_info <- get bh - mod_hash <- get bh + mod_info <- get bh iface_hash <- get bh - orphan <- get bh - hasFamInsts <- get bh deps <- lazyGet bh - exports <- {-# SCC "bin_exports" #-} get bh - exp_hash <- get bh - fixities <- {-# SCC "bin_fixities" #-} get bh - warns <- {-# SCC "bin_warns" #-} lazyGet bh - anns <- {-# SCC "bin_anns" #-} lazyGet bh - decls <- {-# SCC "bin_tycldecls" #-} get bh - extra_decls <- get bh - defaults <- get bh - foreign_ <- get bh - insts <- {-# SCC "bin_insts" #-} get bh - fam_insts <- {-# SCC "bin_fam_insts" #-} get bh - rules <- {-# SCC "bin_rules" #-} lazyGet bh - orphan_hash <- get bh - trust <- get bh - trust_pkg <- get bh - complete_matches <- get bh + public <- lazyGet bh top_env <- lazyGet bh docs <- lazyGetMaybe bh + self_recomp <- lazyGetMaybe bh + simplified_core <- lazyGetMaybe bh + return (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = - -- We can't populate this field here, as we are - -- missing the 'mi_ext_fields_' field, which is - -- handled in 'getIfaceWithExtFields'. - FullIfaceBinHandle Strict.Nothing, + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_anns_ = anns, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - -- And build the cached values - mi_complete_matches_ = complete_matches, + mi_public_ = public, + mi_simplified_core_ = simplified_core, mi_docs_ = docs, mi_top_env_ = top_env, - mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt - -- with specially when the file is read - mi_self_recomp_info_ = self_recomp_info, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash, - mi_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, - mi_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, - mi_fix_fn = mkIfaceFixCache fixities, - mi_hash_fn = mkIfaceHashCache decls - }}) + mi_self_recomp_ = self_recomp, + -- placeholder because this is dealt + -- with specially when the file is read + mi_ext_fields_ = emptyExtensibleFields, + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + }) + +instance Binary IfaceModInfo where + put_ bh (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) = do + put_ bh mod + put_ bh sig_of + put_ bh hsc_src + get bh = do + mod <- get bh + sig_of <- get bh + hsc_src <- get bh + return (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) + + +instance Binary (IfacePublic_ 'ModIfaceFinal) where + put_ bh (IfacePublic { mi_exports_ = exports + , mi_decls_ = decls + , mi_fixities_ = fixities + , mi_warns_ = warns + , mi_anns_ = anns + , mi_defaults_ = defaults + , mi_insts_ = insts + , mi_fam_insts_ = fam_insts + , mi_rules_ = rules + , mi_trust_ = trust + , mi_trust_pkg_ = trust_pkg + , mi_complete_matches_ = complete_matches + , mi_abi_hashes_ = abi_hashes + }) = do + + lazyPut bh exports + lazyPut bh decls + lazyPut bh fixities + lazyPut bh warns + lazyPut bh anns + lazyPut bh defaults + lazyPut bh insts + lazyPut bh fam_insts + lazyPut bh rules + lazyPut bh trust + lazyPut bh trust_pkg + lazyPut bh complete_matches + lazyPut bh abi_hashes + + get bh = do + exports <- lazyGet bh + decls <- lazyGet bh + fixities <- lazyGet bh + warns <- lazyGet bh + anns <- lazyGet bh + defaults <- lazyGet bh + insts <- lazyGet bh + fam_insts <- lazyGet bh + rules <- lazyGet bh + trust <- lazyGet bh + trust_pkg <- lazyGet bh + complete_matches <- lazyGet bh + abi_hashes <- lazyGet bh + return (mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes) + +instance Binary IfaceAbiHashes where + put_ bh (IfaceAbiHashes { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = orphan + , mi_abi_finsts = hasFamInsts + , mi_abi_exp_hash = exp_hash + , mi_abi_orphan_hash = orphan_hash + }) = do + put_ bh mod_hash + put_ bh orphan + put_ bh hasFamInsts + put_ bh exp_hash + put_ bh orphan_hash + get bh = do + mod_hash <- get bh + orphan <- get bh + hasFamInsts <- get bh + exp_hash <- get bh + orphan_hash <- get bh + return $ IfaceAbiHashes { + mi_abi_mod_hash = mod_hash, + mi_abi_orphan = orphan, + mi_abi_finsts = hasFamInsts, + mi_abi_exp_hash = exp_hash, + mi_abi_orphan_hash = orphan_hash + } + +instance Binary IfaceSimplifiedCore where + put_ bh (IfaceSimplifiedCore eds fs) = do + put_ bh eds + put_ bh fs + + get bh = do + eds <- get bh + fs <- get bh + return (IfaceSimplifiedCore eds fs) emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface - { mi_module_ = mod, - mi_sig_of_ = Nothing, - mi_hsc_src_ = HsSrcFile, + { mi_mod_info_ = emptyIfaceModInfo mod, + mi_iface_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_exports_ = [], - mi_fixities_ = [], - mi_warns_ = IfWarnSome [] [], - mi_anns_ = [], - mi_defaults_ = [], - mi_insts_ = [], - mi_fam_insts_ = [], - mi_rules_ = [], - mi_decls_ = [], - mi_extra_decls_ = Nothing, - mi_foreign_ = emptyIfaceForeign, + mi_public_ = emptyPublicModIface (), + mi_simplified_core_ = Nothing, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_trust_ = noIfaceTrustInfo, - mi_trust_pkg_ = False, - mi_complete_matches_ = [], mi_docs_ = Nothing, - mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields, - mi_self_recomp_info_ = Nothing + mi_self_recomp_ = Nothing, + mi_ext_fields_ = emptyExtensibleFields + } +emptyIfaceModInfo :: Module -> IfaceModInfo +emptyIfaceModInfo mod = IfaceModInfo + { mi_mod_info_module = mod + , mi_mod_info_sig_of = Nothing + , mi_mod_info_hsc_src = HsSrcFile + } + + +emptyPublicModIface :: IfaceAbiHashesExts phase -> IfacePublic_ phase +emptyPublicModIface abi_hashes = IfacePublic + { mi_exports_ = [] + , mi_decls_ = [] + , mi_fixities_ = [] + , mi_warns_ = IfWarnSome [] [] + , mi_anns_ = [] + , mi_defaults_ = [] + , mi_insts_ = [] + , mi_fam_insts_ = [] + , mi_rules_ = [] + , mi_abi_hashes_ = abi_hashes + , mi_trust_ = noIfaceTrustInfo + , mi_trust_pkg_ = False + , mi_caches_ = emptyModIfaceCache + , mi_complete_matches_ = [] + } + +emptyModIfaceCache :: IfaceCache +emptyModIfaceCache = IfaceCache { + mi_cache_decl_warn_fn = emptyIfaceWarnCache, + mi_cache_export_warn_fn = emptyIfaceWarnCache, + mi_cache_fix_fn = emptyIfaceFixCache, + mi_cache_hash_fn = emptyIfaceHashCache +} + +emptyIfaceBackend :: IfaceAbiHashes +emptyIfaceBackend = IfaceAbiHashes + { mi_abi_mod_hash = fingerprint0, + mi_abi_orphan = False, + mi_abi_finsts = False, + mi_abi_exp_hash = fingerprint0, + mi_abi_orphan_hash = fingerprint0 + } + emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls_ = [] - , mi_self_recomp_info_ = Nothing + { mi_public_ = emptyPublicModIface emptyIfaceBackend , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing - , mi_final_exts_ = ModIfaceBackend - { mi_mod_hash = fingerprint0, - mi_iface_hash = fingerprint0, - mi_orphan = False, - mi_finsts = False, - mi_exp_hash = fingerprint0, - mi_orphan_hash = fingerprint0, - mi_decl_warn_fn = emptyIfaceWarnCache, - mi_export_warn_fn = emptyIfaceWarnCache, - mi_fix_fn = emptyIfaceFixCache, - mi_hash_fn = emptyIfaceHashCache } } + } + -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface' mkIfaceHashCache :: [(Fingerprint,IfaceDecl)] @@ -657,11 +829,11 @@ emptyIfaceHashCache _occ = Nothing -- ModIface is completely forced since it will live in memory for a long time. -- If forcing it uses a lot of memory, then store less things in ModIface. -instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) +instance ( NFData (IfaceAbiHashesExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) - = rnf a1 + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = (a1 :: IfaceBinHandle phase) `seq` rnf a2 `seq` rnf a3 `seq` rnf a4 @@ -671,24 +843,27 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 - `seq` rnf a11 - `seq` rnf a12 - `seq` rnf a13 - `seq` rnf a14 - `seq` rnf a15 - `seq` rnf a16 - `seq` rnf a17 - `seq` rnf a18 - `seq` rnf a19 - `seq` rnf a20 - `seq` rnf a21 - `seq` rnf a22 - -- IfaceBinHandle - `seq` (a23 :: IfaceBinHandle phase) - `seq` rnf a24 - -instance NFData ModIfaceBackend where - rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + +instance NFData IfaceModInfo where + rnf (IfaceModInfo a1 a2 a3) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + + +instance NFData IfaceSimplifiedCore where + rnf (IfaceSimplifiedCore eds fs) = rnf eds `seq` rnf fs + +instance NFData IfaceAbiHashes where + rnf (IfaceAbiHashes a1 a2 a3 a4 a5) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + +instance (NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) where + rnf (IfacePublic a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = rnf a1 `seq` rnf a2 `seq` rnf a3 @@ -699,6 +874,18 @@ instance NFData ModIfaceBackend where `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +instance NFData IfaceCache where + rnf (IfaceCache a1 a2 a3 a4) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + forceModIface :: ModIface -> IO () @@ -745,28 +932,38 @@ to serialise the 'ModIface' to disk again. -- | Given a 'PartialModIface', turn it into a 'ModIface' by completing -- missing fields. completePartialModIface :: PartialModIface + -> Fingerprint -> [(Fingerprint, IfaceDecl)] - -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - -> ModIfaceBackend + -> Maybe IfaceSimplifiedCore + -> IfaceAbiHashes + -> IfaceCache -> ModIface -completePartialModIface partial decls extra_decls final_exts = partial - { mi_decls_ = decls - , mi_extra_decls_ = extra_decls - , mi_final_exts_ = final_exts +completePartialModIface partial iface_hash decls extra_decls final_exts cache = partial + { mi_public_ = completePublicModIface decls final_exts cache (mi_public_ partial) + , mi_simplified_core_ = extra_decls , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_iface_hash_ = iface_hash } + where -set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase -set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } - -set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase -set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } +-- | Given a 'PartialIfacePublic', turn it into an 'IfacePublic' by completing +-- missing fields. +completePublicModIface :: [(Fingerprint, IfaceDecl)] + -> IfaceAbiHashes + -> IfaceCache + -> PartialIfacePublic + -> IfacePublic +completePublicModIface decls abi_hashes cache partial = partial + { mi_decls_ = decls + , mi_abi_hashes_ = abi_hashes + , mi_caches_ = cache + } -set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase -set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } +set_mi_mod_info :: IfaceModInfo -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info val iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = val } -set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase -set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } +set_mi_self_recomp :: Maybe IfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -774,59 +971,100 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } +set_mi_public :: (IfacePublic_ phase -> IfacePublic_ phase) -> ModIface_ phase -> ModIface_ phase +set_mi_public f iface = clear_mi_hi_bytes $ iface { mi_public_ = f (mi_public_ iface) } + +set_mi_simplified_core :: Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase +set_mi_simplified_core val iface = clear_mi_hi_bytes $ iface { mi_simplified_core_ = val } + +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +{- Settings for mi_public interface fields -} + set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase -set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } +set_mi_exports val = set_mi_public (\iface -> iface { mi_exports_ = val }) set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase -set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } +set_mi_fixities val = set_mi_public (\iface -> iface { mi_fixities_ = val }) set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase -set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } +set_mi_warns val = set_mi_public (\iface -> iface { mi_warns_ = val }) set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase -set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } +set_mi_anns val = set_mi_public (\iface -> iface { mi_anns_ = val }) set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase -set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } +set_mi_insts val = set_mi_public (\iface -> iface { mi_insts_ = val }) set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase -set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } +set_mi_fam_insts val = set_mi_public (\iface -> iface { mi_fam_insts_ = val }) set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase -set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } +set_mi_rules val = set_mi_public (\iface -> iface { mi_rules_ = val }) set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase -set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } +set_mi_decls val = set_mi_public (\iface -> iface { mi_decls_ = val }) set_mi_defaults :: [IfaceDefault] -> ModIface_ phase -> ModIface_ phase -set_mi_defaults val iface = clear_mi_hi_bytes $ iface { mi_defaults_ = val } - -set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase -set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } - -set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase -set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } - -set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase -set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } +set_mi_defaults val = set_mi_public (\iface -> iface { mi_defaults_ = val }) set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase -set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } +set_mi_trust val = set_mi_public (\iface -> iface { mi_trust_ = val }) set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase -set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } +set_mi_trust_pkg val = set_mi_public (\iface -> iface { mi_trust_pkg_ = val }) set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase -set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } +set_mi_complete_matches val = set_mi_public (\iface -> iface { mi_complete_matches_ = val }) + +set_mi_abi_hashes :: IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_abi_hashes val = set_mi_public (\iface -> iface { mi_abi_hashes_ = val }) + +{- Setters for mi_caches interface fields -} + +set_mi_decl_warn_fn :: (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_decl_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_decl_warn_fn = val } }) + +set_mi_export_warn_fn :: (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_export_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_export_warn_fn = val } }) + +set_mi_fix_fn :: (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase +set_mi_fix_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_fix_fn = val } }) + +set_mi_hash_fn :: (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase +set_mi_hash_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_hash_fn = val } }) + +set_mi_caches :: IfaceCache -> ModIface_ phase -> ModIface_ phase +set_mi_caches val = set_mi_public (\iface -> iface { mi_caches_ = val }) + +{- + +-} + +{- Setters for mi_mod_info interface fields -} + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val = set_mi_mod_info_field (\info -> info { mi_mod_info_module = val }) + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val = set_mi_mod_info_field (\info -> info { mi_mod_info_sig_of = val }) + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val = set_mi_mod_info_field (\info -> info { mi_mod_info_hsc_src = val }) + +-- | Helper function for setting fields in mi_mod_info_ +set_mi_mod_info_field :: (IfaceModInfo -> IfaceModInfo) -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info_field f iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = f (mi_mod_info_ iface) } -set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase -set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } -set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase -set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } -set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase -set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } -- | Invalidate any byte array buffer we might have. clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase @@ -887,18 +1125,20 @@ However, with the pragma, the correct core is generated: -- See Note [Inline Pattern synonym of ModIface] for why we have all these -- inline pragmas. -{-# INLINE ModIface #-} +{-# INLINE mi_mod_info #-} +{-# INLINE mi_iface_hash #-} {-# INLINE mi_module #-} {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} +{-# INLINE mi_public #-} {-# INLINE mi_exports #-} {-# INLINE mi_fixities #-} {-# INLINE mi_warns #-} {-# INLINE mi_anns #-} {-# INLINE mi_decls #-} -{-# INLINE mi_extra_decls #-} -{-# INLINE mi_foreign #-} +{-# INLINE mi_simplified_core #-} +{-# INLINE mi_defaults #-} {-# INLINE mi_top_env #-} {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} @@ -907,32 +1147,63 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} {-# INLINE mi_docs #-} -{-# INLINE mi_final_exts #-} +{-# INLINE mi_abi_hashes #-} {-# INLINE mi_ext_fields #-} {-# INLINE mi_hi_bytes #-} +{-# INLINE mi_self_recomp_info #-} +{-# INLINE mi_fix_fn #-} +{-# INLINE mi_hash_fn #-} +{-# INLINE mi_decl_warn_fn #-} +{-# INLINE mi_export_warn_fn #-} +{-# INLINE ModIface #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> - [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> - [IfaceAnnotation] -> [IfaceDeclExts phase] -> - Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> + IfaceModInfo + -> Module + -> Maybe Module + -> HscSource + -> Fingerprint + -> Dependencies + -> IfacePublic_ phase + -> [IfaceExport] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDeclExts phase] + -> Maybe IfaceSimplifiedCore + -> [IfaceDefault] + -> IfaceTopEnv + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> Maybe Docs + -> IfaceAbiHashesExts phase + -> ExtensibleFields + -> IfaceBinHandle phase + -> Maybe IfaceSelfRecomp + -> (OccName -> Maybe Fixity) + -> (OccName -> Maybe (OccName, Fingerprint)) + -> (OccName -> Maybe (WarningTxt GhcRn)) + -> (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase pattern ModIface - { mi_module + { mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_defaults , mi_top_env , mi_insts @@ -942,33 +1213,45 @@ pattern ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_hash_fn + , mi_decl_warn_fn + , mi_export_warn_fn } <- PrivateModIface - { mi_module_ = mi_module - , mi_sig_of_ = mi_sig_of - , mi_hsc_src_ = mi_hsc_src + { mi_mod_info_ = mi_mod_info at IfaceModInfo { mi_mod_info_module = mi_module + , mi_mod_info_sig_of = mi_sig_of + , mi_mod_info_hsc_src = mi_hsc_src } + , mi_iface_hash_ = mi_iface_hash , mi_deps_ = mi_deps - , mi_exports_ = mi_exports - , mi_fixities_ = mi_fixities - , mi_warns_ = mi_warns - , mi_anns_ = mi_anns - , mi_decls_ = mi_decls - , mi_extra_decls_ = mi_extra_decls - , mi_foreign_ = mi_foreign - , mi_defaults_ = mi_defaults - , mi_top_env_ = mi_top_env - , mi_insts_ = mi_insts - , mi_fam_insts_ = mi_fam_insts - , mi_rules_ = mi_rules - , mi_trust_ = mi_trust - , mi_trust_pkg_ = mi_trust_pkg - , mi_complete_matches_ = mi_complete_matches + , mi_public_ = mi_public at IfacePublic { + mi_exports_ = mi_exports + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_defaults_ = mi_defaults + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mi_decl_warn_fn, + mi_cache_export_warn_fn = mi_export_warn_fn, + mi_cache_fix_fn = mi_fix_fn, + mi_cache_hash_fn = mi_hash_fn + } + , mi_abi_hashes_ = mi_abi_hashes + } , mi_docs_ = mi_docs - , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields , mi_hi_bytes_ = mi_hi_bytes - , mi_self_recomp_info_ = mi_self_recomp_info + , mi_self_recomp_ = mi_self_recomp_info + , mi_simplified_core_ = mi_simplified_core + , mi_top_env_ = mi_top_env } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -107,6 +107,9 @@ module GHC.Utils.Binary simpleBindingNameReader, FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, BinArray, + + -- * FingerprintWithValue + FingerprintWithValue(..) ) where import GHC.Prelude @@ -135,6 +138,7 @@ import Data.ByteString (ByteString, copy) import Data.Coerce import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS +import qualified Data.ByteString.Short.Internal as SBS import Data.IORef import Data.Char ( ord, chr ) import Data.List.NonEmpty ( NonEmpty(..)) @@ -1771,7 +1775,7 @@ type SymbolTable a = Array Int a --------------------------------------------------------- putFS :: WriteBinHandle -> FastString -> IO () -putFS bh fs = putBS bh $ bytesFS fs +putFS bh fs = putSBS bh $ fastStringToShortByteString fs getFS :: ReadBinHandle -> IO FastString getFS bh = do @@ -1791,6 +1795,18 @@ getByteString bh l = BS.create l $ \dest -> do getPrim bh l (\src -> copyBytes dest src l) +putSBS :: WriteBinHandle -> SBS.ShortByteString -> IO () +putSBS bh sbs = do + let l = SBS.length sbs + put_ bh l + putPrim bh l (\p -> SBS.copyToPtr sbs 0 p l) + + +getSBS :: ReadBinHandle -> IO SBS.ShortByteString +getSBS bh = do + l <- get bh :: IO Int + getPrim bh l (\src -> SBS.createFromPtr src l) + putBS :: WriteBinHandle -> ByteString -> IO () putBS bh bs = BS.unsafeUseAsCStringLen bs $ \(ptr, l) -> do @@ -1803,6 +1819,10 @@ getBS bh = do BS.create l $ \dest -> do getPrim bh l (\src -> copyBytes dest src l) +instance Binary SBS.ShortByteString where + put_ bh f = putSBS bh f + get bh = getSBS bh + instance Binary ByteString where put_ bh f = putBS bh f get bh = getBS bh @@ -2088,3 +2108,36 @@ source location as part of a larger structure. instance (Binary v) => Binary (IntMap v) where put_ bh m = put_ bh (IntMap.toAscList m) get bh = IntMap.fromAscList <$> get bh + + +{- Note [FingerprintWithValue] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +FingerprintWithValue is a wrapper which allows us to store a fingerprint and +optionally the value which was used to create the fingerprint. + +This is useful for storing information in interface files, where we want to +store the fingerprint of the interface file, but also the value which was used +to create the fingerprint (e.g. the DynFlags). + +The wrapper is useful to ensure that the fingerprint can be read quickly without +having to deserialise the value itself. +-} + +-- | A wrapper which allows us to store a fingerprint and optionally the value which +-- was used to create the fingerprint. +data FingerprintWithValue a = FingerprintWithValue !Fingerprint (Maybe a) + deriving Functor + +instance Binary a => Binary (FingerprintWithValue a) where + put_ bh (FingerprintWithValue fp val) = do + put_ bh fp + lazyPutMaybe bh val + + get bh = do + fp <- get bh + val <- lazyGetMaybe bh + return $ FingerprintWithValue fp val + +instance NFData a => NFData (FingerprintWithValue a) where + rnf (FingerprintWithValue fp mflags) + = rnf fp `seq` rnf mflags `seq` () \ No newline at end of file ===================================== ghc/Main.hs ===================================== @@ -1133,6 +1133,8 @@ abiHash strs = do mods <- mapM find_it strs + -- MP: loadUserInterface is inefficient here since we will never find a cached + -- interface. computeInterface is probably better. let get_iface modl = loadUserInterface NotBoot (text "abiHash") modl ifaces <- initIfaceCheck (text "abiHash") hsc_env $ mapM get_iface mods @@ -1140,7 +1142,7 @@ abiHash strs = do put_ bh hiVersion -- package hashes change when the compiler version changes (for now) -- see #5328 - mapM_ (put_ bh . mi_mod_hash . mi_final_exts) ifaces + mapM_ (put_ bh . mi_mod_hash) ifaces f <- fingerprintBinMem bh putStrLn (showPpr dflags f) ===================================== m4/fp_settings.m4 ===================================== @@ -89,7 +89,7 @@ AC_DEFUN([FP_SETTINGS], SettingsLlcCommand="$LlcCmd" SettingsOptCommand="$OptCmd" SettingsLlvmAsCommand="$LlvmAsCmd" - SettingsLlvmAsFlags="$LlvmAsCmd" + SettingsLlvmAsFlags="$LlvmAsFlags" if test "$EnableDistroToolchain" = "YES"; then # If the user specified --enable-distro-toolchain then we just use the ===================================== testsuite/tests/deriving/should_compile/T17324.stderr ===================================== @@ -1,4 +1,4 @@ - -T17324.hs:8:1: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] +T17324.hs:8:21: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] The import of ‘Dual, Product, Sum’ from module ‘Data.Monoid’ is redundant + ===================================== testsuite/tests/module/T11970A.stderr ===================================== @@ -1,5 +1,5 @@ [1 of 2] Compiling T11970A1 ( T11970A1.hs, T11970A1.o ) [2 of 2] Compiling T11970A ( T11970A.hs, T11970A.o ) - -T11970A.hs:3:1: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] +T11970A.hs:3:19: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] The import of ‘Fail(b)’ from module ‘T11970A1’ is redundant + ===================================== testsuite/tests/module/mod176.stderr ===================================== @@ -1,4 +1,4 @@ - -mod176.hs:4:1: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] +mod176.hs:4:23: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] The import of ‘Monad, return’ from module ‘Control.Monad’ is redundant + ===================================== testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr ===================================== @@ -1,5 +1,4 @@ [1 of 3] Compiling OverloadedRecFldsFail06_A ( OverloadedRecFldsFail06_A.hs, OverloadedRecFldsFail06_A.o ) - OverloadedRecFldsFail06_A.hs:9:15: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: data constructor ‘MkUnused’ @@ -8,9 +7,9 @@ OverloadedRecFldsFail06_A.hs:9:42: warning: [GHC-40910] [-Wunused-top-binds (in OverloadedRecFldsFail06_A.hs:9:59: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)] Defined but not used: record field of MkUnused ‘used_locally’ -[2 of 3] Compiling Main ( overloadedrecfldsfail06.hs, overloadedrecfldsfail06.o ) -overloadedrecfldsfail06.hs:7:1: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] +[2 of 3] Compiling Main ( overloadedrecfldsfail06.hs, overloadedrecfldsfail06.o ) +overloadedrecfldsfail06.hs:7:35: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] The import of ‘MkV, Unused, Unused(unused), V(x), U(y)’ from module ‘OverloadedRecFldsFail06_A’ is redundant @@ -19,11 +18,11 @@ overloadedrecfldsfail06.hs:8:1: error: [GHC-66111] [-Wunused-imports (in -Wextra except perhaps to import instances from ‘OverloadedRecFldsFail06_A’ To import instances alone, use: import OverloadedRecFldsFail06_A() -overloadedrecfldsfail06.hs:9:1: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] +overloadedrecfldsfail06.hs:9:50: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] The qualified import of ‘V(y)’ from module ‘OverloadedRecFldsFail06_A’ is redundant -overloadedrecfldsfail06.hs:10:1: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] +overloadedrecfldsfail06.hs:10:50: error: [GHC-38856] [-Wunused-imports (in -Wextra), Werror=unused-imports] The qualified import of ‘U, U(x)’ from module ‘OverloadedRecFldsFail06_A’ is redundant @@ -36,3 +35,4 @@ overloadedrecfldsfail06.hs:18:28: error: [GHC-02256] [-Wambiguous-fields (in -Wd Ambiguous record update with parent type constructor ‘V’. This type-directed disambiguation mechanism will not be supported by -XDuplicateRecordFields in future releases of GHC. Consider disambiguating using module qualification instead. + ===================================== testsuite/tests/rename/should_compile/T14881.stderr ===================================== @@ -1,6 +1,6 @@ [1 of 2] Compiling T14881Aux ( T14881Aux.hs, T14881Aux.o ) [2 of 2] Compiling T14881 ( T14881.hs, T14881.o ) - -T14881.hs:3:1: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] +T14881.hs:3:45: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] The qualified import of ‘adjust, length, L(tail), L(x)’ from module ‘T14881Aux’ is redundant + ===================================== testsuite/tests/rename/should_compile/T24035.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE DuplicateRecordFields #-} +module T24035 where +import T24035_aux (R1 (MkR1, ra), rb) + +x :: R1 -> Bool +x (MkR1 { rb = x0 }) = x0 + +y :: R1 -> Int +y (MkR1 { ra = y0 }) = y0 ===================================== testsuite/tests/rename/should_compile/T24035_aux.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE DuplicateRecordFields #-} +module T24035_aux (R1(..), R2(..)) where + +data R1 = MkR1 {ra :: Int, rb :: Bool} +data R2 = MkR2 {ra :: Int, rb :: Bool} ===================================== testsuite/tests/rename/should_compile/T24035b.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE DuplicateRecordFields #-} + +module T24035b where +import T24035_aux (R1 (MkR1, ra, rb), R2(rb)) + +x :: R1 -> Bool +x (MkR1 { rb = x0 }) = x0 + +y :: R1 -> Int +y (MkR1 { ra = y0 }) = y0 + +-- Use R2 to avoid unused import warning for R2 +useR2 :: R2 -> Int +useR2 _ = 42 ===================================== testsuite/tests/rename/should_compile/T24035b.stderr ===================================== @@ -0,0 +1,3 @@ +T24035b.hs:4:39: warning: [GHC-38856] [-Wunused-imports (in -Wextra)] + The import of ‘R2(rb)’ from module ‘T24035_aux’ is redundant + ===================================== testsuite/tests/rename/should_compile/all.T ===================================== @@ -210,6 +210,8 @@ test('T23434', normal, compile, ['']) test('T23510b', normal, compile, ['']) test('T23512b', normal, compile, ['']) test('T23664', normal, compile, ['']) +test('T24035', [extra_files(['T24035_aux.hs'])], multimod_compile, ['T24035', '-v0 -Wunused-imports']) +test('T24035b', [extra_files(['T24035_aux.hs'])], multimod_compile, ['T24035b', '-v0 -Wunused-imports']) test('T24037', normal, compile, ['']) test('T24084', [extra_files(['T24084_A.hs', 'T24084_B.hs'])], multimod_compile, ['T24084', '-v0']) test('ExportWarnings1', extra_files(['ExportWarnings_base.hs', 'ExportWarnings_aux.hs']), multimod_compile, ['ExportWarnings1', '-v0 -Wno-duplicate-exports -Wx-custom']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c3b770390fee5cc9c170e745b6c513a4aa67868b...a3794d93852aa1c6612c88e7288f32c8754f4f1f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c3b770390fee5cc9c170e745b6c513a4aa67868b...a3794d93852aa1c6612c88e7288f32c8754f4f1f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/e0c3878c/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 22:23:36 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Mar 2025 18:23:36 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] wibble Message-ID: <67d4ac68c5ac2_2f40ea6d71bc131c5@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: 5e0831bd by Simon Peyton Jones at 2025-03-14T22:23:20+00:00 wibble - - - - - 1 changed file: - compiler/GHC/Core/Opt/Simplify/Iteration.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -2252,7 +2252,7 @@ simplInId :: SimplEnv -> InId -> SimplCont -> SimplM (SimplFloats, OutExpr) simplInId env var cont | Just dc <- isDataConWorkId_maybe var , isLazyDataConRep dc -- See Note [Fast path for lazy data constructors] - = rebuild env (Var var) cont + = rebuild zapped_env (Var var) cont | otherwise = case substId env var of ContEx tvs cvs ids e -> simplExprF env' e cont @@ -2261,15 +2261,15 @@ simplInId env var cont where env' = setSubstEnv env tvs cvs ids - DoneId out_id -> simplOutId env' out_id cont' + DoneId out_id -> simplOutId zapped_env out_id cont' where - cont' = trimJoinCont var (idJoinPointHood var) cont - env' = zapSubstEnv env -- See Note [zapSubstEnv] + cont' = trimJoinCont out_id (idJoinPointHood out_id) cont - DoneEx e mb_join -> simplExprF env' e cont' + DoneEx e mb_join -> simplExprF zapped_env e cont' where cont' = trimJoinCont var mb_join cont - env' = zapSubstEnv env -- See Note [zapSubstEnv] + where + zapped_env = zapSubstEnv env -- See Note [zapSubstEnv] --------------------------------------------------------- simplOutId :: SimplEnvIS -> OutId -> SimplCont -> SimplM (SimplFloats, OutExpr) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e0831bd71a76c4cc89cbbbdec4dcd5ab2a4a043 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e0831bd71a76c4cc89cbbbdec4dcd5ab2a4a043 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/635ff0e3/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 23:04:18 2025 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Mar 2025 19:04:18 -0400 Subject: [Git][ghc/ghc][wip/romes/25170-idea4] Rewrite Notes Message-ID: <67d4b5f22f7da_30195043f1e83974f@gitlab.mail> Simon Peyton Jones pushed to branch wip/romes/25170-idea4 at Glasgow Haskell Compiler / GHC Commits: 927f71d1 by Simon Peyton Jones at 2025-03-14T23:03:18+00:00 Rewrite Notes - - - - - 3 changed files: - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/Specialise.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -2008,8 +2008,8 @@ So we go to some effort to avoid repeatedly simplifying the same thing: * We go to some efforts to avoid unnecessarily simplifying ApplyToVal, in at least two places - In simplCast/addCoerce, where we check for isReflCo - - In rebuildCall we avoid simplifying arguments before we have to - (see Note [Trying rewrite rules]) + - We sometimes try rewrite RULES befoe simplifying arguments; + see Note [Plan (BEFORE)] All that said /postInlineUnconditionally/ (called in `completeBind`) does fire in the above (f BIG) situation. See Note [Post-inline for single-use @@ -2325,7 +2325,7 @@ simplOutId env fun cont -- Normal case for (f e1 .. en) simplOutId env fun cont - = -- Try rewrite rules + = -- Try rewrite rules: Plan (BEFORE) in Note [When to apply rewrite rules] do { rule_base <- getSimplRules ; let rules_for_me = getRules rule_base fun out_args = contOutArgs env cont :: [OutExpr] @@ -2422,7 +2422,7 @@ rebuildCall env fun_info rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) cont | null rules = rebuild env (argInfoExpr fun rev_args) cont - | otherwise -- Try rules again + | otherwise -- Try rules again: Plan (AFTER) in Note [When to apply rewrite rules] = do { let args = reverse rev_args ; mb_match <- tryRules env rules fun (map argSpecArg args) ; case mb_match of @@ -2462,83 +2462,90 @@ tryInlining env logger var cont text "Cont: " <+> ppr cont])] -{- Note [Trying rewrite rules] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Consider an application (f e1 e2 e3) where the e1,e2,e3 are not yet -simplified. We want to simplify enough arguments to allow the rules -to apply, but it's more efficient to avoid simplifying e2,e3 if e1 alone -is sufficient. Example: class ops - (+) dNumInt e2 e3 -If we rewrite ((+) dNumInt) to plusInt, we can take advantage of the -latter's strictness when simplifying e2, e3. Moreover, suppose we have - RULE f Int = \x. x True - -Then given (f Int e1) we rewrite to - (\x. x True) e1 -without simplifying e1. Now we can inline x into its unique call site, -and absorb the True into it all in the same pass. If we simplified -e1 first, we couldn't do that; see Note [Avoiding simplifying repeatedly]. - -So we try to apply rules if either - (a) no_more_args: we've run out of argument that the rules can "see" - (b) nr_wanted: none of the rules wants any more arguments - - -Note [RULES apply to simplified arguments] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -It's very desirable to try RULES once the arguments have been simplified, because -doing so ensures that rule cascades work in one pass. Consider - {-# RULES g (h x) = k x - f (k x) = x #-} - ...f (g (h x))... -Then we want to rewrite (g (h x)) to (k x) and only then try f's rules. If -we match f's rules against the un-simplified RHS, it won't match. This -makes a particularly big difference when superclass selectors are involved: - op ($p1 ($p2 (df d))) -We want all this to unravel in one sweep. +{- Note [When to apply rewrite rules] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Should we apply rewrite rules before simplifying the arguments, or after? +Both are plausible: see + - Note [Plan (BEFORE): try RULES /before/ simplifying arguments] + - Note [Plan (AFTER): try RULES /after/ simplifying arguments] -Note [Rewrite rules and inlining] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -In general we try to arrange that inlining is disabled (via a pragma) if -a rewrite rule should apply, so that the rule has a decent chance to fire -before we inline the function. +So we do both! + - Plan (BEFORE) selectively, in `simplOutId` + - Plan (AFTER) always, in the finishing-up case of `rebuildCall` + +The "selectively" in Plan (BEFORE) is a bit ad-hoc: + +* We want Plan (BEFORE) for class ops (see Note [Plan (BEFORE)]). + +* We do NOT want Plan (BEFORE) for primops, because the constant-folding rules + are quite complicated and expeensive, and we don't want to try them twice. + Moreover the beneifts of Plan (BEFORE), described in the Note, don't apply to + primops. -But it turns out that (especially when type-class specialisation or -SpecConstr is involved) it is very helpful for the the rewrite rule to -"win" over inlining when both are active at once: see #21851, #22097. -The simplifier arranges to do this, as follows. In effect, the ai_rewrite -field of the ArgInfo record is the state of a little state-machine: +Note [Plan (BEFORE): try RULES /before/ simplifying arguments] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +It is sometimes desirable to apply RULES before simplifying the function +arguments. Two particuar cases: + +* Class ops + (+) dNumInt e2 e3 + If we rewrite ((+) dNumInt) to plusInt, we can take advantage of the + latter's strictness when simplifying e2, e3. Moreover, if + (+) dNumInt e2 e3 --> (\x y -> ....) e2 e3 + Frequently `x` is used just once in the body of the (\x y -> ...). + If `e2` is un-simplified we can preInlineUnconditinally and that saves + simplifying `e2` twice. See Note [Avoiding simplifying repeatedly]. + +* Specialisation RULES. In general we try to arrange that inlining is disabled + (via a pragma) if a rewrite rule should apply, so that the rule has a decent + chance to fire before we inline the function. + + But it turns out that (especially when type-class specialisation or + SpecConstr is involved) it is very helpful for the the rewrite rule to + "win" over inlining when both are active at once: see #21851, #22097. + + So we want to try RULES before we try inlining. + +Wrinkles: -* mkArgInfo sets the ai_rewrite field to TryRules if there are any rewrite - rules avaialable for that function. +(BF1) Each un-simplified argument has its own static environment, stored + in its `ApplyToVal` nodes. So we can't just match on the un-simplified + arguments: we have to apply that static environment as a substitution + first! This is done lazily in `contOutArgs`, so it'll be done just enough + to allow the rule to match, or not. -* rebuildCall simplifies arguments until enough are simplified to match the - rule with greatest arity. See Note [RULES apply to simplified arguments] - and the first field of `TryRules`. +Note [Plan (AFTER): try RULES /after/ simplifying arguments] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +It's very desirable to try RULES once the arguments have been simplified, +because doing so ensures that rule cascades work in one pass. Consider - But no more! As soon as we have simplified enough arguments to satisfy the - maximum-arity rules, we try the rules; see Note [Trying rewrite rules]. + {-# RULES g (h x) = k x + f (k x) = x #-} + ...f (g (h x))... +Then we want to rewrite (g (h x)) to (k x) and only then try f's rules. If +we match f's rules against the un-simplified RHS, it won't match. This +makes a particularly big difference for -* Once we have tried rules (or immediately if there are no rules) set - ai_rewrite to TryInlining, and the Simplifier will try to inline the - function. We want to try this immediately (before simplifying any (more) - arguments). Why? Consider - f BIG where f = \x{OneOcc}. ...x... - If we inline `f` before simplifying `BIG` well use preInlineUnconditionally, - and we'll simplify BIG once, at x's occurrence, rather than twice. +* Superclass selectors + op ($p1 ($p2 (df d))) + We want all this to unravel in one sweep -* GHC.Core.Opt.Simplify.Utils. mkRewriteCall: if there are no rules, and no - unfolding, we can skip both TryRules and TryInlining, which saves work. +* Constant folding + +# 3# (+# 4# 5#) + We want this to happen in one pass Note [Avoid redundant simplification] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Because RULES apply to simplified arguments, there's a danger of repeatedly -simplifying already-simplified arguments. An important example is that of - (>>=) d e1 e2 -Here e1, e2 are simplified before the rule is applied, but don't really -participate in the rule firing. So we mark them as Simplified to avoid -re-simplifying them. +Because RULES often apply to simplified arguments (see Note [Plan (AFTER)]), +there's a danger of simplifying already-simplified arguments. For example, +suppose we have + RULE f (x,y) = $sf x y +and the expression + f (p,q) e1 e2 +With Plan (AFTER) by the time the rule fires, we will have already simplified e1, e2, +and we want to avoid doing so a second time. So ApplyToVal records if the argument +is already Simplified. Note [Shadowing in the Simplifier] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -562,8 +562,11 @@ contOutArgs env cont go (ApplyToVal { sc_dup = dup, sc_arg = arg, sc_env = env, sc_cont = cont }) | isSimplified dup = arg : go cont | otherwise = GHC.Core.Subst.substExpr (getFullSubst in_scope env) arg : go cont - -- NOT substExprSC: we want to get the benefit of knowing what is - -- evaluated etc, via the in-scope set + -- Make sure we apply the static environment `sc_env` as a substitution + -- to get an OutExpr. See (BF1) in Note [Plan (BEFORE)] + -- in GHC.Core.Opt.Simplify.Iteration + -- NB: we use substExpr, not substExprSC: we want to get the benefit of + -- knowing what is evaluated etc, via the in-scope set -- No more arguments go _ = [] ===================================== compiler/GHC/Core/Opt/Specialise.hs ===================================== @@ -1379,7 +1379,7 @@ version of `g` will contain the call `f @Int`; but in the subsequent run of the Simplifier, there will be a competition between: * The user-supplied SPECIALISE rule for `f` * The inlining of the wrapper for `f` -In fact, the latter wins -- see Note [Rewrite rules and inlining] in +In fact, the latter wins -- see Note [Plan (BEFORE): try RULES /before/ simplifying arguments] GHC.Core.Opt.Simplify.Iteration. However, it a bit fragile. Moreover consider (test T21851_2): @@ -1409,10 +1409,10 @@ we load it up just once, in `initRuleEnv`, called at the beginning of `specProgram`. NB: you might wonder if running rules in the specialiser (this Note) -renders Note [Rewrite rules and inlining] in the Simplifier redundant. -That is, if we run rules in the specialiser, does it matter if we make -rules "win" over inlining in the Simplifier? Yes, it does! See the -discussion in #21851. +renders Note [Plan (BEFORE): try RULES /before/ simplifying arguments] +in the Simplifier (partly) redundant. That is, if we run rules in the +specialiser, does it matter if we make rules "win" over inlining in +the Simplifier? Yes, it does! See the discussion in #21851. Note [Floating dictionaries out of cases] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/927f71d11af90cc1a8b373e9fe642b602dd95260 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/927f71d11af90cc1a8b373e9fe642b602dd95260 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/f9e1155a/attachment-0001.html> From gitlab at gitlab.haskell.org Fri Mar 14 23:53:01 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Fri, 14 Mar 2025 19:53:01 -0400 Subject: [Git][ghc/ghc][wip/T25647] go Message-ID: <67d4c15dca2f4_30195093d744457b9@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 169f0cd7 by Patrick at 2025-03-15T07:52:49+08:00 go - - - - - 4 changed files: - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Types/Basic.hs Changes: ===================================== compiler/GHC/Tc/Solver.hs ===================================== @@ -1795,7 +1795,7 @@ defaultTyVarsAndSimplify rhs_tclvl candidates ; poly_kinds <- xoptM LangExt.PolyKinds ; let default_kv | poly_kinds = default_tv | otherwise = defaultTyVar DefaultKindVars - default_tv = defaultTyVar NonStandardDefaulting + default_tv = defaultTyVar (NonStandardDefaulting DefaultNonStandardTyVars) ; mapM_ default_kv (dVarSetElems cand_kvs) ; mapM_ default_tv (dVarSetElems (cand_tvs `minusDVarSet` cand_kvs)) ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -259,13 +259,12 @@ tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] -- See Note [Type variables in type families instance decl] ; (dvs, outer_wcs_imp_dvs) <- candidateQTyVarsWithBinders outer_exp_tvs (outer_imp_tvs ++ wcs) lhs_ty - ; qtvs <- quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs + ; (qtvs, outer_wcs_imp_qtvs) <- quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs -- Have to make a same defaulting choice for result kind here -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; let final_tvs = scopedSort (qtvs ++ outer_exp_tvs) - ; let non_user_tvs = dVarSetElems $ mkDVarSet qtvs `delDVarSetList` outer_wcs_imp_dvs + ; let final_tvs = scopedSort (qtvs ++ outer_wcs_imp_qtvs ++ outer_exp_tvs) -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ; traceTc "tcFamInstLHSBinders" $ @@ -278,15 +277,15 @@ tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted -- after zonking , text "dvs:" <+> ppr dvs - , text "outer_wcs_imp_dvs:" <+> pprTyVars outer_wcs_imp_dvs + , text "outer_wcs_imp_dvs:" <+> ppr outer_wcs_imp_dvs -- after quantification , text "qtvs:" <+> pprTyVars qtvs - , text "non_user_tvs:" <+> pprTyVars non_user_tvs + , text "outer_wcs_imp_qtvs:" <+> pprTyVars outer_wcs_imp_qtvs , text "final_tvs:" <+> pprTyVars final_tvs ] ; reportUnsolvedEqualities skol_info final_tvs tclvl wanted - return (final_tvs, non_user_tvs) + return (final_tvs, qtvs) -- Gives the kind for every TyCon that has a standalone kind signature type KindSigEnv = NameEnv Kind ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -142,7 +142,8 @@ import GHC.Builtin.Types import GHC.Types.Var.Env import GHC.Types.Unique.Set import GHC.Types.Basic ( TypeOrKind(..) - , DefaultingStrategy(..)) + , NonStandardDefaultingStrategy(..) + , DefaultingStrategy(..), defaultNonStandardTyVars ) import GHC.Data.FastString import GHC.Data.Bag @@ -1370,10 +1371,13 @@ candidateVars (DV { dv_kvs = dep_kv_set, dv_tvs = nondep_tkv_set }) candidateKindVars :: CandidatesQTvs -> TyVarSet candidateKindVars dvs = dVarSetToVarSet (dv_kvs dvs) -intersectCandidates :: CandidatesQTvs -> [Var] -> [Var] -intersectCandidates (DV { dv_kvs = kvs, dv_tvs = tvs }) varList - = dVarSetElems $ kvs `intersectDVarSet` vars `unionDVarSet` (tvs `intersectDVarSet` vars) - where vars = mkDVarSet varList +intersectCandidates :: CandidatesQTvs -> [Var] -> CandidatesQTvs +intersectCandidates (DV { dv_kvs = kvs, dv_tvs = tvs, dv_cvs = cvs }) varList + = DV { dv_kvs = kvs `intersectDVarSet` vars + , dv_tvs = tvs `intersectDVarSet` vars + , dv_cvs = cvs `intersectVarSet` mkVarSet varList } + where + vars = mkDVarSet varList delCandidates :: CandidatesQTvs -> [Var] -> CandidatesQTvs delCandidates (DV { dv_kvs = kvs, dv_tvs = tvs, dv_cvs = cvs }) vars @@ -1390,7 +1394,7 @@ partitionCandidates dvs@(DV { dv_kvs = kvs, dv_tvs = tvs }) pred (extracted_tvs, rest_tvs) = partitionDVarSet pred tvs extracted = dVarSetToVarSet extracted_kvs `unionVarSet` dVarSetToVarSet extracted_tvs -candidateQTyVarsWithBinders :: [TyVar] -> [TyVar] -> Type -> TcM (CandidatesQTvs, [TyVar]) +candidateQTyVarsWithBinders :: [TyVar] -> [TyVar] -> Type -> TcM (CandidatesQTvs, CandidatesQTvs) -- (candidateQTyVarsWithBinders tvs ty) returns the candidateQTyVars -- of (forall tvs. ty), but do not treat 'tvs' as bound for the purpose -- of Note [Naughty quantification candidates]. Why? @@ -1753,14 +1757,14 @@ quantifyTyVars :: SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] -- Already zonked -> TcM [TcTyVar] -quantifyTyVars ski tvs = quantifyTyVarsWithBinders ski tvs [] +quantifyTyVars ski tvs = fst <$> quantifyTyVarsWithBinders ski tvs mempty quantifyTyVarsWithBinders :: SkolemInfo -> CandidatesQTvs -- See Note [Dependent type variables] -- Already zonked - -> [TcTyVar] - -> TcM [TcTyVar] + -> CandidatesQTvs -- try not to default + -> TcM ([TcTyVar], [TcTyVar]) -- See Note [quantifyTyVars] -- Can be given a mixture of TcTyVars and TyVars, in the case of -- associated type declarations. Also accepts covars, but *never* returns any. @@ -1770,35 +1774,38 @@ quantifyTyVarsWithBinders :: -- to the restrictions in Note [quantifyTyVars]. -- for outer_wcs_imp_tvs, do not default, just skolemise add to the list of quantified -quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_tvs +quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs -- short-circuit common case - | isEmptyCandidates dvs && null outer_wcs_imp_tvs + | isEmptyCandidates dvs && isEmptyCandidates outer_wcs_imp_dvs = do { traceTc "quantifyTyVars has nothing to quantify" empty - ; return [] } + ; return ([], []) } | otherwise = do { traceTc "quantifyTyVars {" ( vcat [ text "dvs =" <+> ppr dvs, - text "outer_wc_imp_qtvs=" <+> ppr outer_wcs_imp_tvs + text "outer_wc_imp_qtvs=" <+> ppr outer_wcs_imp_dvs ]) - ; undefaulted <- defaultTyVars dvs - ; final_qtvs <- liftZonkM $ do + ; undefaulted <- defaultTyVars DefaultNonStandardTyVars dvs + ; undefaulted_outer_wcs_imp_tvs <- defaultTyVars TryNotToDefaultNonStandardTyVars outer_wcs_imp_dvs + ; (final_qtvs, final_outer_wcs_imp_qtvs) <- liftZonkM $ do -- resume order and then skolemise - qtvs <- mapMaybeM zonk_quant undefaulted - return qtvs + qtvs <- mapMaybeM zonk_quant $ undefaulted + outer_wcs_imp_qtvs <- mapMaybeM zonk_quant $ undefaulted_outer_wcs_imp_tvs + return (qtvs, outer_wcs_imp_qtvs) ; traceTc "quantifyTyVars }" (vcat [ text "undefaulted:" <+> pprTyVars undefaulted + , text "final_outer_wcs_imp_qtvs:" <+> pprTyVars final_outer_wcs_imp_qtvs , text "final_qtvs:" <+> pprTyVars final_qtvs ]) -- We should never quantify over coercion variables; check this - ; let co_vars = filter isCoVar final_qtvs + ; let co_vars = filter isCoVar (final_qtvs ++ final_outer_wcs_imp_qtvs) ; massertPpr (null co_vars) (ppr co_vars) - ; return final_qtvs } + ; return (final_qtvs, final_outer_wcs_imp_qtvs) } where -- zonk_quant returns a tyvar if it should be quantified over; -- otherwise, it returns Nothing. The latter case happens for @@ -1865,7 +1872,7 @@ defaultTyVar :: DefaultingStrategy -> TcTyVar -- If it's a MetaTyVar then it is unbound -> TcM Bool -- True <=> defaulted away altogether defaultTyVar def_strat tv - | not (isMetaTyVar tv ) + | not (isMetaTyVar tv) || isTyVarTyVar tv -- Do not default TyVarTvs. Doing so would violate the invariants -- on TyVarTvs; see Note [TyVarTv] in GHC.Tc.Utils.TcMType. @@ -1874,16 +1881,19 @@ defaultTyVar def_strat tv = return False | isRuntimeRepVar tv + , default_ns_vars = do { traceTc "Defaulting a RuntimeRep var to LiftedRep" (ppr tv) ; liftZonkM $ writeMetaTyVar tv liftedRepTy ; return True } | isLevityVar tv + , default_ns_vars = do { traceTc "Defaulting a Levity var to Lifted" (ppr tv) ; liftZonkM $ writeMetaTyVar tv liftedDataConTy ; return True } | isMultiplicityVar tv + , default_ns_vars = do { traceTc "Defaulting a Multiplicity var to Many" (ppr tv) ; liftZonkM $ writeMetaTyVar tv manyDataConTy ; return True } @@ -1906,6 +1916,8 @@ defaultTyVar def_strat tv = return False where + default_ns_vars :: Bool + default_ns_vars = defaultNonStandardTyVars def_strat default_kind_var :: TyVar -> TcM Bool -- defaultKindVar is used exclusively with -XNoPolyKinds -- See Note [Defaulting with -XNoPolyKinds] @@ -1936,13 +1948,14 @@ defaultTyVar def_strat tv -- - 'Multiplicity' tyvars default to 'Many' -- - 'Type' tyvars from dv_kvs default to 'Type', when -XNoPolyKinds -- (under -XNoPolyKinds, non-defaulting vars in dv_kvs is an error) -defaultTyVars :: CandidatesQTvs -- ^ all candidates for quantification +defaultTyVars :: NonStandardDefaultingStrategy + -> CandidatesQTvs -- ^ all candidates for quantification -> TcM [TcTyVar] -- ^ those variables not defaulted -defaultTyVars dvs +defaultTyVars ns_strat dvs = do { poly_kinds <- xoptM LangExt.PolyKinds ; let def_tvs, def_kvs :: DefaultingStrategy - def_tvs = NonStandardDefaulting + def_tvs = NonStandardDefaulting ns_strat def_kvs | poly_kinds = def_tvs | otherwise = DefaultKindVars -- As -XNoPolyKinds precludes polymorphic kind variables, we default them. @@ -2124,7 +2137,7 @@ doNotQuantifyTyVars dvs where_found | otherwise = do { traceTc "doNotQuantifyTyVars" (ppr dvs) - ; undefaulted <- defaultTyVars dvs + ; undefaulted <- defaultTyVars DefaultNonStandardTyVars dvs -- could have regular TyVars here, in an associated type RHS, or -- bound by a type declaration head. So filter looking only for -- metavars. e.g. b and c in `class (forall a. a b ~ a c) => C b c` ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -116,7 +116,8 @@ module GHC.Types.Basic ( TyConFlavour(..), TypeOrData(..), NewOrData(..), tyConFlavourAssoc_maybe, - DefaultingStrategy(..), + NonStandardDefaultingStrategy(..), + DefaultingStrategy(..), defaultNonStandardTyVars, ForeignSrcLang (..) ) where @@ -2395,6 +2396,19 @@ GHC.Iface.Type.defaultIfaceTyVarsOfKind -} +-- | Specify whether to default type variables of kind 'RuntimeRep'/'Levity'/'Multiplicity'. +data NonStandardDefaultingStrategy + -- | Default type variables of the given kinds: + -- + -- - default 'RuntimeRep' variables to 'LiftedRep' + -- - default 'Levity' variables to 'Lifted' + -- - default 'Multiplicity' variables to 'Many' + = DefaultNonStandardTyVars + -- | Try not to default type variables of the kinds 'RuntimeRep'/'Levity'/'Multiplicity'. + -- + -- Note that these might get defaulted anyway, if they are kind variables + -- and `-XNoPolyKinds` is enabled. + | TryNotToDefaultNonStandardTyVars -- | Specify whether to default kind variables, and type variables -- of kind 'RuntimeRep'/'Levity'/'Multiplicity'. @@ -2410,12 +2424,19 @@ data DefaultingStrategy -- -- Usually, we pass this option when -XNoPolyKinds is enabled. = DefaultKindVars - -- | Default non-standard variables, of kinds + -- | Default (or don't default) non-standard variables, of kinds -- 'RuntimeRep', 'Levity' and 'Multiplicity'. - | NonStandardDefaulting + | NonStandardDefaulting NonStandardDefaultingStrategy +defaultNonStandardTyVars :: DefaultingStrategy -> Bool +defaultNonStandardTyVars DefaultKindVars = True +defaultNonStandardTyVars (NonStandardDefaulting DefaultNonStandardTyVars) = True +defaultNonStandardTyVars (NonStandardDefaulting TryNotToDefaultNonStandardTyVars) = False +instance Outputable NonStandardDefaultingStrategy where + ppr DefaultNonStandardTyVars = text "DefaultOnlyNonStandardTyVars" + ppr TryNotToDefaultNonStandardTyVars = text "TryNotToDefaultNonStandardTyVars" instance Outputable DefaultingStrategy where ppr DefaultKindVars = text "DefaultKindVars" - ppr NonStandardDefaulting = text "NonStandardDefaulting" + ppr (NonStandardDefaulting ns) = text "NonStandardDefaulting" <+> ppr ns View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/169f0cd7af57b9eaea817f205aa6f53d1398f282 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/169f0cd7af57b9eaea817f205aa6f53d1398f282 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/a6e92c62/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 00:25:11 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Fri, 14 Mar 2025 20:25:11 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/int-index/retry-tyclds Message-ID: <67d4c8e72a203_301950da41ac464e8@gitlab.mail> Vladislav Zavialov pushed new branch wip/int-index/retry-tyclds at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/int-index/retry-tyclds You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/853ab890/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 15 00:32:26 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Fri, 14 Mar 2025 20:32:26 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/wasm-jsffi-interruptible Message-ID: <67d4ca9a2236e_328be7cb354454b4@gitlab.mail> Cheng Shao pushed new branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/wasm-jsffi-interruptible You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/efa6d90c/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 15 00:50:27 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Fri, 14 Mar 2025 20:50:27 -0400 Subject: [Git][ghc/ghc][wip/int-index/retry-tyclds] WIP: Retry type and class declarations Message-ID: <67d4ced3b3333_328be715884447656@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/retry-tyclds at Glasgow Haskell Compiler / GHC Commits: 4b0eef4e by Vladislav Zavialov at 2025-03-15T03:50:11+03:00 WIP: Retry type and class declarations - - - - - 1 changed file: - compiler/GHC/Tc/TyCl.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -91,6 +91,7 @@ import qualified GHC.LanguageExtensions as LangExt import GHC.Data.FastString import GHC.Data.Maybe import GHC.Data.List.SetOps( minusList, equivClasses ) +import GHC.Data.Bag import GHC.Unit import GHC.Unit.Module.ModDetails @@ -110,6 +111,7 @@ import Data.List.NonEmpty ( NonEmpty(..) ) import qualified Data.List.NonEmpty as NE import Data.Traversable ( for ) import Data.Tuple( swap ) +import qualified Data.Semigroup as S {- ************************************************************************ @@ -147,6 +149,22 @@ Thus, we take two passes over the resulting tycons, first checking for general validity and then checking for valid role annotations. -} +data TcTyClGroupsAccum = + TcTyClGroupsAccum + { ttcga_inst_info :: !(Bag (InstInfo GhcRn)) -- Source-code instance decls info + , ttcga_deriv_info :: !(Bag DerivInfo) -- Deriving info + , ttcga_th_bndrs :: !ThBindEnv -- TH binding levels + } + +instance S.Semigroup TcTyClGroupsAccum where + (TcTyClGroupsAccum a1 b1 c1) <> (TcTyClGroupsAccum a2 b2 c2) = + TcTyClGroupsAccum (a1 `unionBags` a2) + (b1 `unionBags` b2) + (c1 `plusNameEnv` c2) + +instance Monoid TcTyClGroupsAccum where + mempty = TcTyClGroupsAccum emptyBag emptyBag emptyNameEnv + tcTyAndClassDecls :: [TyClGroup GhcRn] -- Mutually-recursive groups in -- dependency order -> TcM ( TcGblEnv -- Input env extended by types and @@ -161,28 +179,141 @@ tcTyAndClassDecls tyclds_s -- The code recovers internally, but if anything gave rise to -- an error we'd better stop now, to avoid a cascade -- Type check each group in dependency order folding the global env - = checkNoErrs $ fold_env [] [] emptyNameEnv tyclds_s + = checkNoErrs $ go_prefix_pass mempty tyclds_s where - fold_env :: [InstInfo GhcRn] - -> [DerivInfo] - -> ThBindEnv - -> [TyClGroup GhcRn] - -> TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo], ThBindEnv) - fold_env inst_info deriv_info th_bndrs [] + done :: TcTyClGroupsAccum -> + TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo], ThBindEnv) + done acc = do { gbl_env <- getGblEnv - ; return (gbl_env, inst_info, deriv_info, th_bndrs) } - fold_env inst_info deriv_info th_bndrs (tyclds:tyclds_s) - = do { (tcg_env, inst_info', deriv_info', th_bndrs') - <- tcTyClGroup tyclds - ; setGblEnv tcg_env $ - -- remaining groups are typechecked in the extended global env. - fold_env (inst_info' ++ inst_info) - (deriv_info' ++ deriv_info) - (th_bndrs' `plusNameEnv` th_bndrs) - tyclds_s } + ; return (gbl_env, bagToList inst_info, bagToList deriv_info, th_bndrs) } + where + TcTyClGroupsAccum{ ttcga_inst_info = inst_info + , ttcga_deriv_info = deriv_info + , ttcga_th_bndrs = th_bndrs + } = acc + + go_prefix_pass, go_selection_pass, go_failure_pass :: + TcTyClGroupsAccum -> + [TyClGroup GhcRn] -> + TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo], ThBindEnv) + + go_prefix_pass acc [] = done acc + go_prefix_pass acc gs + = do { (tcg_env, acc', gs') <- tcTyClGroupsPrefixPass gs + ; setGblEnv tcg_env $ go_selection_pass (acc' S.<> acc) gs' } + + go_selection_pass acc [] = done acc + go_selection_pass acc gs + = do { (tcg_env, acc', n, gs') <- tcTyClGroupsSelectionPass gs + ; let go_next_pass | n == 0 = go_failure_pass + | otherwise = go_prefix_pass + ; setGblEnv tcg_env $ go_next_pass (acc' S.<> acc) gs' } + + go_failure_pass acc [] = done acc + go_failure_pass acc (g:gs) + = do { (tg_env, acc') <- tcTyClGroup g + ; setGblEnv tg_env $ go_failure_pass (acc' S.<> acc) gs } + +-- Typecheck the well-kinded prefix of TyClGroups and return the remaining ones. +-- This is the "happy" path. The list of remaining TyClGroups is empty if both +-- conditions hold: +-- 1. The program is kind-correct +-- 2. All dependencies between type declarations are lexical +-- Non-lexical dependencies may arise due to type instances. +tcTyClGroupsPrefixPass :: [TyClGroup GhcRn] -- Mutually-recursive groups in + -- lexical dependency order + -> TcM ( TcGblEnv -- Input env extended by types and classes + -- and their implicit Ids,DataCons + , TcTyClGroupsAccum + , [TyClGroup GhcRn] -- The remaining groups in lexical dependency order + ) +tcTyClGroupsPrefixPass = go 0 [] mempty + where + go :: Int + -> [Name] + -> TcTyClGroupsAccum + -> [TyClGroup GhcRn] + -> TcM (TcGblEnv, TcTyClGroupsAccum, [TyClGroup GhcRn]) + go !n _ acc [] = do + gbl_env <- getGblEnv + traceTc "tcTyClGroupsPrefixPass done" (ppr n) + return (gbl_env, acc, []) + go !n bndrs acc (g:gs) = do + let (bndrs', _) = group_ext g + m_result <- tryTcTyClGroup g + case m_result of + Nothing -> do + gbl_env <- getGblEnv + traceTc "tcTyClGroupsPrefixPass stopped" (ppr n) + let gs' = map (delTyClGroupDeps bndrs) (g:gs) + return (gbl_env, acc, gs') + Just (tcg_env, acc') -> + setGblEnv tcg_env $ + go (n+1) (bndrs' ++ bndrs) (acc' S.<> acc) gs + +-- Typecheck the well-kinded selection of TyClGroups and return the remaining ones. +-- This is the "unhappy" path that exists due to non-lexical dependencies arising +-- from type instances. +tcTyClGroupsSelectionPass :: [TyClGroup GhcRn] -- Mutually-recursive groups in + -- lexical dependency order + -> TcM ( TcGblEnv -- Input env extended by types and classes + -- and their implicit Ids,DataCons + , TcTyClGroupsAccum + , Int -- Number of successfully checked groups + , [TyClGroup GhcRn] -- The remaining groups in lexical dependency order + ) +tcTyClGroupsSelectionPass all_gs = go 0 [] mempty [] ready_gs + where + ready_gs, blocked_gs :: [TyClGroup GhcRn] + (ready_gs, blocked_gs) = selectReadyTyClGroups all_gs + + go :: Int + -> [Name] + -> TcTyClGroupsAccum + -> [TyClGroup GhcRn] + -> [TyClGroup GhcRn] + -> TcM (TcGblEnv, TcTyClGroupsAccum, Int, [TyClGroup GhcRn]) + go !n bndrs acc failed_gs [] = do + gbl_env <- getGblEnv + traceTc "tcTyClGroupsSelectionPass done" (ppr n) + let blocked_gs' = map (delTyClGroupDeps bndrs) blocked_gs + return (gbl_env, acc, n, reverse failed_gs ++ blocked_gs') + go !n bndrs acc failed_gs (g:gs) = do + let (bndrs', _) = group_ext g + m_result <- tryTcTyClGroup g + case m_result of + Nothing -> go n bndrs acc (g:failed_gs) gs + Just (tcg_env, acc') -> + setGblEnv tcg_env $ + go (n+1) (bndrs' ++ bndrs) (acc' S.<> acc) failed_gs gs + +selectReadyTyClGroups :: [TyClGroup GhcRn] -> ([TyClGroup GhcRn], [TyClGroup GhcRn]) +selectReadyTyClGroups gs = (ready_inst_gs ++ ready_noinst_gs, blocked_gs) + where + (ready_inst_gs, ready_noinst_gs, blocked_gs) = foldr classify ([], [], []) gs + -- ready_inst_gs: most likely to unblock further type checking + -- ready_noinst_gs: might indirectly unlock further type checking + -- blocked_gs: unusable + + classify :: TyClGroup GhcRn -> ([TyClGroup GhcRn], [TyClGroup GhcRn], [TyClGroup GhcRn]) + -> ([TyClGroup GhcRn], [TyClGroup GhcRn], [TyClGroup GhcRn]) + classify g at TyClGroup{ group_ext = (_, deps) + , group_instds = inst_ds } + ~(xs, ys, zs) + | not ready = (xs, ys, g:zs) + | null inst_ds = (xs, g:ys, zs) + | otherwise = (g:xs, ys, zs) + where ready = isEmptyNameSet deps + +tryTcTyClGroup :: TyClGroup GhcRn -> TcM (Maybe (TcGblEnv, TcTyClGroupsAccum)) +tryTcTyClGroup g = tryTcDiscardingErrs (return Nothing) (Just <$> tcTyClGroup g) + +delTyClGroupDeps :: [Name] -> TyClGroup GhcRn -> TyClGroup GhcRn +delTyClGroupDeps names g at TyClGroup{group_ext = (bndrs, deps)} + = g {group_ext = (bndrs, delListFromNameSet deps names)} tcTyClGroup :: TyClGroup GhcRn - -> TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo], ThBindEnv) + -> TcM (TcGblEnv, TcTyClGroupsAccum) -- Typecheck one strongly-connected component of type, class, and instance decls -- See Note [TyClGroups and dependency analysis] in GHC.Hs.Decls tcTyClGroup (TyClGroup { group_tyclds = tyclds @@ -245,8 +376,10 @@ tcTyClGroup (TyClGroup { group_tyclds = tyclds ; let deriv_info = datafam_deriv_info ++ data_deriv_info ; let gbl_env'' = gbl_env' { tcg_ksigs = tcg_ksigs gbl_env' `unionNameSet` kindless } - ; return (gbl_env'', inst_info, deriv_info, - th_bndrs' `plusNameEnv` th_bndrs) } + ; let acc = TcTyClGroupsAccum{ ttcga_inst_info = listToBag inst_info + , ttcga_deriv_info = listToBag deriv_info + , ttcga_th_bndrs = th_bndrs' `plusNameEnv` th_bndrs } + ; return (gbl_env'', acc) } -- Gives the kind for every TyCon that has a standalone kind signature type KindSigEnv = NameEnv Kind View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4b0eef4eea952308ef121860e4e7210c00a56391 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4b0eef4eea952308ef121860e4e7210c00a56391 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/6ab27344/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 01:01:55 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Fri, 14 Mar 2025 21:01:55 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] woohoo mvar Message-ID: <67d4d1833da67_328be717172c499cb@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: b2239cb7 by Cheng Shao at 2025-03-15T01:01:44+00:00 woohoo mvar - - - - - 3 changed files: - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - rts/wasm/JSFFI.c - rts/wasm/blocker.cmm Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -82,8 +82,8 @@ filled is generated via raiseJSException. stg_blockPromise :: String -> JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> case stg_jsffi_check (unsafeCoerce# $ toException $ WouldBlockException err_msg) s0 of - (# s1 #) -> case myThreadId# s1 of - (# s2, tso #) -> case makeStablePtr# tso s2 of + (# s1 #) -> case newMVar# s1 of + (# s2, mv# #) -> case makeStablePtr# mv# s2 of (# s3, sp #) -> case unIO (msg_p p $ StablePtr $ unsafeCoerce# sp) s3 of -- Since we eagerly free the Promise here, we must return @@ -104,15 +104,11 @@ stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> -- the Promise to resolve or reject, and also mark it -- as OPAQUE just to be sure. keepAlive# raiseJSException s5 $ - stg_jsffi_block $ - throw PromisePendingException + readMVar# mv# foreign import prim "stg_jsffi_check" stg_jsffi_check :: Any -> State# RealWorld -> (# State# RealWorld #) -foreign import prim "stg_jsffi_block" - stg_jsffi_block :: Any -> State# RealWorld -> (# State# RealWorld, r #) - foreign import javascript unsafe "$1.then(() => __exports.rts_promiseResolveUnit($2), err => __exports.rts_promiseReject($2, err))" stg_messagePromiseUnit :: JSVal -> StablePtr Any -> IO () ===================================== rts/wasm/JSFFI.c ===================================== @@ -144,7 +144,6 @@ INLINE_HEADER void pushClosure (StgTSO *tso, StgWord c) { tso->stackobj->sp[0] = (W_) c; } -extern const StgInfoTable stg_jsffi_block_info; extern const StgInfoTable stg_scheduler_loop_info; extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; @@ -173,19 +172,7 @@ void rts_schedulerLoop(void) { #define mk_rtsPromiseCallback(obj) \ { \ Capability *cap = &MainCapability; \ - StgTSO *tso = (StgTSO*)deRefStablePtr(sp); \ - IF_DEBUG(sanity, checkTSO(tso)); \ - hs_free_stable_ptr(sp); \ - \ - StgStack *stack = tso->stackobj; \ - IF_DEBUG(sanity, checkSTACK(stack)); \ - \ - if (stack->sp[0] == (StgWord)&stg_jsffi_block_info) { \ - dirty_TSO(cap, tso); \ - dirty_STACK(cap, stack); \ - stack->sp[1] = (StgWord)(obj); \ - } \ - scheduleThreadNow(cap, tso); \ + hs_try_putmvar_with_value(cap->no, sp, obj); \ rts_schedulerLoop(); \ } ===================================== rts/wasm/blocker.cmm ===================================== @@ -1,35 +1,5 @@ #include "Cmm.h" -#if !defined(UnregisterisedCompiler) -import CLOSURE STK_CHK_ctr; -import CLOSURE stg_jsffi_block_info; -#endif - -// The ret field will be the boxed result that the JSFFI async import -// actually returns. Or a bottom closure that throws JSException in -// case of Promise rejection. -INFO_TABLE_RET ( stg_jsffi_block, RET_SMALL, W_ info_ptr, P_ ret ) - return () -{ - jump %ENTRY_CODE(Sp(0)) (ret); -} - -// Push a stg_jsffi_block frame and suspend the current thread. bottom -// is a placeholder that throws PromisePendingException, though in -// theory the user should never see PromisePendingException since that -// indicates a thread blocked for async JSFFI is mistakenly resumed -// somehow. -stg_jsffi_block (P_ bottom) -{ - Sp_adj(-2); - Sp(0) = stg_jsffi_block_info; - Sp(1) = bottom; - - ASSERT(SpLim - WDS(RESERVED_STACK_WORDS) <= Sp); - - jump stg_block_noregs (); -} - // Check that we're in a forked thread at the moment, since main // threads that are bound to an InCall frame cannot block waiting for // a Promise to fulfill. err is the SomeException closure of View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b2239cb752430b8fe936b0e0b9b026aae59038cd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b2239cb752430b8fe936b0e0b9b026aae59038cd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/b123da63/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 01:59:32 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Fri, 14 Mar 2025 21:59:32 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] woohoo mvar Message-ID: <67d4df048e73d_328be78c36385807f@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: a23fbb02 by Cheng Shao at 2025-03-15T01:59:18+00:00 woohoo mvar - - - - - 4 changed files: - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/wasm/JSFFI.c - rts/wasm/blocker.cmm Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -82,8 +82,8 @@ filled is generated via raiseJSException. stg_blockPromise :: String -> JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> case stg_jsffi_check (unsafeCoerce# $ toException $ WouldBlockException err_msg) s0 of - (# s1 #) -> case myThreadId# s1 of - (# s2, tso #) -> case makeStablePtr# tso s2 of + (# s1 #) -> case newMVar# s1 of + (# s2, mv# #) -> case makeStablePtr# mv# s2 of (# s3, sp #) -> case unIO (msg_p p $ StablePtr $ unsafeCoerce# sp) s3 of -- Since we eagerly free the Promise here, we must return @@ -104,15 +104,11 @@ stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> -- the Promise to resolve or reject, and also mark it -- as OPAQUE just to be sure. keepAlive# raiseJSException s5 $ - stg_jsffi_block $ - throw PromisePendingException + readMVar# mv# foreign import prim "stg_jsffi_check" stg_jsffi_check :: Any -> State# RealWorld -> (# State# RealWorld #) -foreign import prim "stg_jsffi_block" - stg_jsffi_block :: Any -> State# RealWorld -> (# State# RealWorld, r #) - foreign import javascript unsafe "$1.then(() => __exports.rts_promiseResolveUnit($2), err => __exports.rts_promiseReject($2, err))" stg_messagePromiseUnit :: JSVal -> StablePtr Any -> IO () ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -15,8 +15,7 @@ module GHC.Internal.Wasm.Prim.Types ( fromJSString, toJSString, JSException (..), - WouldBlockException (..), - PromisePendingException (..) + WouldBlockException (..) ) where import GHC.Internal.Base @@ -255,9 +254,3 @@ newtype WouldBlockException deriving (Show) instance Exception WouldBlockException - -data PromisePendingException - = PromisePendingException - deriving (Show) - -instance Exception PromisePendingException ===================================== rts/wasm/JSFFI.c ===================================== @@ -144,7 +144,6 @@ INLINE_HEADER void pushClosure (StgTSO *tso, StgWord c) { tso->stackobj->sp[0] = (W_) c; } -extern const StgInfoTable stg_jsffi_block_info; extern const StgInfoTable stg_scheduler_loop_info; extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; @@ -173,19 +172,7 @@ void rts_schedulerLoop(void) { #define mk_rtsPromiseCallback(obj) \ { \ Capability *cap = &MainCapability; \ - StgTSO *tso = (StgTSO*)deRefStablePtr(sp); \ - IF_DEBUG(sanity, checkTSO(tso)); \ - hs_free_stable_ptr(sp); \ - \ - StgStack *stack = tso->stackobj; \ - IF_DEBUG(sanity, checkSTACK(stack)); \ - \ - if (stack->sp[0] == (StgWord)&stg_jsffi_block_info) { \ - dirty_TSO(cap, tso); \ - dirty_STACK(cap, stack); \ - stack->sp[1] = (StgWord)(obj); \ - } \ - scheduleThreadNow(cap, tso); \ + hs_try_putmvar_with_value(cap->no, sp, obj); \ rts_schedulerLoop(); \ } ===================================== rts/wasm/blocker.cmm ===================================== @@ -1,35 +1,5 @@ #include "Cmm.h" -#if !defined(UnregisterisedCompiler) -import CLOSURE STK_CHK_ctr; -import CLOSURE stg_jsffi_block_info; -#endif - -// The ret field will be the boxed result that the JSFFI async import -// actually returns. Or a bottom closure that throws JSException in -// case of Promise rejection. -INFO_TABLE_RET ( stg_jsffi_block, RET_SMALL, W_ info_ptr, P_ ret ) - return () -{ - jump %ENTRY_CODE(Sp(0)) (ret); -} - -// Push a stg_jsffi_block frame and suspend the current thread. bottom -// is a placeholder that throws PromisePendingException, though in -// theory the user should never see PromisePendingException since that -// indicates a thread blocked for async JSFFI is mistakenly resumed -// somehow. -stg_jsffi_block (P_ bottom) -{ - Sp_adj(-2); - Sp(0) = stg_jsffi_block_info; - Sp(1) = bottom; - - ASSERT(SpLim - WDS(RESERVED_STACK_WORDS) <= Sp); - - jump stg_block_noregs (); -} - // Check that we're in a forked thread at the moment, since main // threads that are bound to an InCall frame cannot block waiting for // a Promise to fulfill. err is the SomeException closure of View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a23fbb02863fa579187c8f04b8e9cd3807e6f70d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a23fbb02863fa579187c8f04b8e9cd3807e6f70d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/4a42dcc1/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 03:21:26 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Fri, 14 Mar 2025 23:21:26 -0400 Subject: [Git][ghc/ghc][wip/T25647] fix double update Message-ID: <67d4f23673cb4_328be713075f4620fd@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 9dc41673 by Patrick at 2025-03-15T11:21:18+08:00 fix double update - - - - - 1 changed file: - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1405,7 +1405,7 @@ candidateQTyVarsWithBinders outer_exp_tvs outer_wcs_imp_tvs ty = do { kvs <- candidateQTyVarsOfKinds (map tyVarKind bound_tvs) ; cur_lvl <- getTcLevel ; all_tvs <- collect_cand_qtvs ty False cur_lvl emptyVarSet kvs ty - ; return (all_tvs `delCandidates` outer_exp_tvs, all_tvs `intersectCandidates` outer_wcs_imp_tvs) } + ; return (all_tvs `delCandidates` bound_tvs, all_tvs `intersectCandidates` outer_wcs_imp_tvs) } where bound_tvs = outer_exp_tvs ++ outer_wcs_imp_tvs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9dc4167358f44e7985d4d2d9da8436457e85704d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9dc4167358f44e7985d4d2d9da8436457e85704d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250314/8d9cc6ab/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 15 04:41:20 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sat, 15 Mar 2025 00:41:20 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] WIP Message-ID: <67d504f032a0e_328be71a23310689a3@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: a5832455 by Cheng Shao at 2025-03-15T04:41:10+00:00 WIP - - - - - 3 changed files: - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - rts/wasm/JSFFI.c Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs ===================================== @@ -1,5 +1,6 @@ {-# LANGUAGE GHCForeignImportPrim #-} {-# LANGUAGE MagicHash #-} +{-# LANGUAGE MultilineStrings #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE UnliftedFFITypes #-} @@ -66,15 +67,27 @@ runIO res m = do js_promiseReject p tmp freeJSVal tmp_v IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles) s0 of - (# s1, _ #) -> case stg_scheduler_loop# s1 of - (# s2, _ #) -> (# s2, p #) + (# s1, tso# #) -> case mkWeakNoFinalizer# tso# () s1 of + (# s2, w# #) -> case makeStablePtr# w# s2 of + (# s3, sp# #) -> case unIO (js_promiseAddThrowTo p $ StablePtr $ unsafeCoerce# sp#) s3 of + (# s4, _ #) -> case stg_scheduler_loop# s4 of + (# s5, _ #) -> (# s5, p #) runNonIO :: (JSVal -> a -> IO ()) -> a -> IO JSVal runNonIO res a = runIO res $ pure a -foreign import javascript unsafe "let res, rej; const p = new Promise((resolve, reject) => { res = resolve; rej = reject; }); p.resolve = res; p.reject = rej; return p;" +foreign import javascript unsafe + """ + const { promise, resolve, reject } = Promise.withResolvers(); + promise.resolve = resolve; + promise.reject = reject; + return promise; + """ js_promiseWithResolvers :: IO JSVal +foreign import javascript unsafe "$1.throwTo = (err) => __exports.rts_promiseThrowTo($2, err);" + js_promiseAddThrowTo :: JSVal -> StablePtr Any -> IO () + foreign import prim "stg_scheduler_loopzh" stg_scheduler_loop# :: State# RealWorld -> (# State# RealWorld, () #) ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -5,6 +5,7 @@ {-# LANGUAGE UnliftedFFITypes #-} module GHC.Internal.Wasm.Prim.Imports ( + raiseJSException, stg_blockPromise, stg_messagePromiseUnit, stg_messagePromiseJSVal, @@ -98,13 +99,7 @@ stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> -- and prevents dmdanal from being naughty (# s4, _ #) -> case unIO (freeJSVal p) s4 of (# s5, _ #) -> - -- raiseJSException_closure is used by the RTS in case - -- the Promise is rejected, and it is likely a CAF. So - -- we need to keep it alive when we block waiting for - -- the Promise to resolve or reject, and also mark it - -- as OPAQUE just to be sure. - keepAlive# raiseJSException s5 $ - readMVar# mv# + readMVar# mv# s5 foreign import prim "stg_jsffi_check" stg_jsffi_check :: Any -> State# RealWorld -> (# State# RealWorld #) ===================================== rts/wasm/JSFFI.c ===================================== @@ -1,5 +1,6 @@ #include "Rts.h" #include "Prelude.h" +#include "RaiseAsync.h" #include "Schedule.h" #include "sm/Sanity.h" @@ -7,6 +8,7 @@ extern HsBool rts_JSFFI_flag; extern HsStablePtr rts_threadDelay_impl; +extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure; int __main_void(void); @@ -20,6 +22,7 @@ int __main_argc_argv(int argc, char *argv[]) { hs_init_ghc(&argc, &argv, __conf); // See Note [threadDelay on wasm] for details. rts_JSFFI_flag = HS_BOOL_TRUE; + getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure); rts_threadDelay_impl = getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure); return 0; } @@ -145,7 +148,6 @@ INLINE_HEADER void pushClosure (StgTSO *tso, StgWord c) { } extern const StgInfoTable stg_scheduler_loop_info; -extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; // schedule a future round of RTS scheduler loop via setImmediate(), // to avoid jamming the JavaScript main thread @@ -211,6 +213,25 @@ void rts_promiseReject(HsStablePtr, HsJSVal); void rts_promiseReject(HsStablePtr sp, HsJSVal js_err) mk_rtsPromiseCallback(rts_apply(cap, &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, rts_mkJSVal(cap, js_err))) +__attribute__((export_name("rts_promiseThrowTo"))) +void rts_promiseThrowTo(HsStablePtr, HsJSVal); +void rts_promiseThrowTo(HsStablePtr sp, HsJSVal js_err) { + Capability *cap = &MainCapability; + StgWeak *w = (StgWeak *)deRefStablePtr(sp); + if (w->header.info == &stg_DEAD_WEAK_info) { + return; + } + ASSERT(w->header.info == &stg_WEAK_info); + StgTSO *tso = (StgTSO *)w->key; + ASSERT(tso->header.info == &stg_TSO_info); + throwToSelf( + cap, tso, + rts_apply( + cap, + &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, + rts_mkJSVal(cap, js_err))); +} + __attribute__((export_name("rts_freeStablePtr"))) void rts_freeStablePtr(HsStablePtr); void rts_freeStablePtr(HsStablePtr sp) { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a5832455ca6fe36542d3bf83dbc1a4861f9bd7d1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a5832455ca6fe36542d3bf83dbc1a4861f9bd7d1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/544e3a48/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 06:06:01 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sat, 15 Mar 2025 02:06:01 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] WIP Message-ID: <67d518c96846d_328be7225a3807359c@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: 6b9e7a27 by Cheng Shao at 2025-03-15T06:05:46+00:00 WIP - - - - - 3 changed files: - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - rts/wasm/JSFFI.c Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs ===================================== @@ -1,5 +1,6 @@ {-# LANGUAGE GHCForeignImportPrim #-} {-# LANGUAGE MagicHash #-} +{-# LANGUAGE MultilineStrings #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE UnliftedFFITypes #-} @@ -34,6 +35,7 @@ import GHC.Internal.Base import GHC.Internal.Exception.Type import GHC.Internal.Exts import GHC.Internal.IO +import GHC.Internal.IORef import GHC.Internal.Int import GHC.Internal.Stable import GHC.Internal.TopHandler (flushStdHandles) @@ -65,16 +67,33 @@ runIO res m = do let tmp@(JSString tmp_v) = toJSString $ displayException err js_promiseReject p tmp freeJSVal tmp_v - IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles) s0 of - (# s1, _ #) -> case stg_scheduler_loop# s1 of - (# s2, _ #) -> (# s2, p #) + post_action_ref <- newIORef $ pure () + IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles *> join (readIORef post_action_ref)) s0 of + (# s1, tso# #) -> case mkWeakNoFinalizer# tso# () s1 of + (# s2, w# #) -> case makeStablePtr# w# s2 of + (# s3, sp# #) -> case unIO (writeIORef post_action_ref $ js_promiseDelThrowTo p *> freeStablePtr (StablePtr $ unsafeCoerce# sp#)) s3 of + (# s4, _ #) -> case unIO (js_promiseAddThrowTo p $ StablePtr $ unsafeCoerce# sp#) s4 of + (# s5, _ #) -> case stg_scheduler_loop# s5 of + (# s6, _ #) -> (# s6, p #) runNonIO :: (JSVal -> a -> IO ()) -> a -> IO JSVal runNonIO res a = runIO res $ pure a -foreign import javascript unsafe "let res, rej; const p = new Promise((resolve, reject) => { res = resolve; rej = reject; }); p.resolve = res; p.reject = rej; return p;" +foreign import javascript unsafe + """ + const { promise, resolve, reject } = Promise.withResolvers(); + promise.resolve = resolve; + promise.reject = reject; + return promise; + """ js_promiseWithResolvers :: IO JSVal +foreign import javascript unsafe "$1.throwTo = (err) => __exports.rts_promiseThrowTo($2, err);" + js_promiseAddThrowTo :: JSVal -> StablePtr Any -> IO () + +foreign import javascript unsafe "$1.throwTo = () => {};" + js_promiseDelThrowTo :: JSVal -> IO () + foreign import prim "stg_scheduler_loopzh" stg_scheduler_loop# :: State# RealWorld -> (# State# RealWorld, () #) ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -5,6 +5,7 @@ {-# LANGUAGE UnliftedFFITypes #-} module GHC.Internal.Wasm.Prim.Imports ( + raiseJSException, stg_blockPromise, stg_messagePromiseUnit, stg_messagePromiseJSVal, @@ -98,13 +99,7 @@ stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> -- and prevents dmdanal from being naughty (# s4, _ #) -> case unIO (freeJSVal p) s4 of (# s5, _ #) -> - -- raiseJSException_closure is used by the RTS in case - -- the Promise is rejected, and it is likely a CAF. So - -- we need to keep it alive when we block waiting for - -- the Promise to resolve or reject, and also mark it - -- as OPAQUE just to be sure. - keepAlive# raiseJSException s5 $ - readMVar# mv# + readMVar# mv# s5 foreign import prim "stg_jsffi_check" stg_jsffi_check :: Any -> State# RealWorld -> (# State# RealWorld #) ===================================== rts/wasm/JSFFI.c ===================================== @@ -1,5 +1,6 @@ #include "Rts.h" #include "Prelude.h" +#include "RaiseAsync.h" #include "Schedule.h" #include "sm/Sanity.h" @@ -7,6 +8,7 @@ extern HsBool rts_JSFFI_flag; extern HsStablePtr rts_threadDelay_impl; +extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure; int __main_void(void); @@ -20,6 +22,7 @@ int __main_argc_argv(int argc, char *argv[]) { hs_init_ghc(&argc, &argv, __conf); // See Note [threadDelay on wasm] for details. rts_JSFFI_flag = HS_BOOL_TRUE; + getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure); rts_threadDelay_impl = getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure); return 0; } @@ -145,7 +148,6 @@ INLINE_HEADER void pushClosure (StgTSO *tso, StgWord c) { } extern const StgInfoTable stg_scheduler_loop_info; -extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; // schedule a future round of RTS scheduler loop via setImmediate(), // to avoid jamming the JavaScript main thread @@ -211,6 +213,25 @@ void rts_promiseReject(HsStablePtr, HsJSVal); void rts_promiseReject(HsStablePtr sp, HsJSVal js_err) mk_rtsPromiseCallback(rts_apply(cap, &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, rts_mkJSVal(cap, js_err))) +__attribute__((export_name("rts_promiseThrowTo"))) +void rts_promiseThrowTo(HsStablePtr, HsJSVal); +void rts_promiseThrowTo(HsStablePtr sp, HsJSVal js_err) { + Capability *cap = &MainCapability; + StgWeak *w = (StgWeak *)deRefStablePtr(sp); + if (w->header.info == &stg_DEAD_WEAK_info) { + return; + } + ASSERT(w->header.info == &stg_WEAK_info); + StgTSO *tso = (StgTSO *)w->key; + ASSERT(tso->header.info == &stg_TSO_info); + throwToSelf( + cap, tso, + rts_apply( + cap, + &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, + rts_mkJSVal(cap, js_err))); +} + __attribute__((export_name("rts_freeStablePtr"))) void rts_freeStablePtr(HsStablePtr); void rts_freeStablePtr(HsStablePtr sp) { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6b9e7a2738bc89c1781e26d369f1ea6b06b32711 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6b9e7a2738bc89c1781e26d369f1ea6b06b32711 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/74101148/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 06:30:43 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sat, 15 Mar 2025 02:30:43 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] 2 commits: WIP pin raiseJSException Message-ID: <67d51e9346c74_328be725de344737ae@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: e7f3c404 by Cheng Shao at 2025-03-15T06:21:59+00:00 WIP pin raiseJSException - - - - - 7d7fbff1 by Cheng Shao at 2025-03-15T06:29:17+00:00 WIP - - - - - 3 changed files: - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - rts/wasm/JSFFI.c Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs ===================================== @@ -34,6 +34,7 @@ import GHC.Internal.Base import GHC.Internal.Exception.Type import GHC.Internal.Exts import GHC.Internal.IO +import GHC.Internal.IORef import GHC.Internal.Int import GHC.Internal.Stable import GHC.Internal.TopHandler (flushStdHandles) @@ -65,9 +66,14 @@ runIO res m = do let tmp@(JSString tmp_v) = toJSString $ displayException err js_promiseReject p tmp freeJSVal tmp_v - IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles) s0 of - (# s1, _ #) -> case stg_scheduler_loop# s1 of - (# s2, _ #) -> (# s2, p #) + post_action_ref <- newIORef $ pure () + IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles *> join (readIORef post_action_ref)) s0 of + (# s1, tso# #) -> case mkWeakNoFinalizer# tso# () s1 of + (# s2, w# #) -> case makeStablePtr# w# s2 of + (# s3, sp# #) -> case unIO (writeIORef post_action_ref $ js_promiseDelThrowTo p *> freeStablePtr (StablePtr $ unsafeCoerce# sp#)) s3 of + (# s4, _ #) -> case unIO (js_promiseAddThrowTo p $ StablePtr $ unsafeCoerce# sp#) s4 of + (# s5, _ #) -> case stg_scheduler_loop# s5 of + (# s6, _ #) -> (# s6, p #) runNonIO :: (JSVal -> a -> IO ()) -> a -> IO JSVal runNonIO res a = runIO res $ pure a @@ -75,6 +81,12 @@ runNonIO res a = runIO res $ pure a foreign import javascript unsafe "let res, rej; const p = new Promise((resolve, reject) => { res = resolve; rej = reject; }); p.resolve = res; p.reject = rej; return p;" js_promiseWithResolvers :: IO JSVal +foreign import javascript unsafe "$1.throwTo = (err) => __exports.rts_promiseThrowTo($2, err);" + js_promiseAddThrowTo :: JSVal -> StablePtr Any -> IO () + +foreign import javascript unsafe "$1.throwTo = () => {};" + js_promiseDelThrowTo :: JSVal -> IO () + foreign import prim "stg_scheduler_loopzh" stg_scheduler_loop# :: State# RealWorld -> (# State# RealWorld, () #) ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -5,6 +5,7 @@ {-# LANGUAGE UnliftedFFITypes #-} module GHC.Internal.Wasm.Prim.Imports ( + raiseJSException, stg_blockPromise, stg_messagePromiseUnit, stg_messagePromiseJSVal, @@ -98,13 +99,7 @@ stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> -- and prevents dmdanal from being naughty (# s4, _ #) -> case unIO (freeJSVal p) s4 of (# s5, _ #) -> - -- raiseJSException_closure is used by the RTS in case - -- the Promise is rejected, and it is likely a CAF. So - -- we need to keep it alive when we block waiting for - -- the Promise to resolve or reject, and also mark it - -- as OPAQUE just to be sure. - keepAlive# raiseJSException s5 $ - readMVar# mv# + readMVar# mv# s5 foreign import prim "stg_jsffi_check" stg_jsffi_check :: Any -> State# RealWorld -> (# State# RealWorld #) ===================================== rts/wasm/JSFFI.c ===================================== @@ -1,5 +1,6 @@ #include "Rts.h" #include "Prelude.h" +#include "RaiseAsync.h" #include "Schedule.h" #include "sm/Sanity.h" @@ -7,6 +8,7 @@ extern HsBool rts_JSFFI_flag; extern HsStablePtr rts_threadDelay_impl; +extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure; int __main_void(void); @@ -20,6 +22,7 @@ int __main_argc_argv(int argc, char *argv[]) { hs_init_ghc(&argc, &argv, __conf); // See Note [threadDelay on wasm] for details. rts_JSFFI_flag = HS_BOOL_TRUE; + getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure); rts_threadDelay_impl = getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure); return 0; } @@ -145,7 +148,6 @@ INLINE_HEADER void pushClosure (StgTSO *tso, StgWord c) { } extern const StgInfoTable stg_scheduler_loop_info; -extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; // schedule a future round of RTS scheduler loop via setImmediate(), // to avoid jamming the JavaScript main thread @@ -211,6 +213,25 @@ void rts_promiseReject(HsStablePtr, HsJSVal); void rts_promiseReject(HsStablePtr sp, HsJSVal js_err) mk_rtsPromiseCallback(rts_apply(cap, &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, rts_mkJSVal(cap, js_err))) +__attribute__((export_name("rts_promiseThrowTo"))) +void rts_promiseThrowTo(HsStablePtr, HsJSVal); +void rts_promiseThrowTo(HsStablePtr sp, HsJSVal js_err) { + Capability *cap = &MainCapability; + StgWeak *w = (StgWeak *)deRefStablePtr(sp); + if (w->header.info == &stg_DEAD_WEAK_info) { + return; + } + ASSERT(w->header.info == &stg_WEAK_info); + StgTSO *tso = (StgTSO *)w->key; + ASSERT(tso->header.info == &stg_TSO_info); + throwToSelf( + cap, tso, + rts_apply( + cap, + &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, + rts_mkJSVal(cap, js_err))); +} + __attribute__((export_name("rts_freeStablePtr"))) void rts_freeStablePtr(HsStablePtr); void rts_freeStablePtr(HsStablePtr sp) { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6b9e7a2738bc89c1781e26d369f1ea6b06b32711...7d7fbff193288da5621bc8a2933ee7b35cfaf818 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6b9e7a2738bc89c1781e26d369f1ea6b06b32711...7d7fbff193288da5621bc8a2933ee7b35cfaf818 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/fd88a4bb/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 06:44:36 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 15 Mar 2025 02:44:36 -0400 Subject: [Git][ghc/ghc][wip/T25647] rename and update note Message-ID: <67d521d4992ab_328be725e86287415b@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: e11e2062 by Patrick at 2025-03-15T14:44:24+08:00 rename and update note - - - - - 2 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -21,7 +21,7 @@ module GHC.Tc.TyCl ( tcFamTyPats, tcTyFamInstEqn, tcAddOpenTyFamInstCtxt, tcMkDataFamInstCtxt, tcAddDataFamInstCtxt, unravelFamInstPats, addConsistencyConstraints, - checkFamTelescope, tcFamInstLHSBinders + checkFamTelescope, quantifyFamInstLHSBinders ) where import GHC.Prelude @@ -249,9 +249,9 @@ tcTyClGroup (TyClGroup { group_tyclds = tyclds th_bndrs' `plusNameEnv` th_bndrs) } -tcFamInstLHSBinders :: TcLevel -> SkolemInfo -> HsOuterFamEqnTyVarBndrs GhcTc -> HsOuterFamEqnTyVarBndrs GhcRn +quantifyFamInstLHSBinders :: TcLevel -> SkolemInfo -> HsOuterFamEqnTyVarBndrs GhcTc -> HsOuterFamEqnTyVarBndrs GhcRn -> [TcTyVar] -> Type -> WantedConstraints -> IOEnv (Env TcGblEnv TcLclEnv) ([TyCoVar], [TcTyVar]) -tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted = do +quantifyFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted = do ; let outer_exp_tvs = scopedSort $ explicitOuterTyVars outer_bndrs ; let outer_imp_tvs = implicitOuterTyVars outer_bndrs @@ -267,7 +267,7 @@ tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted ; let final_tvs = scopedSort (qtvs ++ outer_wcs_imp_qtvs ++ outer_exp_tvs) -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] - ; traceTc "tcFamInstLHSBinders" $ + ; traceTc "quantifyFamInstLHSBinders" $ vcat [ text "lhs_ty:" <+> ppr lhs_ty , text "outer_bndrs:" <+> ppr outer_bndrs @@ -3479,7 +3479,7 @@ tcTyFamInstEqnGuts fam_tc mb_clsinfo outer_hs_bndrs hs_pats hs_rhs_ty ; traceTc "tcTyFamInstEqnGuts 0" (ppr outer_bndrs $$ ppr skol_info) -- -- See Note [Type variables in type families instance decl] - ; (final_tvs, qtvs) <- tcFamInstLHSBinders tclvl skol_info outer_bndrs outer_hs_bndrs wcs lhs_ty wanted + ; (final_tvs, qtvs) <- quantifyFamInstLHSBinders tclvl skol_info outer_bndrs outer_hs_bndrs wcs lhs_ty wanted -- See Note [Error on unconstrained meta-variables] in GHC.Tc.Utils.TcMType -- Example: typecheck/should_fail/T17301 ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -894,11 +894,6 @@ To begin with, let's clarify the terminology: * NonStandardTyVars: RuntimeRep, Multiplicity, Levity * UTVQ and UTVNQ would not be both present in the same equation. see Note [forall-or-nothing rule] -The old implementation: -* We are not doing any type variables defaulting for NonStandardTyVars at all. - But ITV are defaulted in other places. -* In rename phase, UTVQ or UTVNQ are collected to binders except WC. -* In typecheck phase, UTVQ or UTVNQ are treated as skolems, WC and ITV are given TauVars. Main goal: We want ITV defaulting happens in general just as we do in other places(Be it NonStandardTyVars or not). @@ -932,8 +927,8 @@ Implementation plan: * In typecheck phase, collect wildcards in local typecheck env, 1. emit wildcard type variables to the typecheck env using addWildCards in `tcAnonWildCardOcc` 2. we use captureWildCards to collect them. -* ITV: Assign them TauVars, do defaulting and quantification. -* WC and UTVNQ: Assign them TauVars, but skip defaulting, but quantify just like ITV. +* ITV: Assign them TauVars, do defaulting(DefaultNonStandardTyVars) and quantification. +* WC and UTVNQ: Assign them TauVars, but try to skip defaulting(TryNotToDefaultNonStandardTyVars), but quantify just like ITV. -} {- @@ -1016,7 +1011,7 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity , lhs_applied_kind , res_kind ) } - ; (final_tvs, qtvs) <- tcFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted + ; (final_tvs, qtvs) <- quantifyFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty wanted ; (final_tvs, non_user_tvs, lhs_ty, master_res_kind, instance_res_kind, stupid_theta) <- liftZonkM $ do View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e11e20628f27698445fbd5f70faa4a9d5b5863a3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e11e20628f27698445fbd5f70faa4a9d5b5863a3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/c609d41e/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 06:49:59 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 15 Mar 2025 02:49:59 -0400 Subject: [Git][ghc/ghc][wip/T25647] rename Message-ID: <67d52317cce63_328be73456c8c748e0@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: e7dd2d32 by Patrick at 2025-03-15T14:49:51+08:00 rename - - - - - 1 changed file: - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1784,7 +1784,7 @@ quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs = do { traceTc "quantifyTyVars {" ( vcat [ text "dvs =" <+> ppr dvs, - text "outer_wc_imp_qtvs=" <+> ppr outer_wcs_imp_dvs + text "outer_wcs_imp_dvs=" <+> ppr outer_wcs_imp_dvs ]) ; undefaulted <- defaultTyVars DefaultNonStandardTyVars dvs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e7dd2d325aae6e5b55679acd5aac86b07aa34180 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e7dd2d325aae6e5b55679acd5aac86b07aa34180 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/0c8b60a2/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 15 08:30:18 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sat, 15 Mar 2025 04:30:18 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] WIP Message-ID: <67d53a99c8644_3ab84d90c5b83929b@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: a01000cc by Cheng Shao at 2025-03-15T07:42:16+00:00 WIP - - - - - 2 changed files: - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - rts/wasm/JSFFI.c Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs ===================================== @@ -34,6 +34,7 @@ import GHC.Internal.Base import GHC.Internal.Exception.Type import GHC.Internal.Exts import GHC.Internal.IO +import GHC.Internal.IORef import GHC.Internal.Int import GHC.Internal.Stable import GHC.Internal.TopHandler (flushStdHandles) @@ -65,9 +66,14 @@ runIO res m = do let tmp@(JSString tmp_v) = toJSString $ displayException err js_promiseReject p tmp freeJSVal tmp_v - IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles) s0 of - (# s1, _ #) -> case stg_scheduler_loop# s1 of - (# s2, _ #) -> (# s2, p #) + post_action_ref <- newIORef $ pure () + IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles *> join (readIORef post_action_ref)) s0 of + (# s1, tso# #) -> case mkWeakNoFinalizer# tso# () s1 of + (# s2, w# #) -> case makeStablePtr# w# s2 of + (# s3, sp# #) -> case unIO (writeIORef post_action_ref $ js_promiseDelThrowTo p *> freeStablePtr (StablePtr $ unsafeCoerce# sp#)) s3 of + (# s4, _ #) -> case unIO (js_promiseAddThrowTo p $ StablePtr $ unsafeCoerce# sp#) s4 of + (# s5, _ #) -> case stg_scheduler_loop# s5 of + (# s6, _ #) -> (# s6, p #) runNonIO :: (JSVal -> a -> IO ()) -> a -> IO JSVal runNonIO res a = runIO res $ pure a @@ -75,6 +81,12 @@ runNonIO res a = runIO res $ pure a foreign import javascript unsafe "let res, rej; const p = new Promise((resolve, reject) => { res = resolve; rej = reject; }); p.resolve = res; p.reject = rej; return p;" js_promiseWithResolvers :: IO JSVal +foreign import javascript unsafe "$1.throwTo = (err) => __exports.rts_promiseThrowTo($2, err);" + js_promiseAddThrowTo :: JSVal -> StablePtr Any -> IO () + +foreign import javascript unsafe "$1.throwTo = () => {};" + js_promiseDelThrowTo :: JSVal -> IO () + foreign import prim "stg_scheduler_loopzh" stg_scheduler_loop# :: State# RealWorld -> (# State# RealWorld, () #) ===================================== rts/wasm/JSFFI.c ===================================== @@ -1,6 +1,8 @@ #include "Rts.h" #include "Prelude.h" +#include "RaiseAsync.h" #include "Schedule.h" +#include "Threads.h" #include "sm/Sanity.h" #if defined(__wasm_reference_types__) @@ -212,6 +214,27 @@ void rts_promiseReject(HsStablePtr, HsJSVal); void rts_promiseReject(HsStablePtr sp, HsJSVal js_err) mk_rtsPromiseCallback(rts_apply(cap, &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, rts_mkJSVal(cap, js_err))) +__attribute__((export_name("rts_promiseThrowTo"))) +void rts_promiseThrowTo(HsStablePtr, HsJSVal); +void rts_promiseThrowTo(HsStablePtr sp, HsJSVal js_err) { + Capability *cap = &MainCapability; + StgWeak *w = (StgWeak *)deRefStablePtr(sp); + if (w->header.info == &stg_DEAD_WEAK_info) { + return; + } + ASSERT(w->header.info == &stg_WEAK_info); + StgTSO *tso = (StgTSO *)w->key; + ASSERT(tso->header.info == &stg_TSO_info); + throwToSelf( + cap, tso, + rts_apply( + cap, + &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, + rts_mkJSVal(cap, js_err))); + tryWakeupThread(cap, tso); + rts_schedulerLoop(); +} + __attribute__((export_name("rts_freeStablePtr"))) void rts_freeStablePtr(HsStablePtr); void rts_freeStablePtr(HsStablePtr sp) { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a01000cc2d785627f3e98d561e28ba35de202ea6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a01000cc2d785627f3e98d561e28ba35de202ea6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/e6af0e37/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 09:37:46 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 15 Mar 2025 05:37:46 -0400 Subject: [Git][ghc/ghc][master] iface: Store logical parts of ModIface together Message-ID: <67d54a69f1a63_3ab84df2772c4801e@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b15fca2b by Matthew Pickering at 2025-03-15T05:36:40-04:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore ------------------------- - - - - - 17 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - ghc/Main.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -100,29 +100,37 @@ module GHC ( findGlobalAnns, mkNamePprCtxForModule, ModIface, - ModIface_( - mi_module, - mi_sig_of, - mi_hsc_src, - mi_hi_bytes, - mi_deps, - mi_exports, - mi_fixities, - mi_warns, - mi_anns, - mi_insts, - mi_fam_insts, - mi_rules, - mi_decls, - mi_extra_decls, - mi_top_env, - mi_trust, - mi_trust_pkg, - mi_complete_matches, - mi_docs, - mi_final_exts, - mi_ext_fields - ), + ModIface_( mi_mod_info + , mi_module + , mi_sig_of + , mi_hsc_src + , mi_iface_hash + , mi_deps + , mi_public + , mi_exports + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_defaults + , mi_simplified_core + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_abi_hashes + , mi_ext_fields + , mi_hi_bytes + , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn + ), pattern ModIface, SafeHaskellMode(..), ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -844,7 +844,7 @@ hscRecompStatus case recomp_if_result of OutOfDateItem reason mb_checked_iface -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ fmap (mi_iface_hash . mi_final_exts) mb_checked_iface + return $ HscRecompNeeded $ fmap mi_iface_hash mb_checked_iface UpToDateItem checked_iface -> do let lcl_dflags = ms_hspp_opts mod_summary if | not (backendGeneratesCode (backend lcl_dflags)) -> do @@ -862,7 +862,7 @@ hscRecompStatus , xopt LangExt.TemplateHaskell lcl_dflags -> do msg $ needsRecompileBecause THWithJS - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface | otherwise -> do -- Do need linkable @@ -918,7 +918,7 @@ hscRecompStatus return $ HscUpToDate checked_iface $ linkable OutOfDateItem reason _ -> do msg $ NeedsRecompile reason - return $ HscRecompNeeded $ Just $ mi_iface_hash $ mi_final_exts $ checked_iface + return $ HscRecompNeeded $ Just $ mi_iface_hash $ checked_iface -- | Check that the .o files produced by compilation are already up-to-date -- or not. @@ -968,10 +968,8 @@ loadByteCode iface mod_sum = do let this_mod = ms_mod mod_sum if_date = fromJust $ ms_iface_date mod_sum - case mi_extra_decls iface of - Just extra_decls -> do - let fi = WholeCoreBindings extra_decls this_mod (ms_location mod_sum) - (mi_foreign iface) + case iface_core_bindings iface (ms_location mod_sum) of + Just fi -> do return (UpToDateItem (Linkable if_date this_mod (NE.singleton (CoreBindings fi)))) _ -> return $ outOfDateItemBecause MissingBytecode Nothing @@ -1019,15 +1017,15 @@ compile_for_interpreter hsc_env use = -- | Assemble 'WholeCoreBindings' if the interface contains Core bindings. iface_core_bindings :: ModIface -> ModLocation -> Maybe WholeCoreBindings iface_core_bindings iface wcb_mod_location = - mi_extra_decls <&> \ wcb_bindings -> + mi_simplified_core <&> \(IfaceSimplifiedCore bindings foreign') -> WholeCoreBindings { - wcb_bindings, + wcb_bindings = bindings, wcb_module = mi_module, wcb_mod_location, - wcb_foreign = mi_foreign + wcb_foreign = foreign' } where - ModIface {mi_module, mi_extra_decls, mi_foreign} = iface + ModIface {mi_module, mi_simplified_core} = iface -- | Return an 'IO' that hydrates Core bindings and compiles them to bytecode if -- the interface contains any, using the supplied type env for typechecking. @@ -1376,7 +1374,7 @@ hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do -- dynamic interfaces. Hopefully both the dynamic and the non-dynamic -- interfaces stay in sync... -- - let change = old_iface /= Just (mi_iface_hash (mi_final_exts iface)) + let change = old_iface /= Just (mi_iface_hash iface) let dt = dynamicTooState dflags ===================================== compiler/GHC/HsToCore/Usage.hs ===================================== @@ -185,7 +185,7 @@ mkObjectUsage pit plugins fc hug th_links_needed th_pkgs_needed = do case miface of Nothing -> pprPanic "mkObjectUsage" (ppr m) Just iface -> - return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash (mi_final_exts iface)) + return $ UsageHomeModuleInterface (moduleName m) (toUnitId $ moduleUnit m) (mi_iface_hash iface) librarySpecToUsage :: LibrarySpec -> IO [Usage] librarySpecToUsage (Objects os) = traverse (fing Nothing) os @@ -278,10 +278,10 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names usg_entities = Map.toList ent_hashs, usg_safe = imp_safe } where - finsts_mod = mi_finsts (mi_final_exts iface) - hash_env = mi_hash_fn (mi_final_exts iface) - mod_hash = mi_mod_hash (mi_final_exts iface) - export_hash | depend_on_exports = Just (mi_exp_hash (mi_final_exts iface)) + finsts_mod = mi_finsts iface + hash_env = mi_hash_fn iface + mod_hash = mi_mod_hash iface + export_hash | depend_on_exports = Just (mi_exp_hash iface) | otherwise = Nothing by_is_safe (ImportedByUser imv) = imv_is_safe imv ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -41,34 +41,28 @@ data IfaceDynFlags = IfaceDynFlags , ifaceCallerCCFilters :: [CallerCcFilter] } -pprIfaceDynFlags :: (Fingerprint, Maybe IfaceDynFlags) -> SDoc -pprIfaceDynFlags (f, mflags) = - vcat $ - [ text "fingerprint:" <+> (ppr f) - ] - ++ case mflags of - Nothing -> [missingExtraFlagInfo] - Just (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) -> - [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) - , text "safe-mode:" <+> ppr a2 - , text "lang:" <+> ppr a3 - , text "exts:" <+> ppr a4 - , text "cpp-options:" - , nest 2 $ ppr a5 - , text "js-options:" - , nest 2 $ ppr a6 - , text "cmm-options:" - , nest 2 $ ppr a7 - , text "paths:" <+> hcat (map text a8) - , text "prof:" <+> ppr a9 - , text "ticky:" - , nest 2 $ vcat (map ppr a10) - , text "codegen:" - , nest 2 $ vcat (map ppr a11) - , text "fat-iface:" <+> ppr a12 - , text "debug-level:" <+> ppr a13 - , text "caller-cc-filters:" <+> ppr a14 - ] +pprIfaceDynFlags :: IfaceDynFlags -> SDoc +pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = + vcat [ text "main-is:" <+> (ppr $ fmap (fmap (text @SDoc)) a1) + , text "safe-mode:" <+> ppr a2 + , text "lang:" <+> ppr a3 + , text "exts:" <+> ppr a4 + , text "cpp-options:" + , nest 2 $ ppr a5 + , text "js-options:" + , nest 2 $ ppr a6 + , text "cmm-options:" + , nest 2 $ ppr a7 + , text "paths:" <+> hcat (map text a8) + , text "prof:" <+> ppr a9 + , text "ticky:" + , nest 2 $ vcat (map ppr a10) + , text "codegen:" + , nest 2 $ vcat (map ppr a11) + , text "fat-iface:" <+> ppr a12 + , text "debug-level:" <+> ppr a13 + , text "caller-cc-filters:" <+> ppr a14 + ] missingExtraFlagInfo :: SDoc missingExtraFlagInfo = text "flags: no detailed info, recompile with -fwrite-if-self-recomp-flags" ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -59,7 +59,6 @@ import GHC.Driver.Plugins import GHC.Iface.Warnings import GHC.Iface.Syntax import GHC.Iface.Ext.Fields -import GHC.Iface.Flags import GHC.Iface.Binary import GHC.Iface.Rename import GHC.Iface.Env @@ -74,7 +73,6 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Logger -import GHC.Utils.Fingerprint( Fingerprint ) import GHC.Settings.Constants @@ -644,7 +642,7 @@ loadInterface doc_str mod from & set_mi_fam_insts (panic "No mi_fam_insts in PIT") & set_mi_rules (panic "No mi_rules in PIT") & set_mi_anns (panic "No mi_anns in PIT") - & set_mi_extra_decls (panic "No mi_extra_decls in PIT") + & set_mi_simplified_core (panic "No mi_simplified_core in PIT") bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1083,7 +1081,7 @@ load_dynamic_too :: Logger -> NameCache -> UnitState -> DynFlags load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do read_file logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case Succeeded (dynIface, _) - | mi_mod_hash (mi_final_exts iface) == mi_mod_hash (mi_final_exts dynIface) + | mi_mod_hash iface == mi_mod_hash dynIface -> return (Succeeded ()) | otherwise -> do return $ (Failed $ DynamicHashMismatchError wanted_mod loc) @@ -1174,11 +1172,10 @@ ghcPrimIface & set_mi_exports ghcPrimExports & set_mi_decls [] & set_mi_fixities ghcPrimFixities - & set_mi_final_exts ((mi_final_exts empty_iface) - { mi_fix_fn = mkIfaceFixCache ghcPrimFixities - , mi_decl_warn_fn = mkIfaceDeclWarnCache ghcPrimWarns - , mi_export_warn_fn = mkIfaceExportWarnCache ghcPrimWarns - }) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) + & set_mi_decl_warn_fn (mkIfaceDeclWarnCache ghcPrimWarns) + & set_mi_export_warn_fn (mkIfaceExportWarnCache ghcPrimWarns) + & set_mi_fix_fn (mkIfaceFixCache ghcPrimFixities) & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] in GHC.Builtin.Utils & set_mi_warns (toIfaceWarnings ghcPrimWarns) -- See Note [GHC.Prim Deprecations] in GHC.Builtin.Utils @@ -1263,21 +1260,14 @@ pprModIface unit_state iface = vcat $ [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (withSelfRecomp iface empty $ \_ -> text "[self-recomp]") - <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) - <+> (if mi_finsts exts then text "[family instance module]" else Outputable.empty) + <+> (if mi_orphan iface then text "[orphan module]" else Outputable.empty) + <+> (if mi_finsts iface then text "[family instance module]" else Outputable.empty) <+> integer hiVersion - , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash exts)) - , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash (mi_final_exts iface))) - , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash exts)) - , withSelfRecomp iface empty $ \(ModIfaceSelfRecomp src usages flag_hash opt_hash hpc_hash plugin_hash) -> vcat - [ nest 2 (text "src_hash:" <+> ppr src) - , nest 2 (text "flags:" <+> pprIfaceDynFlags flag_hash) - , nest 2 (text "opt_hash:" <+> ppr opt_hash) - , nest 2 (text "hpc_hash:" <+> ppr hpc_hash) - , nest 2 (text "plugin_hash:" <+> ppr plugin_hash) - , vcat (map pprUsage usages) - ] - , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash exts)) + , nest 2 (text "ABI hash:" <+> ppr (mi_mod_hash iface)) + , nest 2 (text "interface hash:" <+> ppr (mi_iface_hash iface)) + , nest 2 (text "export-list hash:" <+> ppr (mi_exp_hash iface)) + , withSelfRecomp iface empty ppr + , nest 2 (text "orphan hash:" <+> ppr (mi_orphan_hash iface)) , nest 2 (text "sig of:" <+> ppr (mi_sig_of iface)) , nest 2 (text "where") , text "exports:" @@ -1288,10 +1278,14 @@ pprModIface unit_state iface , vcat (map pprIfaceAnnotation (mi_anns iface)) , pprFixities (mi_fixities iface) , vcat [ppr ver $$ nest 2 (ppr decl) | (ver,decl) <- mi_decls iface] - , case mi_extra_decls iface of + , case mi_simplified_core iface of Nothing -> empty - Just eds -> text "extra decls:" - $$ nest 2 (vcat ([ppr bs | bs <- eds])) + Just (IfaceSimplifiedCore eds fs) -> + vcat [ text "extra decls:" + $$ nest 2 (vcat ([ppr bs | bs <- eds])) + , text "foreign stubs:" + $$ nest 2 (ppr fs) + ] , vcat (map ppr (mi_insts iface)) , vcat (map ppr (mi_fam_insts iface)) , vcat (map ppr (mi_rules iface)) @@ -1303,7 +1297,6 @@ pprModIface unit_state iface , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where - exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" @@ -1329,35 +1322,6 @@ pprExport avail@(AvailTC n _) = pp_export [] = Outputable.empty pp_export names = braces (hsep (map ppr names)) -pprUsage :: Usage -> SDoc -pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } - = pprUsageImport mod hash safe -pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name - , usg_mod_hash = hash, usg_safe = safe - , usg_exports = exports, usg_entities = entities } - = pprUsageImport (mkModule unit_id mod_name) hash safe $$ - nest 2 ( - maybe Outputable.empty (\v -> text "exports: " <> ppr v) exports $$ - vcat [ ppr n <+> ppr v | (n,v) <- entities ] - ) -pprUsage usage at UsageFile{} - = hsep [text "addDependentFile", - doubleQuotes (ftext (usg_file_path usage)), - ppr (usg_file_hash usage)] -pprUsage usage at UsageMergedRequirement{} - = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] -pprUsage usage at UsageHomeModuleInterface{} - = hsep [text "implementation", ppr (usg_mod_name usage) - , ppr (usg_unit_id usage) - , ppr (usg_iface_hash usage)] - -pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc -pprUsageImport mod hash safe - = hsep [ text "import", pp_safe, ppr mod - , ppr hash ] - where - pp_safe | safe = text "safe" - | otherwise = text " -/ " pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -88,13 +88,13 @@ import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModSummary import GHC.Unit.Module.Deps -import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (encodeIfaceForeign, emptyIfaceForeign) import Data.Function import Data.List ( sortBy ) import Data.Ord import Data.IORef - +import Data.Traversable {- ************************************************************************ @@ -143,11 +143,13 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos stubs foreign_files = updateDecl (mi_decls partial_iface) mb_stg_infos mb_cmm_infos -- See Note [Foreign stubs and TH bytecode linking] - foreign_ <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + mi_simplified_core <- for (mi_simplified_core partial_iface) $ \simpl_core -> do + fs <- encodeIfaceForeign (hsc_logger hsc_env) (hsc_dflags hsc_env) stubs foreign_files + return $ (simpl_core { mi_sc_foreign = fs }) full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env $ set_mi_foreign foreign_ $ set_mi_decls decls partial_iface + addFingerprints hsc_env $ set_mi_simplified_core mi_simplified_core $ set_mi_decls decls partial_iface -- Debug printing let unit_state = hsc_units hsc_env @@ -289,7 +291,7 @@ mkIface_ :: HscEnv -> Module -> CoreProgram -> HscSource -> NameEnv FixItem -> Warnings GhcRn -> Bool -> SafeHaskellMode - -> Maybe ModIfaceSelfRecomp + -> Maybe IfaceSelfRecomp -> Maybe Docs -> ModDetails -> PartialModIface @@ -316,8 +318,8 @@ mkIface_ hsc_env entities = typeEnvElts type_env show_linear_types = xopt LangExt.LinearTypes (hsc_dflags hsc_env) - extra_decls = if gopt Opt_WriteIfSimplifiedCore dflags then Just [ toIfaceTopBind b | b <- core_prog ] - else Nothing + simplified_core = if gopt Opt_WriteIfSimplifiedCore dflags then Just (IfaceSimplifiedCore [ toIfaceTopBind b | b <- core_prog ] emptyIfaceForeign) + else Nothing decls = [ tyThingToIfaceDecl show_linear_types entity | entity <- entities, let name = getName entity, @@ -370,12 +372,12 @@ mkIface_ hsc_env & set_mi_anns annotations & set_mi_top_env rdrs & set_mi_decls decls - & set_mi_extra_decls extra_decls + & set_mi_simplified_core simplified_core & set_mi_trust trust_info & set_mi_trust_pkg pkg_trust_req & set_mi_complete_matches (icomplete_matches) & set_mi_docs docs - & set_mi_final_exts () + & set_mi_abi_hashes () & set_mi_ext_fields emptyExtensibleFields & set_mi_hi_bytes PartialIfaceBinHandle ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -88,6 +88,7 @@ import Data.Ord import Data.Containers.ListUtils import Data.Bifunctor import GHC.Iface.Errors.Ppr +import Data.Functor {- ----------------------------------------------- @@ -325,8 +326,8 @@ check_old_iface hsc_env mod_summary maybe_iface maybe_dyn_iface <- liftIO $ loadIface (setDynamicNow dflags) (msDynHiFilePath mod_summary) case maybe_dyn_iface of Nothing -> return $ outOfDateItemBecause MissingDynHiFile Nothing - Just dyn_iface | mi_iface_hash (mi_final_exts dyn_iface) - /= mi_iface_hash (mi_final_exts normal_iface) + Just dyn_iface | mi_iface_hash dyn_iface + /= mi_iface_hash normal_iface -> return $ outOfDateItemBecause MismatchedDynHiFile Nothing Just {} -> return res _ -> return res @@ -382,7 +383,7 @@ check_old_iface hsc_env mod_summary maybe_iface checkVersions :: HscEnv -> ModSummary -> ModIface -- Old interface - -> ModIfaceSelfRecomp + -> IfaceSelfRecomp -> IfG (MaybeValidated ModIface) checkVersions hsc_env mod_summary iface self_recomp = do { liftIO $ trace_hi_diffs logger @@ -435,7 +436,7 @@ checkVersions hsc_env mod_summary iface self_recomp -- | Check if any plugins are requesting recompilation -checkPlugins :: Plugins -> ModIfaceSelfRecomp -> IfG RecompileRequired +checkPlugins :: Plugins -> IfaceSelfRecomp -> IfG RecompileRequired checkPlugins plugins self_recomp = liftIO $ do recomp <- recompPlugins plugins let new_fingerprint = fingerprintPluginRecompile recomp @@ -528,10 +529,10 @@ checkHie dflags mod_summary = _ -> UpToDate -- | Check the flags haven't changed -checkFlagHash :: HscEnv -> Module -> ModIfaceSelfRecomp -> IO RecompileRequired +checkFlagHash :: HscEnv -> Module -> IfaceSelfRecomp -> IO RecompileRequired checkFlagHash hsc_env iface_mod self_recomp = do let logger = hsc_logger hsc_env - let (old_fp, old_flags) = mi_sr_flag_hash self_recomp + let FingerprintWithValue old_fp old_flags = mi_sr_flag_hash self_recomp (new_fp, new_flags) <- fingerprintDynFlags hsc_env iface_mod putNameLiterally if old_fp == new_fp then up_to_date logger (text "Module flags unchanged") @@ -573,7 +574,7 @@ checkIfaceFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) if a' == b' then pure () else modify (([ text s <+> text "flags changed"] ++ [diffSimple p a b]) ++) -- | Check the optimisation flags haven't changed -checkOptimHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkOptimHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkOptimHash hsc_env iface = do let logger = hsc_logger hsc_env let old_hash = mi_sr_opt_hash iface @@ -589,7 +590,7 @@ checkOptimHash hsc_env iface = do old_hash new_hash -- | Check the HPC flags haven't changed -checkHpcHash :: HscEnv -> ModIfaceSelfRecomp -> IO RecompileRequired +checkHpcHash :: HscEnv -> IfaceSelfRecomp -> IO RecompileRequired checkHpcHash hsc_env self_recomp = do let logger = hsc_logger hsc_env let old_hash = mi_sr_hpc_hash self_recomp @@ -606,7 +607,7 @@ checkHpcHash hsc_env self_recomp = do -- Check that the set of signatures we are merging in match. -- If the -unit-id flags change, this can change too. -checkMergedSignatures :: HscEnv -> ModSummary -> ModIfaceSelfRecomp -> IO RecompileRequired +checkMergedSignatures :: HscEnv -> ModSummary -> IfaceSelfRecomp -> IO RecompileRequired checkMergedSignatures hsc_env mod_summary self_recomp = do let logger = hsc_logger hsc_env let unit_state = hsc_units hsc_env @@ -748,7 +749,7 @@ checkModUsage _ UsagePackageModule{ logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChanged (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) -- We only track the ABI hash of package modules, rather than -- individual entity usages, so if the ABI hash changes we must -- recompile. This is safe but may entail more recompilation when @@ -758,7 +759,7 @@ checkModUsage _ UsageMergedRequirement{ usg_mod = mod, usg_mod_hash = old_mod_ha logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedRaw (moduleName mod) - checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash (mi_final_exts iface)) + checkModuleFingerprint logger reason old_mod_hash (mi_mod_hash iface) checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name , usg_unit_id = uid , usg_iface_hash = old_mod_hash } = do @@ -766,7 +767,7 @@ checkModUsage _ UsageHomeModuleInterface{ usg_mod_name = mod_name logger <- getLogger needInterface mod $ \iface -> do let reason = ModuleChangedIface mod_name - checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash (mi_final_exts iface)) + checkIfaceFingerprint logger reason old_mod_hash (mi_iface_hash iface) checkModUsage _ UsageHomeModule{ usg_mod_name = mod_name, @@ -779,9 +780,9 @@ checkModUsage _ UsageHomeModule{ logger <- getLogger needInterface mod $ \iface -> do let - new_mod_hash = mi_mod_hash (mi_final_exts iface) - new_decl_hash = mi_hash_fn (mi_final_exts iface) - new_export_hash = mi_exp_hash (mi_final_exts iface) + new_mod_hash = mi_mod_hash iface + new_decl_hash = mi_hash_fn iface + new_export_hash = mi_exp_hash iface reason = ModuleChanged (moduleName mod) @@ -986,7 +987,7 @@ we use is: -- | Compute the information needed for self-recompilation checking. This -- information can be computed before the backend phase. -mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO ModIfaceSelfRecomp +mkSelfRecomp :: HscEnv -> Module -> Fingerprint -> [Usage] -> IO IfaceSelfRecomp mkSelfRecomp hsc_env this_mod src_hash usages = do let dflags = hsc_dflags hsc_env @@ -1000,10 +1001,10 @@ mkSelfRecomp hsc_env this_mod src_hash usages = do let include_detailed_flags (flag_hash, flags) = if gopt Opt_WriteSelfRecompFlags dflags - then (flag_hash, Just flags) - else (flag_hash, Nothing) + then FingerprintWithValue flag_hash (Just flags) + else FingerprintWithValue flag_hash Nothing - return (ModIfaceSelfRecomp + return (IfaceSelfRecomp { mi_sr_flag_hash = include_detailed_flags dyn_flags_info , mi_sr_hpc_hash = hpc_hash , mi_sr_opt_hash = opt_hash @@ -1018,28 +1019,92 @@ addFingerprints :: HscEnv -> PartialModIface -> IO ModIface -addFingerprints hsc_env iface0 - = do - eps <- hscEPS hsc_env - let - decls = mi_decls iface0 - decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings $ mi_warns iface0) - export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ mi_warns iface0) - fix_fn = mkIfaceFixCache (mi_fixities iface0) +addFingerprints hsc_env iface0 = do + (abiHashes, caches, decls_w_hashes) <- addAbiHashes hsc_env (mi_mod_info iface0) (mi_public iface0) (mi_deps iface0) + + -- put the declarations in a canonical order, sorted by OccName + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ + [(getOccName d, e) | e@(_, d) <- decls_w_hashes] + + -- This key is safe because mi_extra_decls contains tidied things. + getOcc (IfGblTopBndr b) = getOccName b + getOcc (IfLclTopBndr fs _ _ details) = + case details of + IfRecSelId { ifRecSelFirstCon = first_con } + -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) + _ -> mkVarOccFS (ifLclNameFS fs) + + binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () + binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) + + sorted_extra_decls :: Maybe IfaceSimplifiedCore + sorted_extra_decls = mi_simplified_core iface0 <&> \simpl_core -> + IfaceSimplifiedCore (sortOn binding_key (mi_sc_extra_decls simpl_core)) (mi_sc_foreign simpl_core) + + -- The interface hash depends on: + -- - the ABI hash, plus + -- - the things which can affect whether a module is recompiled + -- - the module level annotations, + -- - deps (home and external packages, dependent files) + iface_hash <- computeFingerprint putNameLiterally + (mi_abi_mod_hash abiHashes, + mi_self_recomp_info iface0, + mi_deps iface0) + + let final_iface = completePartialModIface iface0 iface_hash + sorted_decls sorted_extra_decls abiHashes caches + -- + return final_iface + + + +-- The ABI hash should depend on everything in IfacePublic +-- This is however computed in a very convoluted way, so be careful your +-- addition ends up in the right place. In essence all this function does is +-- compute a hash of the arguments. +-- +-- Why the convoluted way? Hashing individual declarations allows us to do fine-grained +-- recompilation checking for home package modules, which record precisely what they use +-- from each module. +addAbiHashes :: HscEnv -> IfaceModInfo -> PartialIfacePublic -> Dependencies -> IO (IfaceAbiHashes, IfaceCache, [(Fingerprint, IfaceDecl)]) +addAbiHashes hsc_env info iface_public deps = do + eps <- hscEPS hsc_env + let + -- If you have arrived here by accident then congratulations, + -- you have discovered the ABI hash. Your reward is to update the ABI hash to + -- account for your change to the interface file. Omitting your field using a + -- wildcard may lead to some unfortunate consequences. + + -- MP: TODO: Existing bug where defaults, trust_pkg and complete are not taken into account + -- when computing the ABI hash. + IfacePublic exports fixities warns anns decls _defaults insts fam_insts rules trust _trust_pkg _complete _cache () = iface_public + -- And these fields of deps should be in IfacePublic, but in good time. + Dependencies _ _ _ sig_mods trusted_pkgs boot_mods orph_mods fis_mods = deps + decl_warn_fn = mkIfaceDeclWarnCache (fromIfaceWarnings warns) + export_warn_fn = mkIfaceExportWarnCache (fromIfaceWarnings $ warns) + fix_fn = mkIfaceFixCache fixities + + this_mod = mi_mod_info_module info + semantic_mod = mi_mod_info_semantic_module info + (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph insts + (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph rules + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph fam_insts + ann_fn = mkIfaceAnnCache anns -- The ABI of a declaration represents everything that is made -- visible about the declaration that a client can depend on. -- see IfaceDeclABI below. - declABI :: IfaceDecl -> IfaceDeclABI + declABI :: IfaceDecl -> IfaceDeclABI -- TODO: I'm not sure if this should be semantic_mod or this_mod. -- See also Note [Identity versus semantic module] - declABI decl = (this_mod, decl, extras) + declABI decl = (this_mod, decl, extras) where extras = declExtras fix_fn ann_fn non_orph_rules non_orph_insts non_orph_fis top_lvl_name_env decl -- This is used for looking up the Name of a default method -- from its OccName. See Note [default method Name] - top_lvl_name_env = + top_lvl_name_env = mkOccEnv [ (nameOccName nm, nm) | IfaceId { ifName = nm } <- decls ] @@ -1047,15 +1112,15 @@ addFingerprints hsc_env iface0 -- This is computed by finding the free external names of each -- declaration, including IfaceDeclExtras (things that a -- declaration implicitly depends on). - edges :: [ Node OccName IfaceDeclABI ] - edges = [ DigraphNode abi (getOccName decl) out + edges :: [ Node OccName IfaceDeclABI ] + edges = [ DigraphNode abi (getOccName decl) out | decl <- decls , let abi = declABI decl , let out = localOccs $ freeNamesDeclABI abi ] - name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) - localOccs = + name_module n = assertPpr (isExternalName n) (ppr n) (nameModule n) + localOccs = map (getParent . getOccName) -- NB: names always use semantic module, so -- filtering must be on the semantic module! @@ -1073,17 +1138,17 @@ addFingerprints hsc_env iface0 -- maps OccNames to their parents in the current module. -- e.g. a reference to a constructor must be turned into a reference -- to the TyCon for the purposes of calculating dependencies. - parent_map :: OccEnv OccName - parent_map = foldl' extend emptyOccEnv decls + parent_map :: OccEnv OccName + parent_map = foldl' extend emptyOccEnv decls where extend env d = extendOccEnvList env [ (b,n) | b <- ifaceDeclImplicitBndrs d ] where n = getOccName d -- Strongly-connected groups of declarations, in dependency order - groups :: [SCC IfaceDeclABI] - groups = stronglyConnCompFromEdgedVerticesOrd edges + groups :: [SCC IfaceDeclABI] + groups = stronglyConnCompFromEdgedVerticesOrd edges - global_hash_fn = mkHashFun hsc_env eps + global_hash_fn = mkHashFun hsc_env eps -- How to output Names when generating the data to fingerprint. -- Here we want to output the fingerprint for each top-level @@ -1091,9 +1156,9 @@ addFingerprints hsc_env iface0 -- module. In this way, the fingerprint for a declaration will -- change if the fingerprint for anything it refers to (transitively) -- changes. - mk_put_name :: OccEnv (OccName,Fingerprint) + mk_put_name :: OccEnv (OccName,Fingerprint) -> WriteBinHandle -> Name -> IO () - mk_put_name local_env bh name + mk_put_name local_env bh name | isWiredInName name = putNameLiterally bh name -- wired-in names don't have fingerprints | otherwise @@ -1120,21 +1185,21 @@ addFingerprints hsc_env iface0 -- take a strongly-connected group of declarations and compute -- its fingerprint. - fingerprint_group :: (OccEnv (OccName,Fingerprint), + fingerprint_group :: (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) -> SCC IfaceDeclABI -> IO (OccEnv (OccName,Fingerprint), [(Fingerprint,IfaceDecl)]) - fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) - = do let hash_fn = mk_put_name local_env - decl = abiDecl abi + fingerprint_group (local_env, decls_w_hashes) (AcyclicSCC abi) + = do let hash_fn = mk_put_name local_env + decl = abiDecl abi --pprTrace "fingerprinting" (ppr (ifName decl) ) $ do - hash <- computeFingerprint hash_fn abi - env' <- extend_hash_env local_env (hash,decl) - return (env', (hash,decl) : decls_w_hashes) + hash <- computeFingerprint hash_fn abi + env' <- extend_hash_env local_env (hash,decl) + return (env', (hash,decl) : decls_w_hashes) - fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) + fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) = do let stable_abis = sortBy cmp_abiNames abis stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env @@ -1150,33 +1215,27 @@ addFingerprints hsc_env iface0 return (local_env2, pairs ++ decls_w_hashes) -- Make a fingerprint from the ordinal position of a binding in its group. - mkRecFingerprint :: Word64 -> Fingerprint - mkRecFingerprint i = Fingerprint 0 i + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i - bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint - bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. -- - extend_hash_env :: OccEnv (OccName,Fingerprint) + extend_hash_env :: OccEnv (OccName,Fingerprint) -> (Fingerprint,IfaceDecl) -> IO (OccEnv (OccName,Fingerprint)) - extend_hash_env env0 (hash,d) = + extend_hash_env env0 (hash,d) = return (foldr (\(b,fp) env -> extendOccEnv env b (b,fp)) env0 (ifaceDeclFingerprints hash d)) -- - (local_env, decls_w_hashes) <- + (local_env, decls_w_hashes) <- foldM fingerprint_group (emptyOccEnv, []) groups - -- when calculating fingerprints, we always need to use canonical ordering - -- for lists of things. The mi_deps has various lists of modules and - -- suchlike, which are stored in canonical order: - let sorted_deps :: Dependencies - sorted_deps = mi_deps iface0 - -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way -- that changes in orphans get propagated all the way up the @@ -1202,10 +1261,11 @@ addFingerprints hsc_env iface0 -- External. It's true that Home1 will get rebuilt if the orphans -- of External, but we also need to make sure Home2 gets rebuilt -- as well. See #12733 for more details. - let orph_mods - = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] - $ dep_orphs sorted_deps - dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods + let orph_mods_no_self + = filter (/= this_mod) -- Note [Do not update EPS with your own hi-boot] + $ orph_mods + dep_orphan_hashes <- getOrphanHashes hsc_env orph_mods_no_self + -- Note [Do not update EPS with your own hi-boot] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1216,26 +1276,26 @@ addFingerprints hsc_env iface0 -- instances yourself, no need to consult hs-boot; if you do load the -- interface into EPS, you will see a duplicate orphan instance. - orphan_hash <- computeFingerprint (mk_put_name local_env) + orphan_hash <- computeFingerprint (mk_put_name local_env) (map ifDFun orph_insts, orph_rules, orph_fis) - -- Hash of the transitive things in dependencies - dep_hash <- computeFingerprint putNameLiterally - (dep_sig_mods (mi_deps iface0), - dep_boot_mods (mi_deps iface0), - -- Trusted packages are like orphans - dep_trusted_pkgs (mi_deps iface0), + -- Hash of the transitive things in dependencies + dep_hash <- computeFingerprint putNameLiterally + (sig_mods, + boot_mods, + -- Trusted packages are like orphans + trusted_pkgs, -- See Note [Export hash depends on non-orphan family instances] - dep_finsts (mi_deps iface0) ) + fis_mods ) - -- the export list hash doesn't depend on the fingerprints of - -- the Names it mentions, only the Names themselves, hence putNameLiterally. - export_hash <- computeFingerprint putNameLiterally - (mi_exports iface0, + -- the export list hash doesn't depend on the fingerprints of + -- the Names it mentions, only the Names themselves, hence putNameLiterally. + export_hash <- computeFingerprint putNameLiterally + (exports, orphan_hash, dep_hash, dep_orphan_hashes, - mi_trust iface0) + trust) -- Make sure change of Safe Haskell mode causes recomp. -- Note [Export hash depends on non-orphan family instances] @@ -1266,79 +1326,44 @@ addFingerprints hsc_env iface0 -- (also we didn't store it anywhere!) -- - -- put the declarations in a canonical order, sorted by OccName - let sorted_decls :: [(Fingerprint, IfaceDecl)] - sorted_decls = Map.elems $ Map.fromList $ - [(getOccName d, e) | e@(_, d) <- decls_w_hashes] - -- This key is safe because mi_extra_decls contains tidied things. - getOcc (IfGblTopBndr b) = getOccName b - getOcc (IfLclTopBndr fs _ _ details) = - case details of - IfRecSelId { ifRecSelFirstCon = first_con } - -> mkRecFieldOccFS (getOccFS first_con) (ifLclNameFS fs) - _ -> mkVarOccFS (ifLclNameFS fs) - - binding_key (IfaceNonRec b _) = IfaceNonRec (getOcc b) () - binding_key (IfaceRec bs) = IfaceRec (map (\(b, _) -> (getOcc b, ())) bs) - - sorted_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - sorted_extra_decls = sortOn binding_key <$> mi_extra_decls iface0 - - -- the ABI hash depends on: - -- - decls - -- - export list - -- - orphans - -- - deprecations - -- - flag abi hash - -- - foreign stubs and files - mod_hash <- computeFingerprint putNameLiterally - (map fst sorted_decls, + -- the ABI hash depends on: + -- - decls + -- - export list + -- - orphans + -- - deprecations + -- - flag abi hash + mod_hash <- computeFingerprint putNameLiterally + (sort (map fst decls_w_hashes), export_hash, -- includes orphan_hash - mi_warns iface0, - mi_foreign iface0) - - - -- The interface hash depends on: - -- - the ABI hash, plus - -- - the things which can affect whether a module is recompiled - -- - the module level annotations, - -- - deps (home and external packages, dependent files) - iface_hash <- computeFingerprint putNameLiterally - (mod_hash, - ann_fn (mkVarOccFS (fsLit "module")), -- See mkIfaceAnnCache - mi_self_recomp_info iface0, - sorted_deps ) + ann_fn AnnModule, + warns) - let - final_iface_exts = ModIfaceBackend - { mi_mod_hash = mod_hash - , mi_iface_hash = iface_hash - , mi_orphan = not ( all ifRuleAuto orph_rules + -- Surely the ABI depends on "module" annotations? + -- Also named defaults + + + + let + final_iface_exts = IfaceAbiHashes + { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = not ( all ifRuleAuto orph_rules -- See Note [Orphans and auto-generated rules] && null orph_insts && null orph_fis) - , mi_finsts = not (null (mi_fam_insts iface0)) - , mi_exp_hash = export_hash - , mi_orphan_hash = orphan_hash - , mi_decl_warn_fn = decl_warn_fn - , mi_export_warn_fn = export_warn_fn - , mi_fix_fn = fix_fn - , mi_hash_fn = lookupOccEnv local_env + , mi_abi_finsts = not (null fam_insts) + , mi_abi_exp_hash = export_hash + , mi_abi_orphan_hash = orphan_hash } - final_iface = completePartialModIface iface0 - sorted_decls sorted_extra_decls final_iface_exts - -- - return final_iface + caches = IfaceCache + { mi_cache_decl_warn_fn = decl_warn_fn + , mi_cache_export_warn_fn = export_warn_fn + , mi_cache_fix_fn = fix_fn + , mi_cache_hash_fn = lookupOccEnv local_env + } + return (final_iface_exts, caches, decls_w_hashes) where - this_mod = mi_module iface0 - semantic_mod = mi_semantic_module iface0 - (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0) - (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) - (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - ann_fn = mkIfaceAnnCache (mi_anns iface0) - -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules -- (in particular, the orphan modules which are transitively imported by the @@ -1378,7 +1403,7 @@ getOrphanHashes hsc_env mods = do get_orph_hash mod = do iface <- initIfaceLoad hsc_env . withIfaceErr ctx $ loadInterface (text "getOrphanHashes") mod ImportBySystem - return (mi_orphan_hash (mi_final_exts iface)) + return (mi_orphan_hash iface) mapM get_orph_hash mods @@ -1531,7 +1556,7 @@ instance Binary IfaceIdExtras where put_ bh (IdExtras fix rules anns)= do { put_ bh fix; put_ bh rules; put_ bh anns } declExtras :: (OccName -> Maybe Fixity) - -> (OccName -> [AnnPayload]) + -> (AnnCacheKey -> [AnnPayload]) -> OccEnv [IfaceRule] -> OccEnv [IfaceClsInst] -> OccEnv [IfaceFamInst] @@ -1546,10 +1571,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl IfaceDataExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n) ++ map ifDFun (lookupOccEnvL inst_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) (map (id_extras . occName . ifConName) (visibleIfConDecls cons)) IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} -> - IfaceClassExtras (fix_fn n) insts (ann_fn n) meths defms + IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms where insts = (map ifDFun $ (concatMap at_extras ats) ++ lookupOccEnvL inst_env n) @@ -1562,17 +1587,16 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env decl , let dmOcc = mkDefaultMethodOcc (nameOccName bndr) , Just dmName <- [lookupOccEnv dm_env dmOcc] ] IfaceSynonym{} -> IfaceSynonymExtras (fix_fn n) - (ann_fn n) + (ann_fn (AnnOccName n)) IfaceFamily{} -> IfaceFamilyExtras (fix_fn n) (map ifFamInstAxiom (lookupOccEnvL fi_env n)) - (ann_fn n) + (ann_fn (AnnOccName n)) _other -> IfaceOtherDeclExtras where n = getOccName decl - id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn occ) + id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl) - {- Note [default method Name] (see also #15970) ~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1685,20 +1709,25 @@ mkHashFun hsc_env eps name -- just one of the many horrible hacks in the backpack -- implementation. $ loadInterface (text "lookupVers2") mod ImportBySystem - return $ snd (mi_hash_fn (mi_final_exts iface) occ `orElse` + return $ snd (mi_hash_fn iface occ `orElse` pprPanic "lookupVers1" (ppr mod <+> ppr occ)) +data AnnCacheKey = AnnModule | AnnOccName OccName + -- | Creates cached lookup for the 'mi_anns' field of ModIface -- Hackily, we use "module" as the OccName for any module-level annotations -mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload] +mkIfaceAnnCache :: [IfaceAnnotation] -> AnnCacheKey -> [AnnPayload] mkIfaceAnnCache anns - = \n -> lookupOccEnv env n `orElse` [] + = \n -> case n of + AnnModule -> module_anns + AnnOccName occn -> lookupOccEnv env occn `orElse` [] where - pair (IfaceAnnotation target value) = - (case target of - NamedTarget occn -> occn - ModuleTarget _ -> mkVarOccFS (fsLit "module") - , [value]) + (module_anns, occ_anns) = partitionEithers $ map classify anns + classify (IfaceAnnotation target value) = + case target of + NamedTarget occn -> Right (occn, [value]) + ModuleTarget _ -> Left value + -- flipping (++), so the first argument is always short - env = mkOccEnv_C (flip (++)) (map pair anns) + env = mkOccEnv_C (flip (++)) occ_anns ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -1,5 +1,5 @@ module GHC.Iface.Recomp.Types ( - ModIfaceSelfRecomp(..), + IfaceSelfRecomp(..), IfaceDynFlags(..), pprIfaceDynFlags, missingExtraFlagInfo, @@ -9,7 +9,9 @@ import GHC.Prelude import GHC.Fingerprint import GHC.Utils.Outputable import GHC.Iface.Flags +import GHC.Types.SafeHaskell import GHC.Unit.Module.Deps +import GHC.Unit.Module import GHC.Utils.Binary @@ -59,8 +61,8 @@ proper way. -- itself. -- -- See Note [Self recompilation information in interface files] -data ModIfaceSelfRecomp = - ModIfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint +data IfaceSelfRecomp = + IfaceSelfRecomp { mi_sr_src_hash :: !Fingerprint -- ^ Hash of the .hs source, used for recompilation checking. , mi_sr_usages :: [Usage] -- ^ Usages; kept sorted so that it's easy to decide @@ -69,7 +71,7 @@ data ModIfaceSelfRecomp = -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - , mi_sr_flag_hash :: !(Fingerprint, Maybe IfaceDynFlags) + , mi_sr_flag_hash :: !(FingerprintWithValue IfaceDynFlags) -- ^ Hash of the important flags used when compiling the module, excluding -- optimisation flags , mi_sr_opt_hash :: !Fingerprint @@ -81,8 +83,8 @@ data ModIfaceSelfRecomp = } -instance Binary ModIfaceSelfRecomp where - put_ bh (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do +instance Binary IfaceSelfRecomp where + put_ bh (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = do put_ bh mi_sr_src_hash lazyPut bh mi_sr_usages put_ bh mi_sr_flag_hash @@ -97,19 +99,58 @@ instance Binary ModIfaceSelfRecomp where opt_hash <- get bh hpc_hash <- get bh plugin_hash <- get bh - return $ ModIfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } + return $ IfaceSelfRecomp { mi_sr_src_hash = src_hash, mi_sr_usages = usages, mi_sr_flag_hash = flag_hash, mi_sr_opt_hash = opt_hash, mi_sr_hpc_hash = hpc_hash, mi_sr_plugin_hash = plugin_hash } -instance Outputable ModIfaceSelfRecomp where - ppr (ModIfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) +instance Outputable IfaceSelfRecomp where + ppr (IfaceSelfRecomp{mi_sr_src_hash, mi_sr_usages, mi_sr_flag_hash, mi_sr_opt_hash, mi_sr_hpc_hash, mi_sr_plugin_hash}) = vcat [text "Self-Recomp" , nest 2 (vcat [ text "src hash:" <+> ppr mi_sr_src_hash - , text "usages:" <+> ppr (length mi_sr_usages) - , text "flags:" <+> pprIfaceDynFlags mi_sr_flag_hash + , text "flags:" <+> pprFingerprintWithValue missingExtraFlagInfo (fmap pprIfaceDynFlags mi_sr_flag_hash) , text "opt hash:" <+> ppr mi_sr_opt_hash , text "hpc hash:" <+> ppr mi_sr_hpc_hash , text "plugin hash:" <+> ppr mi_sr_plugin_hash + , text "usages:" <+> ppr (map pprUsage mi_sr_usages) ])] -instance NFData ModIfaceSelfRecomp where - rnf (ModIfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) - = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () \ No newline at end of file +instance NFData IfaceSelfRecomp where + rnf (IfaceSelfRecomp src_hash usages flag_hash opt_hash hpc_hash plugin_hash) + = rnf src_hash `seq` rnf usages `seq` rnf flag_hash `seq` rnf opt_hash `seq` rnf hpc_hash `seq` rnf plugin_hash `seq` () + +pprFingerprintWithValue :: SDoc -> FingerprintWithValue SDoc -> SDoc +pprFingerprintWithValue missingInfo (FingerprintWithValue fp mflags) + = vcat $ + [ text "fingerprint:" <+> (ppr fp) + ] + ++ case mflags of + Nothing -> [missingInfo] + Just doc -> [doc] + +pprUsage :: Usage -> SDoc +pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } + = pprUsageImport mod hash safe +pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name + , usg_mod_hash = hash, usg_safe = safe + , usg_exports = exports, usg_entities = entities } + = pprUsageImport (mkModule unit_id mod_name) hash safe $$ + nest 2 ( + maybe empty (\v -> text "exports: " <> ppr v) exports $$ + vcat [ ppr n <+> ppr v | (n,v) <- entities ] + ) +pprUsage usage at UsageFile{} + = hsep [text "addDependentFile", + doubleQuotes (ftext (usg_file_path usage)), + ppr (usg_file_hash usage)] +pprUsage usage at UsageMergedRequirement{} + = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] +pprUsage usage at UsageHomeModuleInterface{} + = hsep [text "implementation", ppr (usg_mod_name usage) + , ppr (usg_unit_id usage) + , ppr (usg_iface_hash usage)] + +pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc +pprUsageImport mod hash safe + = hsep [ text "import", pp_safe, ppr mod + , ppr hash ] + where + pp_safe | safe = text "safe" + | otherwise = text " -/ " \ No newline at end of file ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -183,7 +183,7 @@ lookupFixityRn_help name -- loadInterfaceForName will find B.hi even if B is a hidden module, -- and that's what we want. = do { iface <- loadInterfaceForName doc name - ; let mb_fix = mi_fix_fn (mi_final_exts iface) occ + ; let mb_fix = mi_fix_fn iface occ ; let msg = case mb_fix of Nothing -> text "looking up name" <+> ppr name ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -489,8 +489,8 @@ calculateAvails :: HomeUnit calculateAvails home_unit other_home_units iface mod_safe' want_boot imported_by = let imp_mod = mi_module iface imp_sem_mod= mi_semantic_module iface - orph_iface = mi_orphan (mi_final_exts iface) - has_finsts = mi_finsts (mi_final_exts iface) + orph_iface = mi_orphan iface + has_finsts = mi_finsts iface deps = mi_deps iface trust = getSafeMode $ mi_trust iface trust_pkg = mi_trust_pkg iface @@ -1401,7 +1401,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) _ -> failLookupWith err mk_depr_export_warning gre - = DeprecatedExport name <$> mi_export_warn_fn (mi_final_exts iface) name + = DeprecatedExport name <$> mi_export_warn_fn iface name where name = greName gre ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -539,9 +539,9 @@ warnIfDeclDeprecated gre@(GRE { gre_imp = iss }) lookupImpDeclDeprec :: ModIface -> GlobalRdrElt -> Maybe (WarningTxt GhcRn) lookupImpDeclDeprec iface gre -- Bleat if the thing, or its parent, is warn'd - = mi_decl_warn_fn (mi_final_exts iface) (greOccName gre) `mplus` + = mi_decl_warn_fn iface (greOccName gre) `mplus` case greParent gre of - ParentIs p -> mi_decl_warn_fn (mi_final_exts iface) (nameOccName p) + ParentIs p -> mi_decl_warn_fn iface (nameOccName p) NoParent -> Nothing warnIfExportDeprecated :: GlobalRdrElt -> RnM () @@ -562,7 +562,7 @@ warnIfExportDeprecated gre@(GRE { gre_imp = iss }) process_import_spec is = do let mod = is_mod $ is_decl is iface <- loadInterfaceForModule doc mod - let mb_warn_txt = mi_export_warn_fn (mi_final_exts iface) name + let mb_warn_txt = mi_export_warn_fn iface name return $ (moduleName mod, ) <$> mb_warn_txt ------------------------- ===================================== compiler/GHC/Tc/Instance/Family.hs ===================================== @@ -308,7 +308,7 @@ checkFamInstConsistency directlyImpMods ifc <- modIface mod deps <- dep_finsts . mi_deps <$> modIface mod pure $ - if mi_finsts (mi_final_exts ifc) + if mi_finsts ifc then mod:deps else deps ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -97,7 +97,7 @@ checkHsigDeclM sig_iface sig_thing real_thing = do -- implementation cases. checkBootDeclM Hsig sig_thing real_thing real_fixity <- lookupFixityRn name - let sig_fixity = case mi_fix_fn (mi_final_exts sig_iface) (occName name) of + let sig_fixity = case mi_fix_fn sig_iface (occName name) of Nothing -> defaultFixity Just f -> f when (real_fixity /= sig_fixity) $ @@ -850,7 +850,7 @@ mergeSignatures if outer_mod == mi_module iface -- Don't add ourselves! then tcg_merged tcg_env - else (mi_module iface, mi_mod_hash (mi_final_exts iface)) : tcg_merged tcg_env + else (mi_module iface, mi_mod_hash iface) : tcg_merged tcg_env } -- Note [Signature merging DFuns] ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -1,18 +1,20 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ExplicitNamespaces #-} -- | Dependencies and Usage of a module module GHC.Unit.Module.Deps - ( Dependencies - , mkDependencies - , noDependencies - , dep_direct_mods - , dep_direct_pkgs - , dep_sig_mods - , dep_trusted_pkgs - , dep_orphs - , dep_plugin_pkgs - , dep_finsts - , dep_boot_mods + ( Dependencies(dep_direct_mods + , dep_direct_pkgs + , dep_sig_mods + , dep_trusted_pkgs + , dep_orphs + , dep_plugin_pkgs + , dep_finsts + , dep_boot_mods + , Dependencies) , dep_orphs_update , dep_finsts_update + , mkDependencies + , noDependencies , pprDeps , Usage (..) , ImportAvails (..) @@ -52,38 +54,38 @@ import Control.DeepSeq -- -- See Note [Transitive Information in Dependencies] data Dependencies = Deps - { dep_direct_mods :: Set (UnitId, ModuleNameWithIsBoot) + { dep_direct_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All home-package modules which are directly imported by this one. -- This may include modules from other units when using multiple home units - , dep_direct_pkgs :: Set UnitId + , dep_direct_pkgs_ :: Set UnitId -- ^ All packages directly imported by this module -- I.e. packages to which this module's direct imports belong. -- Does not include other home units when using multiple home units. -- Modules from these units will go in `dep_direct_mods` - , dep_plugin_pkgs :: Set UnitId + , dep_plugin_pkgs_ :: Set UnitId -- ^ All units needed for plugins ------------------------------------ -- Transitive information below here - , dep_sig_mods :: ![ModuleName] + , dep_sig_mods_ :: ![ModuleName] -- ^ Transitive closure of hsig files in the home package - , dep_trusted_pkgs :: Set UnitId + , dep_trusted_pkgs_ :: Set UnitId -- Packages which we are required to trust -- when the module is imported as a safe import -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names - , dep_boot_mods :: Set (UnitId, ModuleNameWithIsBoot) + , dep_boot_mods_ :: Set (UnitId, ModuleNameWithIsBoot) -- ^ All modules which have boot files below this one, and whether we -- should use the boot file or not. -- This information is only used to populate the eps_is_boot field. -- See Note [Structure of dep_boot_mods] - , dep_orphs :: [Module] + , dep_orphs_ :: [Module] -- ^ Transitive closure of orphan modules (whether -- home or external pkg). -- @@ -93,7 +95,7 @@ data Dependencies = Deps -- which relies on dep_orphs having the complete list!) -- This does NOT include us, unlike 'imp_orphs'. - , dep_finsts :: [Module] + , dep_finsts_ :: [Module] -- ^ Transitive closure of depended upon modules which -- contain family instances (whether home or external). -- This is used by 'checkFamInstConsistency'. This @@ -105,6 +107,26 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. +pattern Dependencies :: Set (UnitId, ModuleNameWithIsBoot) + -> Set UnitId + -> Set UnitId + -> [ModuleName] + -> Set UnitId + -> Set (UnitId, ModuleNameWithIsBoot) + -> [Module] + -> [Module] + -> Dependencies +pattern Dependencies {dep_direct_mods, dep_direct_pkgs, dep_plugin_pkgs, dep_sig_mods, dep_trusted_pkgs, dep_boot_mods, dep_orphs, dep_finsts} + <- Deps {dep_direct_mods_ = dep_direct_mods + , dep_direct_pkgs_ = dep_direct_pkgs + , dep_plugin_pkgs_ = dep_plugin_pkgs + , dep_sig_mods_ = dep_sig_mods + , dep_trusted_pkgs_ = dep_trusted_pkgs + , dep_boot_mods_ = dep_boot_mods + , dep_orphs_ = dep_orphs + , dep_finsts_ = dep_finsts} +{-# COMPLETE Dependencies #-} + instance NFData Dependencies where rnf (Deps dmods dpkgs ppkgs hsigms tps bmods orphs finsts) = rnf dmods @@ -158,14 +180,14 @@ mkDependencies home_unit mod imports plugin_mods = sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports - in Deps { dep_direct_mods = direct_mods - , dep_direct_pkgs = direct_pkgs - , dep_plugin_pkgs = plugin_units - , dep_sig_mods = sort sig_mods - , dep_trusted_pkgs = trust_pkgs - , dep_boot_mods = source_mods - , dep_orphs = sortBy stableModuleCmp dep_orphs - , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) + in Deps { dep_direct_mods_ = direct_mods + , dep_direct_pkgs_ = direct_pkgs + , dep_plugin_pkgs_ = plugin_units + , dep_sig_mods_ = sort sig_mods + , dep_trusted_pkgs_ = trust_pkgs + , dep_boot_mods_ = source_mods + , dep_orphs_ = sortBy stableModuleCmp dep_orphs + , dep_finsts_ = sortBy stableModuleCmp (imp_finsts imports) -- sort to get into canonical order -- NB. remember to use lexicographic ordering } @@ -174,14 +196,13 @@ mkDependencies home_unit mod imports plugin_mods = dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_orphs_update deps f = do r <- f (dep_orphs deps) - pure (deps { dep_orphs = sortBy stableModuleCmp r }) + pure (deps { dep_orphs_ = sortBy stableModuleCmp r }) -- | Update module dependencies containing family instances (used by Backpack) dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies dep_finsts_update deps f = do r <- f (dep_finsts deps) - pure (deps { dep_finsts = sortBy stableModuleCmp r }) - + pure (deps { dep_finsts_ = sortBy stableModuleCmp r }) instance Binary Dependencies where put_ bh deps = do put_ bh (dep_direct_mods deps) @@ -201,36 +222,36 @@ instance Binary Dependencies where sms <- get bh os <- get bh fis <- get bh - return (Deps { dep_direct_mods = dms - , dep_direct_pkgs = dps - , dep_plugin_pkgs = plugin_pkgs - , dep_sig_mods = hsigms - , dep_boot_mods = sms - , dep_trusted_pkgs = tps - , dep_orphs = os, - dep_finsts = fis }) + return (Deps { dep_direct_mods_ = dms + , dep_direct_pkgs_ = dps + , dep_plugin_pkgs_ = plugin_pkgs + , dep_sig_mods_ = hsigms + , dep_boot_mods_ = sms + , dep_trusted_pkgs_ = tps + , dep_orphs_ = os, + dep_finsts_ = fis }) noDependencies :: Dependencies noDependencies = Deps - { dep_direct_mods = Set.empty - , dep_direct_pkgs = Set.empty - , dep_plugin_pkgs = Set.empty - , dep_sig_mods = [] - , dep_boot_mods = Set.empty - , dep_trusted_pkgs = Set.empty - , dep_orphs = [] - , dep_finsts = [] + { dep_direct_mods_ = Set.empty + , dep_direct_pkgs_ = Set.empty + , dep_plugin_pkgs_ = Set.empty + , dep_sig_mods_ = [] + , dep_boot_mods_ = Set.empty + , dep_trusted_pkgs_ = Set.empty + , dep_orphs_ = [] + , dep_finsts_ = [] } -- | Pretty-print unit dependencies pprDeps :: UnitState -> Dependencies -> SDoc -pprDeps unit_state (Deps { dep_direct_mods = dmods - , dep_boot_mods = bmods - , dep_plugin_pkgs = plgns - , dep_orphs = orphs - , dep_direct_pkgs = pkgs - , dep_trusted_pkgs = tps - , dep_finsts = finsts +pprDeps unit_state (Deps { dep_direct_mods_ = dmods + , dep_boot_mods_ = bmods + , dep_plugin_pkgs_ = plgns + , dep_orphs_ = orphs + , dep_direct_pkgs_ = pkgs + , dep_trusted_pkgs_ = tps + , dep_finsts_ = finsts }) = pprWithUnitState unit_state $ vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -11,18 +11,20 @@ module GHC.Unit.Module.ModIface ( ModIface , ModIface_ - ( mi_module + ( mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls , mi_defaults - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_top_env , mi_insts , mi_fam_insts @@ -31,12 +33,17 @@ module GHC.Unit.Module.ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_decl_warn_fn + , mi_export_warn_fn + , mi_hash_fn ) , pattern ModIface + , set_mi_mod_info , set_mi_module , set_mi_sig_of , set_mi_hsc_src @@ -52,24 +59,34 @@ module GHC.Unit.Module.ModIface , set_mi_rules , set_mi_decls , set_mi_defaults - , set_mi_extra_decls - , set_mi_foreign + , set_mi_simplified_core , set_mi_top_env , set_mi_trust , set_mi_trust_pkg , set_mi_complete_matches , set_mi_docs - , set_mi_final_exts + , set_mi_abi_hashes , set_mi_ext_fields + , set_mi_caches + , set_mi_decl_warn_fn + , set_mi_export_warn_fn + , set_mi_fix_fn + , set_mi_hash_fn , completePartialModIface , IfaceBinHandle(..) , PartialModIface - , ModIfaceBackend (..) - , ModIfaceSelfRecomp (..) + , IfaceAbiHashes (..) + , IfaceSelfRecomp (..) + , IfaceCache (..) + , IfaceSimplifiedCore (..) , withSelfRecomp , IfaceDeclExts - , IfaceBackendExts + , IfaceAbiHashesExts , IfaceExport + , IfacePublic_(..) + , IfacePublic + , PartialIfacePublic + , IfaceModInfo(..) , WhetherHasOrphans , WhetherHasFamInst , IfaceTopEnv (..) @@ -77,6 +94,7 @@ module GHC.Unit.Module.ModIface , mi_boot , mi_fix , mi_semantic_module + , mi_mod_info_semantic_module , mi_free_holes , mi_mnwib , mi_flag_hash @@ -85,6 +103,11 @@ module GHC.Unit.Module.ModIface , mi_plugin_hash , mi_src_hash , mi_usages + , mi_mod_hash + , mi_orphan + , mi_finsts + , mi_exp_hash + , mi_orphan_hash , renameFreeHoles , emptyPartialModIface , emptyFullModIface @@ -106,7 +129,7 @@ import GHC.Iface.Recomp.Types import GHC.Unit import GHC.Unit.Module.Deps import GHC.Unit.Module.Warnings -import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..), emptyIfaceForeign) +import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..)) import GHC.Types.Avail @@ -147,36 +170,36 @@ We can build a full interface file two ways: type PartialModIface = ModIface_ 'ModIfaceCore type ModIface = ModIface_ 'ModIfaceFinal --- | Extends a PartialModIface with information which is either: --- * Computed after codegen --- * Or computed just before writing the iface to disk. (Hashes) --- In order to fully instantiate it. -data ModIfaceBackend = ModIfaceBackend - { mi_mod_hash :: !Fingerprint +type PartialIfacePublic = IfacePublic_ 'ModIfaceCore +type IfacePublic = IfacePublic_ 'ModIfaceFinal + +-- | Extends a PartialModIface with hashes of the ABI. +-- +-- * The mi_mod_hash is the hash of the entire ABI +-- * THe other fields are more specific hashes of parts of the ABI +data IfaceAbiHashes = IfaceAbiHashes + { mi_abi_mod_hash :: !Fingerprint -- ^ Hash of the ABI only - , mi_iface_hash :: !Fingerprint - -- ^ Hash of the whole interface - , mi_orphan :: !WhetherHasOrphans + , mi_abi_orphan :: !WhetherHasOrphans -- ^ Whether this module has orphans - , mi_finsts :: !WhetherHasFamInst + , mi_abi_finsts :: !WhetherHasFamInst -- ^ Whether this module has family instances. See Note [The type family -- instance consistency story]. - , mi_exp_hash :: !Fingerprint + , mi_abi_exp_hash :: !Fingerprint -- ^ Hash of export list - , mi_orphan_hash :: !Fingerprint + , mi_abi_orphan_hash :: !Fingerprint -- ^ Hash for orphan rules, class and family instances combined + -- NOT transitive + } - -- Cached environments for easy lookup. These are computed (lazily) from - -- other fields and are not put into the interface file. - -- Not really produced by the backend but there is no need to create them - -- any earlier. - , mi_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) +data IfaceCache = IfaceCache + { mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for declaration deprecations - , mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) + , mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn)) -- ^ Cached lookup for 'mi_warns' for export deprecations - , mi_fix_fn :: !(OccName -> Maybe Fixity) + , mi_cache_fix_fn :: !(OccName -> Maybe Fixity) -- ^ Cached lookup for 'mi_fixities' - , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) + , mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint)) -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that -- the thing isn't in decls. It's useful to know that when seeing if we are -- up to date wrt. the old interface. The 'OccName' is the parent of the @@ -195,9 +218,9 @@ type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where IfaceDeclExts 'ModIfaceCore = IfaceDecl IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) -type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where - IfaceBackendExts 'ModIfaceCore = () - IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend +type family IfaceAbiHashesExts (phase :: ModIfacePhase) = bk | bk -> phase where + IfaceAbiHashesExts 'ModIfaceCore = () + IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes -- | In-memory byte array representation of a 'ModIface'. -- @@ -212,7 +235,7 @@ data IfaceBinHandle (phase :: ModIfacePhase) where FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -withSelfRecomp :: ModIface_ phase -> r -> (ModIfaceSelfRecomp -> r) -> r +withSelfRecomp :: ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r withSelfRecomp iface nk jk = case mi_self_recomp_info iface of Nothing -> nk @@ -220,34 +243,80 @@ withSelfRecomp iface nk jk = --- | A 'ModIface' plus a 'ModDetails' summarises everything we know --- about a compiled module. The 'ModIface' is the stuff *before* linking, --- and can be written out to an interface file. The 'ModDetails is after --- linking and can be completely recovered from just the 'ModIface'. +-- | A 'ModIface' summarises everything we know +-- about a compiled module. -- --- When we read an interface file, we also construct a 'ModIface' from it, --- except that we explicitly make the 'mi_decls' and a few other fields empty; --- as when reading we consolidate the declarations etc. into a number of indexed --- maps and environments in the 'ExternalPackageState'. +-- See Note [Structure of ModIface] for information about what belongs in each field. -- --- See Note [Strictness in ModIface] to learn about why some fields are --- strict and others are not. +-- See Note [Strictness in ModIface] to learn about why all the fields are lazy. -- -- See Note [Private fields in ModIface] to learn why we don't export any of the -- fields. data ModIface_ (phase :: ModIfacePhase) = PrivateModIface { - mi_module_ :: !Module, -- ^ Name of the module we are for - mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? + mi_hi_bytes_ :: !(IfaceBinHandle phase), + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. + mi_iface_hash_ :: Fingerprint, -- A hash of the whole interface - mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? + mi_mod_info_ :: IfaceModInfo, + -- ^ Meta information about the module the interface file is for mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) + -- MP: Needs to be refactored (#25844) + + mi_public_ :: IfacePublic_ phase, + -- ^ The parts of interface which are used by other modules when + -- importing this module. The main, original part of an interface. - mi_exports_ :: ![IfaceExport], + + mi_self_recomp_ :: Maybe IfaceSelfRecomp, + -- ^ Information needed for checking self-recompilation. + -- See Note [Self recompilation information in interface files] + + mi_simplified_core_ :: Maybe IfaceSimplifiedCore, + -- ^ The part of the interface written when `-fwrite-if-simplified-core` is enabled. + -- These parts are used to restart bytecode generation. + + mi_docs_ :: Maybe Docs, + -- ^ Docstrings and related data for use by haddock, the ghci + -- @:doc@ command, and other tools. + -- + -- @Just _@ @<=>@ the module was built with @-haddock at . + + mi_top_env_ :: IfaceTopEnv, + -- ^ Just enough information to reconstruct the top level environment in + -- the /original source/ code for this module. which + -- is NOT the same as mi_exports, nor mi_decls (which + -- may contains declarations for things not actually + -- defined by the user). Used for GHCi and for inspecting + -- the contents of modules via the GHC API only. + + mi_ext_fields_ :: ExtensibleFields + -- ^ Additional optional fields, where the Map key represents + -- the field name, resulting in a (size, serialized data) pair. + -- Because the data is intended to be serialized through the + -- internal `Binary` class (increasing compatibility with types + -- using `Name` and `FastString`, such as HIE), this format is + -- chosen over `ByteString`s. + } + +-- | Meta information about the module the interface file is for +data IfaceModInfo = IfaceModInfo { + mi_mod_info_module :: Module, -- ^ Name of the module we are for + mi_mod_info_sig_of :: Maybe Module, -- ^ Are we a sig of another mod? + mi_mod_info_hsc_src :: HscSource -- ^ Boot? Signature? +} + +-- | The public interface of a module which are used by other modules when importing this module. +-- The ABI of a module. +data IfacePublic_ phase = IfacePublic { + mi_exports_ :: [IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things @@ -273,25 +342,10 @@ data ModIface_ (phase :: ModIfacePhase) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], - -- ^ Extra variable definitions which are **NOT** exposed but when - -- combined with mi_decls allows us to restart code generation. - -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - - mi_foreign_ :: !IfaceForeign, - -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. - -- See Note [Foreign stubs and TH bytecode linking] mi_defaults_ :: [IfaceDefault], -- ^ default declarations exported by the module - mi_top_env_ :: IfaceTopEnv, - -- ^ Just enough information to reconstruct the top level environment in - -- the /original source/ code for this module. which - -- is NOT the same as mi_exports, nor mi_decls (which - -- may contains declarations for things not actually - -- defined by the user). Used for GHCi and for inspecting - -- the contents of modules via the GHC API only. -- Instance declarations and rules mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance @@ -299,53 +353,81 @@ data ModIface_ (phase :: ModIfacePhase) mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_trust_ :: !IfaceTrustInfo, + mi_trust_ :: IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg_ :: !Bool, + mi_trust_pkg_ :: Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches_ :: ![IfaceCompleteMatch], + mi_complete_matches_ :: [IfaceCompleteMatch], + -- ^ {-# COMPLETE #-} declarations - mi_docs_ :: !(Maybe Docs), - -- ^ Docstrings and related data for use by haddock, the ghci - -- @:doc@ command, and other tools. - -- - -- @Just _@ @<=>@ the module was built with @-haddock at . + mi_caches_ :: IfaceCache, + -- ^ Cached lookups of some parts of mi_public - mi_final_exts_ :: !(IfaceBackendExts phase), - -- ^ Either `()` or `ModIfaceBackend` for + mi_abi_hashes_ :: (IfaceAbiHashesExts phase) + -- ^ Either `()` or `IfaceAbiHashes` for -- a fully instantiated interface. - - mi_ext_fields_ :: !ExtensibleFields, - -- ^ Additional optional fields, where the Map key represents - -- the field name, resulting in a (size, serialized data) pair. - -- Because the data is intended to be serialized through the - -- internal `Binary` class (increasing compatibility with types - -- using `Name` and `FastString`, such as HIE), this format is - -- chosen over `ByteString`s. - -- - - mi_hi_bytes_ :: !(IfaceBinHandle phase), - -- ^ A serialised in-memory buffer of this 'ModIface'. - -- If this handle is given, we can avoid serialising the 'ModIface' - -- when writing this 'ModIface' to disk, and write this buffer to disk instead. - -- See Note [Sharing of ModIface]. - - mi_self_recomp_info_ :: !(Maybe ModIfaceSelfRecomp) - -- ^ Information needed for checking self-recompilation. - -- See Note [Self recompilation information in interface files] - } + -- These fields are hashes of different parts of the public interface. +} + +mkIfacePublic :: [IfaceExport] + -> [IfaceDeclExts 'ModIfaceFinal] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDefault] + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> IfaceAbiHashes + -> IfacePublic +mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes = IfacePublic { + mi_exports_ = exports, + mi_decls_ = decls, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_defaults_ = defaults, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, + mi_cache_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, + mi_cache_fix_fn = mkIfaceFixCache fixities, + mi_cache_hash_fn = mkIfaceHashCache decls + }, + mi_abi_hashes_ = abi_hashes +} + +-- | The information needed to restart bytecode generation. +-- Enabled by `-fwrite-if-simplified-core`. +data IfaceSimplifiedCore = IfaceSimplifiedCore { + mi_sc_extra_decls :: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -- ^ Extra variable definitions which are **NOT** exposed but when + -- combined with mi_decls allows us to restart code generation. + -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] + , mi_sc_foreign :: IfaceForeign + -- ^ Foreign stubs and files to supplement 'mi_extra_decls_'. + -- See Note [Foreign stubs and TH bytecode linking] +} -- Enough information to reconstruct the top level environment for a module data IfaceTopEnv = IfaceTopEnv - { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff - , ifaceImports :: ![IfaceImport] -- ^ all the imports in this module + { ifaceTopExports :: DetOrdAvails -- ^ all top level things in this module, including unexported stuff + , ifaceImports :: [IfaceImport] -- ^ all the imports in this module } instance NFData IfaceTopEnv where @@ -362,6 +444,35 @@ instance Binary IfaceTopEnv where {- +Note [Structure of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The ModIface structure is divided into several logical parts: + +1. mi_mod_info: Basic module metadata (name, version, etc.) + +2. mi_public: The public interface of the module, which includes: + - Exports, declarations, fixities, warnings, annotations + - Class and type family instances + - Rewrite rules and COMPLETE pragmas + - Safe Haskell and package trust information + - ABI hashes for recompilation checking + +4. mi_self_recomp: Information needed for self-recompilation checking + (see Note [Self recompilation information in interface files]) + +5. mi_simplified_core: Optional simplified Core for bytecode generation + (only present when -fwrite-if-simplified-core is enabled) + +6. mi_docs: Optional documentation (only present when -haddock is enabled) + +7. mi_top_env: Information about the top-level environment of the original source + +8. mi_ext_fields: Additional fields for extensibility + +This structure helps organize the interface data according to its purpose and usage +patterns. Different parts of the compiler use different fields. By separating them +logically in the interface we can arrange to only deserialize the fields that are needed. + Note [Strictness in ModIface] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -371,7 +482,7 @@ The ModIface is the Haskell representation of an interface (.hi) file. that we have just compiled * For packages that we depend on we load the ModIface from disk. -Some fields in the ModIface are deliberately lazy because when we read +All fields in the ModIface are deliberately lazy because when we read an interface file we don't always need all the parts. For example, an interface file contains information about documentation which is often not needed during compilation. This is achieved using the lazyPut/lazyGet pair. @@ -384,23 +495,43 @@ That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to forceModIface. -} -mi_flag_hash :: ModIface_ phase -> Maybe (Fingerprint, Maybe IfaceDynFlags) -mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_info_ +mi_flag_hash :: ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags) +mi_flag_hash = fmap mi_sr_flag_hash . mi_self_recomp_ mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint -mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_info_ +mi_opt_hash = fmap mi_sr_opt_hash . mi_self_recomp_ mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint -mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_info_ +mi_hpc_hash = fmap mi_sr_hpc_hash . mi_self_recomp_ mi_src_hash :: ModIface_ phase -> Maybe Fingerprint -mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_info_ +mi_src_hash = fmap mi_sr_src_hash . mi_self_recomp_ mi_usages :: ModIface_ phase -> Maybe [Usage] -mi_usages = fmap mi_sr_usages . mi_self_recomp_info_ +mi_usages = fmap mi_sr_usages . mi_self_recomp_ mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint -mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_info_ +mi_plugin_hash = fmap mi_sr_plugin_hash . mi_self_recomp_ + +-- | Accessor for the module hash of the ABI from a ModIface. +mi_mod_hash :: ModIface -> Fingerprint +mi_mod_hash iface = mi_abi_mod_hash (mi_abi_hashes iface) + +-- | Accessor for whether this module has orphans from a ModIface. +mi_orphan :: ModIface -> WhetherHasOrphans +mi_orphan iface = mi_abi_orphan (mi_abi_hashes iface) + +-- | Accessor for whether this module has family instances from a ModIface. +mi_finsts :: ModIface -> WhetherHasFamInst +mi_finsts iface = mi_abi_finsts (mi_abi_hashes iface) + +-- | Accessor for the hash of the export list from a ModIface. +mi_exp_hash :: ModIface -> Fingerprint +mi_exp_hash iface = mi_abi_exp_hash (mi_abi_hashes iface) + +-- | Accessor for the hash of orphan rules, class and family instances combined from a ModIface. +mi_orphan_hash :: ModIface -> Fingerprint +mi_orphan_hash iface = mi_abi_orphan_hash (mi_abi_hashes iface) -- | Old-style accessor for whether or not the ModIface came from an hs-boot -- file. @@ -415,16 +546,19 @@ mi_mnwib iface = GWIB (moduleName $ mi_module iface) (mi_boot iface) -- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be -- found, 'defaultFixity' is returned instead. mi_fix :: ModIface -> OccName -> Fixity -mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity +mi_fix iface name = mi_fix_fn iface name `orElse` defaultFixity -- | The semantic module for this interface; e.g., if it's a interface -- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module' -- will be @<A>@. -mi_semantic_module :: ModIface_ a -> Module -mi_semantic_module iface = case mi_sig_of iface of - Nothing -> mi_module iface +mi_mod_info_semantic_module :: IfaceModInfo -> Module +mi_mod_info_semantic_module iface = case mi_mod_info_sig_of iface of + Nothing -> mi_mod_info_module iface Just mod -> mod +mi_semantic_module :: ModIface_ a -> Module +mi_semantic_module iface = mi_mod_info_semantic_module (mi_mod_info iface) + -- | The "precise" free holes, e.g., the signatures that this -- 'ModIface' depends on. mi_free_holes :: ModIface -> UniqDSet ModuleName @@ -455,191 +589,229 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + put_ bh (PrivateModIface + { mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself -- may contain an in-memory byte array buffer for this -- 'ModIface'. If we used 'put_' on this 'ModIface', then -- we likely have a good reason, and do not want to reuse -- the byte array. -- See Note [Private fields in ModIface] + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_anns_ = anns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - mi_complete_matches_ = complete_matches, + mi_public_ = public, mi_top_env_ = top_env, mi_docs_ = docs, mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_self_recomp_info_ = self_recomp, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash - }}) = do - put_ bh mod - put_ bh sig_of - put_ bh hsc_src - put_ bh self_recomp - put_ bh mod_hash + mi_self_recomp_ = self_recomp, + mi_simplified_core_ = simplified_core + }) = do + put_ bh mod_info put_ bh iface_hash - put_ bh orphan - put_ bh hasFamInsts lazyPut bh deps - put_ bh exports - put_ bh exp_hash - put_ bh fixities - lazyPut bh warns - lazyPut bh anns - put_ bh decls - put_ bh extra_decls - put_ bh defaults - put_ bh foreign_ - put_ bh insts - put_ bh fam_insts - lazyPut bh rules - put_ bh orphan_hash - put_ bh trust - put_ bh trust_pkg - put_ bh complete_matches + lazyPut bh public lazyPut bh top_env lazyPutMaybe bh docs + lazyPutMaybe bh self_recomp + lazyPutMaybe bh simplified_core get bh = do - mod <- get bh - sig_of <- get bh - hsc_src <- get bh - self_recomp_info <- get bh - mod_hash <- get bh + mod_info <- get bh iface_hash <- get bh - orphan <- get bh - hasFamInsts <- get bh deps <- lazyGet bh - exports <- {-# SCC "bin_exports" #-} get bh - exp_hash <- get bh - fixities <- {-# SCC "bin_fixities" #-} get bh - warns <- {-# SCC "bin_warns" #-} lazyGet bh - anns <- {-# SCC "bin_anns" #-} lazyGet bh - decls <- {-# SCC "bin_tycldecls" #-} get bh - extra_decls <- get bh - defaults <- get bh - foreign_ <- get bh - insts <- {-# SCC "bin_insts" #-} get bh - fam_insts <- {-# SCC "bin_fam_insts" #-} get bh - rules <- {-# SCC "bin_rules" #-} lazyGet bh - orphan_hash <- get bh - trust <- get bh - trust_pkg <- get bh - complete_matches <- get bh + public <- lazyGet bh top_env <- lazyGet bh docs <- lazyGetMaybe bh + self_recomp <- lazyGetMaybe bh + simplified_core <- lazyGetMaybe bh + return (PrivateModIface { - mi_module_ = mod, - mi_sig_of_ = sig_of, - mi_hsc_src_ = hsc_src, - mi_hi_bytes_ = - -- We can't populate this field here, as we are - -- missing the 'mi_ext_fields_' field, which is - -- handled in 'getIfaceWithExtFields'. - FullIfaceBinHandle Strict.Nothing, + mi_mod_info_ = mod_info, + mi_iface_hash_ = iface_hash, mi_deps_ = deps, - mi_exports_ = exports, - mi_anns_ = anns, - mi_fixities_ = fixities, - mi_warns_ = warns, - mi_decls_ = decls, - mi_extra_decls_ = extra_decls, - mi_foreign_ = foreign_, - mi_defaults_ = defaults, - mi_insts_ = insts, - mi_fam_insts_ = fam_insts, - mi_rules_ = rules, - mi_trust_ = trust, - mi_trust_pkg_ = trust_pkg, - -- And build the cached values - mi_complete_matches_ = complete_matches, + mi_public_ = public, + mi_simplified_core_ = simplified_core, mi_docs_ = docs, mi_top_env_ = top_env, - mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt - -- with specially when the file is read - mi_self_recomp_info_ = self_recomp_info, - mi_final_exts_ = ModIfaceBackend { - mi_mod_hash = mod_hash, - mi_iface_hash = iface_hash, - mi_orphan = orphan, - mi_finsts = hasFamInsts, - mi_exp_hash = exp_hash, - mi_orphan_hash = orphan_hash, - mi_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns, - mi_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns, - mi_fix_fn = mkIfaceFixCache fixities, - mi_hash_fn = mkIfaceHashCache decls - }}) + mi_self_recomp_ = self_recomp, + -- placeholder because this is dealt + -- with specially when the file is read + mi_ext_fields_ = emptyExtensibleFields, + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + }) + +instance Binary IfaceModInfo where + put_ bh (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) = do + put_ bh mod + put_ bh sig_of + put_ bh hsc_src + get bh = do + mod <- get bh + sig_of <- get bh + hsc_src <- get bh + return (IfaceModInfo { mi_mod_info_module = mod + , mi_mod_info_sig_of = sig_of + , mi_mod_info_hsc_src = hsc_src + }) + + +instance Binary (IfacePublic_ 'ModIfaceFinal) where + put_ bh (IfacePublic { mi_exports_ = exports + , mi_decls_ = decls + , mi_fixities_ = fixities + , mi_warns_ = warns + , mi_anns_ = anns + , mi_defaults_ = defaults + , mi_insts_ = insts + , mi_fam_insts_ = fam_insts + , mi_rules_ = rules + , mi_trust_ = trust + , mi_trust_pkg_ = trust_pkg + , mi_complete_matches_ = complete_matches + , mi_abi_hashes_ = abi_hashes + }) = do + + lazyPut bh exports + lazyPut bh decls + lazyPut bh fixities + lazyPut bh warns + lazyPut bh anns + lazyPut bh defaults + lazyPut bh insts + lazyPut bh fam_insts + lazyPut bh rules + lazyPut bh trust + lazyPut bh trust_pkg + lazyPut bh complete_matches + lazyPut bh abi_hashes + + get bh = do + exports <- lazyGet bh + decls <- lazyGet bh + fixities <- lazyGet bh + warns <- lazyGet bh + anns <- lazyGet bh + defaults <- lazyGet bh + insts <- lazyGet bh + fam_insts <- lazyGet bh + rules <- lazyGet bh + trust <- lazyGet bh + trust_pkg <- lazyGet bh + complete_matches <- lazyGet bh + abi_hashes <- lazyGet bh + return (mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes) + +instance Binary IfaceAbiHashes where + put_ bh (IfaceAbiHashes { mi_abi_mod_hash = mod_hash + , mi_abi_orphan = orphan + , mi_abi_finsts = hasFamInsts + , mi_abi_exp_hash = exp_hash + , mi_abi_orphan_hash = orphan_hash + }) = do + put_ bh mod_hash + put_ bh orphan + put_ bh hasFamInsts + put_ bh exp_hash + put_ bh orphan_hash + get bh = do + mod_hash <- get bh + orphan <- get bh + hasFamInsts <- get bh + exp_hash <- get bh + orphan_hash <- get bh + return $ IfaceAbiHashes { + mi_abi_mod_hash = mod_hash, + mi_abi_orphan = orphan, + mi_abi_finsts = hasFamInsts, + mi_abi_exp_hash = exp_hash, + mi_abi_orphan_hash = orphan_hash + } + +instance Binary IfaceSimplifiedCore where + put_ bh (IfaceSimplifiedCore eds fs) = do + put_ bh eds + put_ bh fs + + get bh = do + eds <- get bh + fs <- get bh + return (IfaceSimplifiedCore eds fs) emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod = PrivateModIface - { mi_module_ = mod, - mi_sig_of_ = Nothing, - mi_hsc_src_ = HsSrcFile, + { mi_mod_info_ = emptyIfaceModInfo mod, + mi_iface_hash_ = fingerprint0, mi_hi_bytes_ = PartialIfaceBinHandle, mi_deps_ = noDependencies, - mi_exports_ = [], - mi_fixities_ = [], - mi_warns_ = IfWarnSome [] [], - mi_anns_ = [], - mi_defaults_ = [], - mi_insts_ = [], - mi_fam_insts_ = [], - mi_rules_ = [], - mi_decls_ = [], - mi_extra_decls_ = Nothing, - mi_foreign_ = emptyIfaceForeign, + mi_public_ = emptyPublicModIface (), + mi_simplified_core_ = Nothing, mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] , - mi_trust_ = noIfaceTrustInfo, - mi_trust_pkg_ = False, - mi_complete_matches_ = [], mi_docs_ = Nothing, - mi_final_exts_ = (), - mi_ext_fields_ = emptyExtensibleFields, - mi_self_recomp_info_ = Nothing + mi_self_recomp_ = Nothing, + mi_ext_fields_ = emptyExtensibleFields + } +emptyIfaceModInfo :: Module -> IfaceModInfo +emptyIfaceModInfo mod = IfaceModInfo + { mi_mod_info_module = mod + , mi_mod_info_sig_of = Nothing + , mi_mod_info_hsc_src = HsSrcFile + } + + +emptyPublicModIface :: IfaceAbiHashesExts phase -> IfacePublic_ phase +emptyPublicModIface abi_hashes = IfacePublic + { mi_exports_ = [] + , mi_decls_ = [] + , mi_fixities_ = [] + , mi_warns_ = IfWarnSome [] [] + , mi_anns_ = [] + , mi_defaults_ = [] + , mi_insts_ = [] + , mi_fam_insts_ = [] + , mi_rules_ = [] + , mi_abi_hashes_ = abi_hashes + , mi_trust_ = noIfaceTrustInfo + , mi_trust_pkg_ = False + , mi_caches_ = emptyModIfaceCache + , mi_complete_matches_ = [] + } + +emptyModIfaceCache :: IfaceCache +emptyModIfaceCache = IfaceCache { + mi_cache_decl_warn_fn = emptyIfaceWarnCache, + mi_cache_export_warn_fn = emptyIfaceWarnCache, + mi_cache_fix_fn = emptyIfaceFixCache, + mi_cache_hash_fn = emptyIfaceHashCache +} + +emptyIfaceBackend :: IfaceAbiHashes +emptyIfaceBackend = IfaceAbiHashes + { mi_abi_mod_hash = fingerprint0, + mi_abi_orphan = False, + mi_abi_finsts = False, + mi_abi_exp_hash = fingerprint0, + mi_abi_orphan_hash = fingerprint0 + } + emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls_ = [] - , mi_self_recomp_info_ = Nothing + { mi_public_ = emptyPublicModIface emptyIfaceBackend , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing - , mi_final_exts_ = ModIfaceBackend - { mi_mod_hash = fingerprint0, - mi_iface_hash = fingerprint0, - mi_orphan = False, - mi_finsts = False, - mi_exp_hash = fingerprint0, - mi_orphan_hash = fingerprint0, - mi_decl_warn_fn = emptyIfaceWarnCache, - mi_export_warn_fn = emptyIfaceWarnCache, - mi_fix_fn = emptyIfaceFixCache, - mi_hash_fn = emptyIfaceHashCache } } + } + -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface' mkIfaceHashCache :: [(Fingerprint,IfaceDecl)] @@ -657,11 +829,11 @@ emptyIfaceHashCache _occ = Nothing -- ModIface is completely forced since it will live in memory for a long time. -- If forcing it uses a lot of memory, then store less things in ModIface. -instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) +instance ( NFData (IfaceAbiHashesExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24) - = rnf a1 + rnf (PrivateModIface a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + = (a1 :: IfaceBinHandle phase) `seq` rnf a2 `seq` rnf a3 `seq` rnf a4 @@ -671,24 +843,27 @@ instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 - `seq` rnf a11 - `seq` rnf a12 - `seq` rnf a13 - `seq` rnf a14 - `seq` rnf a15 - `seq` rnf a16 - `seq` rnf a17 - `seq` rnf a18 - `seq` rnf a19 - `seq` rnf a20 - `seq` rnf a21 - `seq` rnf a22 - -- IfaceBinHandle - `seq` (a23 :: IfaceBinHandle phase) - `seq` rnf a24 - -instance NFData ModIfaceBackend where - rnf (ModIfaceBackend a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) + +instance NFData IfaceModInfo where + rnf (IfaceModInfo a1 a2 a3) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + + +instance NFData IfaceSimplifiedCore where + rnf (IfaceSimplifiedCore eds fs) = rnf eds `seq` rnf fs + +instance NFData IfaceAbiHashes where + rnf (IfaceAbiHashes a1 a2 a3 a4 a5) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + `seq` rnf a5 + +instance (NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) where + rnf (IfacePublic a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) = rnf a1 `seq` rnf a2 `seq` rnf a3 @@ -699,6 +874,18 @@ instance NFData ModIfaceBackend where `seq` rnf a8 `seq` rnf a9 `seq` rnf a10 + `seq` rnf a11 + `seq` rnf a12 + `seq` rnf a13 + `seq` rnf a14 + +instance NFData IfaceCache where + rnf (IfaceCache a1 a2 a3 a4) + = rnf a1 + `seq` rnf a2 + `seq` rnf a3 + `seq` rnf a4 + forceModIface :: ModIface -> IO () @@ -745,28 +932,38 @@ to serialise the 'ModIface' to disk again. -- | Given a 'PartialModIface', turn it into a 'ModIface' by completing -- missing fields. completePartialModIface :: PartialModIface + -> Fingerprint -> [(Fingerprint, IfaceDecl)] - -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] - -> ModIfaceBackend + -> Maybe IfaceSimplifiedCore + -> IfaceAbiHashes + -> IfaceCache -> ModIface -completePartialModIface partial decls extra_decls final_exts = partial - { mi_decls_ = decls - , mi_extra_decls_ = extra_decls - , mi_final_exts_ = final_exts +completePartialModIface partial iface_hash decls extra_decls final_exts cache = partial + { mi_public_ = completePublicModIface decls final_exts cache (mi_public_ partial) + , mi_simplified_core_ = extra_decls , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_iface_hash_ = iface_hash } + where -set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase -set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } - -set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase -set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } +-- | Given a 'PartialIfacePublic', turn it into an 'IfacePublic' by completing +-- missing fields. +completePublicModIface :: [(Fingerprint, IfaceDecl)] + -> IfaceAbiHashes + -> IfaceCache + -> PartialIfacePublic + -> IfacePublic +completePublicModIface decls abi_hashes cache partial = partial + { mi_decls_ = decls + , mi_abi_hashes_ = abi_hashes + , mi_caches_ = cache + } -set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase -set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } +set_mi_mod_info :: IfaceModInfo -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info val iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = val } -set_mi_self_recomp :: Maybe ModIfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase -set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_info_ = val } +set_mi_self_recomp :: Maybe IfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase +set_mi_self_recomp val iface = clear_mi_hi_bytes $ iface { mi_self_recomp_ = val } set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } @@ -774,59 +971,100 @@ set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } +set_mi_public :: (IfacePublic_ phase -> IfacePublic_ phase) -> ModIface_ phase -> ModIface_ phase +set_mi_public f iface = clear_mi_hi_bytes $ iface { mi_public_ = f (mi_public_ iface) } + +set_mi_simplified_core :: Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase +set_mi_simplified_core val iface = clear_mi_hi_bytes $ iface { mi_simplified_core_ = val } + +set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +{- Settings for mi_public interface fields -} + set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase -set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } +set_mi_exports val = set_mi_public (\iface -> iface { mi_exports_ = val }) set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase -set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } +set_mi_fixities val = set_mi_public (\iface -> iface { mi_fixities_ = val }) set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase -set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } +set_mi_warns val = set_mi_public (\iface -> iface { mi_warns_ = val }) set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase -set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } +set_mi_anns val = set_mi_public (\iface -> iface { mi_anns_ = val }) set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase -set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } +set_mi_insts val = set_mi_public (\iface -> iface { mi_insts_ = val }) set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase -set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } +set_mi_fam_insts val = set_mi_public (\iface -> iface { mi_fam_insts_ = val }) set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase -set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } +set_mi_rules val = set_mi_public (\iface -> iface { mi_rules_ = val }) set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase -set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } +set_mi_decls val = set_mi_public (\iface -> iface { mi_decls_ = val }) set_mi_defaults :: [IfaceDefault] -> ModIface_ phase -> ModIface_ phase -set_mi_defaults val iface = clear_mi_hi_bytes $ iface { mi_defaults_ = val } - -set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase -set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } - -set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase -set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ } - -set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase -set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } +set_mi_defaults val = set_mi_public (\iface -> iface { mi_defaults_ = val }) set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase -set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } +set_mi_trust val = set_mi_public (\iface -> iface { mi_trust_ = val }) set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase -set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } +set_mi_trust_pkg val = set_mi_public (\iface -> iface { mi_trust_pkg_ = val }) set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase -set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } +set_mi_complete_matches val = set_mi_public (\iface -> iface { mi_complete_matches_ = val }) + +set_mi_abi_hashes :: IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_abi_hashes val = set_mi_public (\iface -> iface { mi_abi_hashes_ = val }) + +{- Setters for mi_caches interface fields -} + +set_mi_decl_warn_fn :: (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_decl_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_decl_warn_fn = val } }) + +set_mi_export_warn_fn :: (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase +set_mi_export_warn_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_export_warn_fn = val } }) + +set_mi_fix_fn :: (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase +set_mi_fix_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_fix_fn = val } }) + +set_mi_hash_fn :: (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase +set_mi_hash_fn val = set_mi_public (\iface -> iface { mi_caches_ = (mi_caches_ iface) { mi_cache_hash_fn = val } }) + +set_mi_caches :: IfaceCache -> ModIface_ phase -> ModIface_ phase +set_mi_caches val = set_mi_public (\iface -> iface { mi_caches_ = val }) + +{- + +-} + +{- Setters for mi_mod_info interface fields -} + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val = set_mi_mod_info_field (\info -> info { mi_mod_info_module = val }) + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val = set_mi_mod_info_field (\info -> info { mi_mod_info_sig_of = val }) + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val = set_mi_mod_info_field (\info -> info { mi_mod_info_hsc_src = val }) + +-- | Helper function for setting fields in mi_mod_info_ +set_mi_mod_info_field :: (IfaceModInfo -> IfaceModInfo) -> ModIface_ phase -> ModIface_ phase +set_mi_mod_info_field f iface = clear_mi_hi_bytes $ iface { mi_mod_info_ = f (mi_mod_info_ iface) } -set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase -set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } -set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase -set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } -set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase -set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } -- | Invalidate any byte array buffer we might have. clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase @@ -887,18 +1125,20 @@ However, with the pragma, the correct core is generated: -- See Note [Inline Pattern synonym of ModIface] for why we have all these -- inline pragmas. -{-# INLINE ModIface #-} +{-# INLINE mi_mod_info #-} +{-# INLINE mi_iface_hash #-} {-# INLINE mi_module #-} {-# INLINE mi_sig_of #-} {-# INLINE mi_hsc_src #-} {-# INLINE mi_deps #-} +{-# INLINE mi_public #-} {-# INLINE mi_exports #-} {-# INLINE mi_fixities #-} {-# INLINE mi_warns #-} {-# INLINE mi_anns #-} {-# INLINE mi_decls #-} -{-# INLINE mi_extra_decls #-} -{-# INLINE mi_foreign #-} +{-# INLINE mi_simplified_core #-} +{-# INLINE mi_defaults #-} {-# INLINE mi_top_env #-} {-# INLINE mi_insts #-} {-# INLINE mi_fam_insts #-} @@ -907,32 +1147,63 @@ However, with the pragma, the correct core is generated: {-# INLINE mi_trust_pkg #-} {-# INLINE mi_complete_matches #-} {-# INLINE mi_docs #-} -{-# INLINE mi_final_exts #-} +{-# INLINE mi_abi_hashes #-} {-# INLINE mi_ext_fields #-} {-# INLINE mi_hi_bytes #-} +{-# INLINE mi_self_recomp_info #-} +{-# INLINE mi_fix_fn #-} +{-# INLINE mi_hash_fn #-} +{-# INLINE mi_decl_warn_fn #-} +{-# INLINE mi_export_warn_fn #-} +{-# INLINE ModIface #-} {-# COMPLETE ModIface #-} pattern ModIface :: - Module -> Maybe Module -> HscSource -> Dependencies -> - [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> - [IfaceAnnotation] -> [IfaceDeclExts phase] -> - Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> - [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> - IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> - IfaceBackendExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe ModIfaceSelfRecomp -> + IfaceModInfo + -> Module + -> Maybe Module + -> HscSource + -> Fingerprint + -> Dependencies + -> IfacePublic_ phase + -> [IfaceExport] + -> [(OccName, Fixity)] + -> IfaceWarnings + -> [IfaceAnnotation] + -> [IfaceDeclExts phase] + -> Maybe IfaceSimplifiedCore + -> [IfaceDefault] + -> IfaceTopEnv + -> [IfaceClsInst] + -> [IfaceFamInst] + -> [IfaceRule] + -> IfaceTrustInfo + -> Bool + -> [IfaceCompleteMatch] + -> Maybe Docs + -> IfaceAbiHashesExts phase + -> ExtensibleFields + -> IfaceBinHandle phase + -> Maybe IfaceSelfRecomp + -> (OccName -> Maybe Fixity) + -> (OccName -> Maybe (OccName, Fingerprint)) + -> (OccName -> Maybe (WarningTxt GhcRn)) + -> (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase pattern ModIface - { mi_module + { mi_mod_info + , mi_module , mi_sig_of , mi_hsc_src + , mi_iface_hash , mi_deps + , mi_public , mi_exports , mi_fixities , mi_warns , mi_anns , mi_decls - , mi_extra_decls - , mi_foreign + , mi_simplified_core , mi_defaults , mi_top_env , mi_insts @@ -942,33 +1213,45 @@ pattern ModIface , mi_trust_pkg , mi_complete_matches , mi_docs - , mi_final_exts + , mi_abi_hashes , mi_ext_fields , mi_hi_bytes , mi_self_recomp_info + , mi_fix_fn + , mi_hash_fn + , mi_decl_warn_fn + , mi_export_warn_fn } <- PrivateModIface - { mi_module_ = mi_module - , mi_sig_of_ = mi_sig_of - , mi_hsc_src_ = mi_hsc_src + { mi_mod_info_ = mi_mod_info at IfaceModInfo { mi_mod_info_module = mi_module + , mi_mod_info_sig_of = mi_sig_of + , mi_mod_info_hsc_src = mi_hsc_src } + , mi_iface_hash_ = mi_iface_hash , mi_deps_ = mi_deps - , mi_exports_ = mi_exports - , mi_fixities_ = mi_fixities - , mi_warns_ = mi_warns - , mi_anns_ = mi_anns - , mi_decls_ = mi_decls - , mi_extra_decls_ = mi_extra_decls - , mi_foreign_ = mi_foreign - , mi_defaults_ = mi_defaults - , mi_top_env_ = mi_top_env - , mi_insts_ = mi_insts - , mi_fam_insts_ = mi_fam_insts - , mi_rules_ = mi_rules - , mi_trust_ = mi_trust - , mi_trust_pkg_ = mi_trust_pkg - , mi_complete_matches_ = mi_complete_matches + , mi_public_ = mi_public at IfacePublic { + mi_exports_ = mi_exports + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_defaults_ = mi_defaults + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_caches_ = IfaceCache { + mi_cache_decl_warn_fn = mi_decl_warn_fn, + mi_cache_export_warn_fn = mi_export_warn_fn, + mi_cache_fix_fn = mi_fix_fn, + mi_cache_hash_fn = mi_hash_fn + } + , mi_abi_hashes_ = mi_abi_hashes + } , mi_docs_ = mi_docs - , mi_final_exts_ = mi_final_exts , mi_ext_fields_ = mi_ext_fields , mi_hi_bytes_ = mi_hi_bytes - , mi_self_recomp_info_ = mi_self_recomp_info + , mi_self_recomp_ = mi_self_recomp_info + , mi_simplified_core_ = mi_simplified_core + , mi_top_env_ = mi_top_env } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -107,6 +107,9 @@ module GHC.Utils.Binary simpleBindingNameReader, FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, BinArray, + + -- * FingerprintWithValue + FingerprintWithValue(..) ) where import GHC.Prelude @@ -2105,3 +2108,36 @@ source location as part of a larger structure. instance (Binary v) => Binary (IntMap v) where put_ bh m = put_ bh (IntMap.toAscList m) get bh = IntMap.fromAscList <$> get bh + + +{- Note [FingerprintWithValue] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +FingerprintWithValue is a wrapper which allows us to store a fingerprint and +optionally the value which was used to create the fingerprint. + +This is useful for storing information in interface files, where we want to +store the fingerprint of the interface file, but also the value which was used +to create the fingerprint (e.g. the DynFlags). + +The wrapper is useful to ensure that the fingerprint can be read quickly without +having to deserialise the value itself. +-} + +-- | A wrapper which allows us to store a fingerprint and optionally the value which +-- was used to create the fingerprint. +data FingerprintWithValue a = FingerprintWithValue !Fingerprint (Maybe a) + deriving Functor + +instance Binary a => Binary (FingerprintWithValue a) where + put_ bh (FingerprintWithValue fp val) = do + put_ bh fp + lazyPutMaybe bh val + + get bh = do + fp <- get bh + val <- lazyGetMaybe bh + return $ FingerprintWithValue fp val + +instance NFData a => NFData (FingerprintWithValue a) where + rnf (FingerprintWithValue fp mflags) + = rnf fp `seq` rnf mflags `seq` () \ No newline at end of file ===================================== ghc/Main.hs ===================================== @@ -1133,6 +1133,8 @@ abiHash strs = do mods <- mapM find_it strs + -- MP: loadUserInterface is inefficient here since we will never find a cached + -- interface. computeInterface is probably better. let get_iface modl = loadUserInterface NotBoot (text "abiHash") modl ifaces <- initIfaceCheck (text "abiHash") hsc_env $ mapM get_iface mods @@ -1140,7 +1142,7 @@ abiHash strs = do put_ bh hiVersion -- package hashes change when the compiler version changes (for now) -- see #5328 - mapM_ (put_ bh . mi_mod_hash . mi_final_exts) ifaces + mapM_ (put_ bh . mi_mod_hash) ifaces f <- fingerprintBinMem bh putStrLn (showPpr dflags f) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b15fca2b61ec238d3148efbb9df0b165f1400439 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b15fca2b61ec238d3148efbb9df0b165f1400439 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/9d742069/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 09:38:09 2025 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 15 Mar 2025 05:38:09 -0400 Subject: [Git][ghc/ghc][master] configure: Fix incorrect SettingsLlvmAsFlags value Message-ID: <67d54a81c6d6f_3ab84df2c7cc508f@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: c758cb71 by Ben Gamari at 2025-03-15T05:37:17-04:00 configure: Fix incorrect SettingsLlvmAsFlags value Previously this was set to `LlvmAsCmd` rather than `LlvmAsFlags`, resulting in #25856. - - - - - 1 changed file: - m4/fp_settings.m4 Changes: ===================================== m4/fp_settings.m4 ===================================== @@ -89,7 +89,7 @@ AC_DEFUN([FP_SETTINGS], SettingsLlcCommand="$LlcCmd" SettingsOptCommand="$OptCmd" SettingsLlvmAsCommand="$LlvmAsCmd" - SettingsLlvmAsFlags="$LlvmAsCmd" + SettingsLlvmAsFlags="$LlvmAsFlags" if test "$EnableDistroToolchain" = "YES"; then # If the user specified --enable-distro-toolchain then we just use the View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c758cb7154e54893af2221960eac543f98550e55 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c758cb7154e54893af2221960eac543f98550e55 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/9618cf37/attachment.html> From gitlab at gitlab.haskell.org Sat Mar 15 09:38:52 2025 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Sat, 15 Mar 2025 05:38:52 -0400 Subject: [Git][ghc/ghc][wip/int-index/retry-tyclds] WIP: Retry type and class declarations Message-ID: <67d54aac8b115_3ab84df2c7cc511db@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/retry-tyclds at Glasgow Haskell Compiler / GHC Commits: 4563d5f4 by Vladislav Zavialov at 2025-03-15T12:37:06+03:00 WIP: Retry type and class declarations Metric Increase: T1969 - - - - - 6 changed files: - compiler/GHC/Tc/TyCl.hs - testsuite/tests/ghci/scripts/T12550.stdout - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -91,6 +91,7 @@ import qualified GHC.LanguageExtensions as LangExt import GHC.Data.FastString import GHC.Data.Maybe import GHC.Data.List.SetOps( minusList, equivClasses ) +import GHC.Data.Bag import GHC.Unit import GHC.Unit.Module.ModDetails @@ -110,6 +111,7 @@ import Data.List.NonEmpty ( NonEmpty(..) ) import qualified Data.List.NonEmpty as NE import Data.Traversable ( for ) import Data.Tuple( swap ) +import qualified Data.Semigroup as S {- ************************************************************************ @@ -147,6 +149,22 @@ Thus, we take two passes over the resulting tycons, first checking for general validity and then checking for valid role annotations. -} +data TcTyClGroupsAccum = + TcTyClGroupsAccum + { ttcga_inst_info :: !(Bag (InstInfo GhcRn)) -- Source-code instance decls info + , ttcga_deriv_info :: !(Bag DerivInfo) -- Deriving info + , ttcga_th_bndrs :: !ThBindEnv -- TH binding levels + } + +instance S.Semigroup TcTyClGroupsAccum where + (TcTyClGroupsAccum a1 b1 c1) <> (TcTyClGroupsAccum a2 b2 c2) = + TcTyClGroupsAccum (a1 `unionBags` a2) + (b1 `unionBags` b2) + (c1 `plusNameEnv` c2) + +instance Monoid TcTyClGroupsAccum where + mempty = TcTyClGroupsAccum emptyBag emptyBag emptyNameEnv + tcTyAndClassDecls :: [TyClGroup GhcRn] -- Mutually-recursive groups in -- dependency order -> TcM ( TcGblEnv -- Input env extended by types and @@ -161,28 +179,141 @@ tcTyAndClassDecls tyclds_s -- The code recovers internally, but if anything gave rise to -- an error we'd better stop now, to avoid a cascade -- Type check each group in dependency order folding the global env - = checkNoErrs $ fold_env [] [] emptyNameEnv tyclds_s + = checkNoErrs $ go_prefix_pass mempty tyclds_s where - fold_env :: [InstInfo GhcRn] - -> [DerivInfo] - -> ThBindEnv - -> [TyClGroup GhcRn] - -> TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo], ThBindEnv) - fold_env inst_info deriv_info th_bndrs [] + done :: TcTyClGroupsAccum -> + TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo], ThBindEnv) + done acc = do { gbl_env <- getGblEnv - ; return (gbl_env, inst_info, deriv_info, th_bndrs) } - fold_env inst_info deriv_info th_bndrs (tyclds:tyclds_s) - = do { (tcg_env, inst_info', deriv_info', th_bndrs') - <- tcTyClGroup tyclds - ; setGblEnv tcg_env $ - -- remaining groups are typechecked in the extended global env. - fold_env (inst_info' ++ inst_info) - (deriv_info' ++ deriv_info) - (th_bndrs' `plusNameEnv` th_bndrs) - tyclds_s } + ; return (gbl_env, bagToList inst_info, bagToList deriv_info, th_bndrs) } + where + TcTyClGroupsAccum{ ttcga_inst_info = inst_info + , ttcga_deriv_info = deriv_info + , ttcga_th_bndrs = th_bndrs + } = acc + + go_prefix_pass, go_selection_pass, go_failure_pass :: + TcTyClGroupsAccum -> + [TyClGroup GhcRn] -> + TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo], ThBindEnv) + + go_prefix_pass acc [] = done acc + go_prefix_pass acc gs + = do { (tcg_env, acc', gs') <- tcTyClGroupsPrefixPass gs + ; setGblEnv tcg_env $ go_selection_pass (acc' S.<> acc) gs' } + + go_selection_pass acc [] = done acc + go_selection_pass acc gs + = do { (tcg_env, acc', n, gs') <- tcTyClGroupsSelectionPass gs + ; let go_next_pass | n == 0 = go_failure_pass + | otherwise = go_prefix_pass + ; setGblEnv tcg_env $ go_next_pass (acc' S.<> acc) gs' } + + go_failure_pass acc [] = done acc + go_failure_pass acc (g:gs) + = do { (tg_env, acc') <- tcTyClGroup g + ; setGblEnv tg_env $ go_failure_pass (acc' S.<> acc) gs } + +-- Typecheck the well-kinded prefix of TyClGroups and return the remaining ones. +-- This is the "happy" path. The list of remaining TyClGroups is empty if both +-- conditions hold: +-- 1. The program is kind-correct +-- 2. All dependencies between type declarations are lexical +-- Non-lexical dependencies may arise due to type instances. +tcTyClGroupsPrefixPass :: [TyClGroup GhcRn] -- Mutually-recursive groups in + -- lexical dependency order + -> TcM ( TcGblEnv -- Input env extended by types and classes + -- and their implicit Ids,DataCons + , TcTyClGroupsAccum + , [TyClGroup GhcRn] -- The remaining groups in lexical dependency order + ) +tcTyClGroupsPrefixPass = go 0 [] mempty + where + go :: Int + -> [Name] + -> TcTyClGroupsAccum + -> [TyClGroup GhcRn] + -> TcM (TcGblEnv, TcTyClGroupsAccum, [TyClGroup GhcRn]) + go !n _ acc [] = do + gbl_env <- getGblEnv + traceTc "tcTyClGroupsPrefixPass done" (ppr n) + return (gbl_env, acc, []) + go !n bndrs acc (g:gs) = do + let (bndrs', _) = group_ext g + m_result <- tryTcTyClGroup g + case m_result of + Nothing -> do + gbl_env <- getGblEnv + traceTc "tcTyClGroupsPrefixPass stopped" (ppr n) + let gs' = map (delTyClGroupDeps bndrs) (g:gs) + return (gbl_env, acc, gs') + Just (tcg_env, acc') -> + setGblEnv tcg_env $ + go (n+1) (bndrs' ++ bndrs) (acc' S.<> acc) gs + +-- Typecheck the well-kinded selection of TyClGroups and return the remaining ones. +-- This is the "unhappy" path that exists due to non-lexical dependencies arising +-- from type instances. +tcTyClGroupsSelectionPass :: [TyClGroup GhcRn] -- Mutually-recursive groups in + -- lexical dependency order + -> TcM ( TcGblEnv -- Input env extended by types and classes + -- and their implicit Ids,DataCons + , TcTyClGroupsAccum + , Int -- Number of successfully checked groups + , [TyClGroup GhcRn] -- The remaining groups in lexical dependency order + ) +tcTyClGroupsSelectionPass all_gs = go 0 [] mempty [] ready_gs + where + ready_gs, blocked_gs :: [TyClGroup GhcRn] + (ready_gs, blocked_gs) = selectReadyTyClGroups all_gs + + go :: Int + -> [Name] + -> TcTyClGroupsAccum + -> [TyClGroup GhcRn] + -> [TyClGroup GhcRn] + -> TcM (TcGblEnv, TcTyClGroupsAccum, Int, [TyClGroup GhcRn]) + go !n bndrs acc failed_gs [] = do + gbl_env <- getGblEnv + traceTc "tcTyClGroupsSelectionPass done" (ppr n) + let blocked_gs' = map (delTyClGroupDeps bndrs) blocked_gs + return (gbl_env, acc, n, reverse failed_gs ++ blocked_gs') + go !n bndrs acc failed_gs (g:gs) = do + let (bndrs', _) = group_ext g + m_result <- tryTcTyClGroup g + case m_result of + Nothing -> go n bndrs acc (g:failed_gs) gs + Just (tcg_env, acc') -> + setGblEnv tcg_env $ + go (n+1) (bndrs' ++ bndrs) (acc' S.<> acc) failed_gs gs + +selectReadyTyClGroups :: [TyClGroup GhcRn] -> ([TyClGroup GhcRn], [TyClGroup GhcRn]) +selectReadyTyClGroups gs = (ready_inst_gs ++ ready_noinst_gs, blocked_gs) + where + (ready_inst_gs, ready_noinst_gs, blocked_gs) = foldr classify ([], [], []) gs + -- ready_inst_gs: most likely to unblock further type checking + -- ready_noinst_gs: might indirectly unblock further type checking + -- blocked_gs: unusable + + classify :: TyClGroup GhcRn -> ([TyClGroup GhcRn], [TyClGroup GhcRn], [TyClGroup GhcRn]) + -> ([TyClGroup GhcRn], [TyClGroup GhcRn], [TyClGroup GhcRn]) + classify g at TyClGroup{ group_ext = (_, deps) + , group_instds = inst_ds } + ~(xs, ys, zs) + | not ready = (xs, ys, g:zs) + | null inst_ds = (xs, g:ys, zs) + | otherwise = (g:xs, ys, zs) + where ready = isEmptyNameSet deps + +tryTcTyClGroup :: TyClGroup GhcRn -> TcM (Maybe (TcGblEnv, TcTyClGroupsAccum)) +tryTcTyClGroup g = tryTcDiscardingErrs (return Nothing) (Just <$> tcTyClGroup g) + +delTyClGroupDeps :: [Name] -> TyClGroup GhcRn -> TyClGroup GhcRn +delTyClGroupDeps names g at TyClGroup{group_ext = (bndrs, deps)} + = g {group_ext = (bndrs, delListFromNameSet deps names)} tcTyClGroup :: TyClGroup GhcRn - -> TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo], ThBindEnv) + -> TcM (TcGblEnv, TcTyClGroupsAccum) -- Typecheck one strongly-connected component of type, class, and instance decls -- See Note [TyClGroups and dependency analysis] in GHC.Hs.Decls tcTyClGroup (TyClGroup { group_tyclds = tyclds @@ -245,8 +376,10 @@ tcTyClGroup (TyClGroup { group_tyclds = tyclds ; let deriv_info = datafam_deriv_info ++ data_deriv_info ; let gbl_env'' = gbl_env' { tcg_ksigs = tcg_ksigs gbl_env' `unionNameSet` kindless } - ; return (gbl_env'', inst_info, deriv_info, - th_bndrs' `plusNameEnv` th_bndrs) } + ; let acc = TcTyClGroupsAccum{ ttcga_inst_info = listToBag inst_info + , ttcga_deriv_info = listToBag deriv_info + , ttcga_th_bndrs = th_bndrs' `plusNameEnv` th_bndrs } + ; return (gbl_env'', acc) } -- Gives the kind for every TyCon that has a standalone kind signature type KindSigEnv = NameEnv Kind ===================================== testsuite/tests/ghci/scripts/T12550.stdout ===================================== @@ -65,12 +65,12 @@ instance Functor Par1 -- Defined in ‘GHC.Internal.Generics’ instance ∀ (f ∷ ★ → ★). Functor f ⇒ Functor (Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance Functor U1 -- Defined in ‘GHC.Internal.Generics’ -instance Functor (URec Char) -- Defined in ‘GHC.Internal.Generics’ +instance Functor (URec Word) -- Defined in ‘GHC.Internal.Generics’ +instance Functor (URec Int) -- Defined in ‘GHC.Internal.Generics’ +instance Functor (URec Float) -- Defined in ‘GHC.Internal.Generics’ instance Functor (URec Double) -- Defined in ‘GHC.Internal.Generics’ -instance Functor (URec Float) -- Defined in ‘GHC.Internal.Generics’ -instance Functor (URec Int) -- Defined in ‘GHC.Internal.Generics’ -instance Functor (URec Word) -- Defined in ‘GHC.Internal.Generics’ +instance Functor (URec Char) -- Defined in ‘GHC.Internal.Generics’ instance Functor V1 -- Defined in ‘GHC.Internal.Generics’ datatypeName ∷ ∀ {k} (d ∷ k) k1 (t ∷ k → (k1 → ★) → k1 → ★) (f ∷ k1 → ★) ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -11274,12 +11274,12 @@ instance forall i (c :: GHC.Internal.Generics.Meta) (f :: * -> *). GHC.Internal. instance GHC.Internal.Base.Functor GHC.Internal.Generics.Par1 -- Defined in ‘GHC.Internal.Generics’ instance forall (f :: * -> *). GHC.Internal.Base.Functor f => GHC.Internal.Base.Functor (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Generics.U1 -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Word) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Generics.V1 -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Text.ParserCombinators.ReadP.P -- Defined in ‘GHC.Internal.Text.ParserCombinators.ReadP’ instance GHC.Internal.Base.Functor GHC.Internal.Text.ParserCombinators.ReadP.ReadP -- Defined in ‘GHC.Internal.Text.ParserCombinators.ReadP’ @@ -11703,12 +11703,12 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Classes.Eq (f p) => GHC.I instance GHC.Internal.Classes.Eq GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Eq GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Eq GHC.Internal.IO.Buffer.BufferState -- Defined in ‘GHC.Internal.IO.Buffer’ instance GHC.Internal.Classes.Eq GHC.Internal.IO.Device.IODeviceType -- Defined in ‘GHC.Internal.IO.Device’ @@ -11868,12 +11868,12 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Classes.Ord (f p) => GHC. instance GHC.Internal.Classes.Ord GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Ord GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Ord GHC.Internal.IO.Device.SeekMode -- Defined in ‘GHC.Internal.IO.Device’ instance GHC.Internal.Classes.Ord GHC.Internal.IO.Handle.Types.BufferMode -- Defined in ‘GHC.Internal.IO.Handle.Types’ @@ -12493,12 +12493,12 @@ instance forall a b c d e f g. GHC.Internal.Generics.Generic (a, b, c, d, e, f, instance forall a b c d e f g h. GHC.Internal.Generics.Generic (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Internal.Generics’ instance forall a b c d e f g h i. GHC.Internal.Generics.Generic (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.Generic () -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.Generic GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Generics’ @@ -12571,12 +12571,12 @@ instance forall i (c :: GHC.Internal.Generics.Meta) k (f :: k -> *). GHC.Interna instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Generics’ instance forall k (f :: k -> *). GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Generics.U1 -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Word) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Generics.V1 -- Defined in ‘GHC.Internal.Generics’ instance forall (mn :: GHC.Internal.Maybe.Maybe GHC.Internal.Types.Symbol) (su :: GHC.Internal.Generics.SourceUnpackedness) (ss :: GHC.Internal.Generics.SourceStrictness) (ds :: GHC.Internal.Generics.DecidedStrictness). (GHC.Internal.Generics.SingI mn, GHC.Internal.Generics.SingI su, GHC.Internal.Generics.SingI ss, GHC.Internal.Generics.SingI ds) => GHC.Internal.Generics.Selector (GHC.Internal.Generics.MetaSel mn su ss ds) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.SingI GHC.Internal.Generics.LeftAssociative -- Defined in ‘GHC.Internal.Generics’ @@ -13155,11 +13155,11 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Show.Show (f p) => GHC.In instance GHC.Internal.Show.Show GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Show.Show GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.UAddr p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Show.Show GHC.Internal.IO.Device.SeekMode -- Defined in ‘GHC.Internal.IO.Device’ ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -14319,12 +14319,12 @@ instance forall i (c :: GHC.Internal.Generics.Meta) (f :: * -> *). GHC.Internal. instance GHC.Internal.Base.Functor GHC.Internal.Generics.Par1 -- Defined in ‘GHC.Internal.Generics’ instance forall (f :: * -> *). GHC.Internal.Base.Functor f => GHC.Internal.Base.Functor (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Generics.U1 -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Word) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Generics.V1 -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Text.ParserCombinators.ReadP.P -- Defined in ‘GHC.Internal.Text.ParserCombinators.ReadP’ instance GHC.Internal.Base.Functor GHC.Internal.Text.ParserCombinators.ReadP.ReadP -- Defined in ‘GHC.Internal.Text.ParserCombinators.ReadP’ @@ -14736,12 +14736,12 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Classes.Eq (f p) => GHC.I instance GHC.Internal.Classes.Eq GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Eq GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Eq GHC.Internal.IO.Buffer.BufferState -- Defined in ‘GHC.Internal.IO.Buffer’ instance GHC.Internal.Classes.Eq GHC.Internal.IO.Device.IODeviceType -- Defined in ‘GHC.Internal.IO.Device’ @@ -14902,12 +14902,12 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Classes.Ord (f p) => GHC. instance GHC.Internal.Classes.Ord GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Ord GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Ord GHC.Internal.IO.Device.SeekMode -- Defined in ‘GHC.Internal.IO.Device’ instance GHC.Internal.Classes.Ord GHC.Internal.IO.Handle.Types.BufferMode -- Defined in ‘GHC.Internal.IO.Handle.Types’ @@ -15529,12 +15529,12 @@ instance forall a b c d e f g. GHC.Internal.Generics.Generic (a, b, c, d, e, f, instance forall a b c d e f g h. GHC.Internal.Generics.Generic (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Internal.Generics’ instance forall a b c d e f g h i. GHC.Internal.Generics.Generic (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.Generic () -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.Generic GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Generics’ @@ -15607,12 +15607,12 @@ instance forall i (c :: GHC.Internal.Generics.Meta) k (f :: k -> *). GHC.Interna instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Generics’ instance forall k (f :: k -> *). GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Generics.U1 -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Word) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Generics.V1 -- Defined in ‘GHC.Internal.Generics’ instance forall (mn :: GHC.Internal.Maybe.Maybe GHC.Internal.Types.Symbol) (su :: GHC.Internal.Generics.SourceUnpackedness) (ss :: GHC.Internal.Generics.SourceStrictness) (ds :: GHC.Internal.Generics.DecidedStrictness). (GHC.Internal.Generics.SingI mn, GHC.Internal.Generics.SingI su, GHC.Internal.Generics.SingI ss, GHC.Internal.Generics.SingI ds) => GHC.Internal.Generics.Selector (GHC.Internal.Generics.MetaSel mn su ss ds) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.SingI GHC.Internal.Generics.LeftAssociative -- Defined in ‘GHC.Internal.Generics’ @@ -16184,11 +16184,11 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Show.Show (f p) => GHC.In instance GHC.Internal.Show.Show GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Show.Show GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.UAddr p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Show.Show GHC.Internal.IO.Device.SeekMode -- Defined in ‘GHC.Internal.IO.Device’ ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -11536,12 +11536,12 @@ instance forall i (c :: GHC.Internal.Generics.Meta) (f :: * -> *). GHC.Internal. instance GHC.Internal.Base.Functor GHC.Internal.Generics.Par1 -- Defined in ‘GHC.Internal.Generics’ instance forall (f :: * -> *). GHC.Internal.Base.Functor f => GHC.Internal.Base.Functor (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Generics.U1 -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Word) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Generics.V1 -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Text.ParserCombinators.ReadP.P -- Defined in ‘GHC.Internal.Text.ParserCombinators.ReadP’ instance GHC.Internal.Base.Functor GHC.Internal.Text.ParserCombinators.ReadP.ReadP -- Defined in ‘GHC.Internal.Text.ParserCombinators.ReadP’ @@ -11958,12 +11958,12 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Classes.Eq (f p) => GHC.I instance GHC.Internal.Classes.Eq GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Eq GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Eq GHC.Internal.IO.Buffer.BufferState -- Defined in ‘GHC.Internal.IO.Buffer’ instance GHC.Internal.Classes.Eq GHC.Internal.IO.Device.IODeviceType -- Defined in ‘GHC.Internal.IO.Device’ @@ -12126,12 +12126,12 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Classes.Ord (f p) => GHC. instance GHC.Internal.Classes.Ord GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Ord GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Ord GHC.Internal.IO.Device.SeekMode -- Defined in ‘GHC.Internal.IO.Device’ instance GHC.Internal.Classes.Ord GHC.Internal.IO.Handle.Types.BufferMode -- Defined in ‘GHC.Internal.IO.Handle.Types’ @@ -12756,12 +12756,12 @@ instance forall a b c d e f g. GHC.Internal.Generics.Generic (a, b, c, d, e, f, instance forall a b c d e f g h. GHC.Internal.Generics.Generic (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Internal.Generics’ instance forall a b c d e f g h i. GHC.Internal.Generics.Generic (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.Generic () -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.Generic GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Generics’ @@ -12834,12 +12834,12 @@ instance forall i (c :: GHC.Internal.Generics.Meta) k (f :: k -> *). GHC.Interna instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Generics’ instance forall k (f :: k -> *). GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Generics.U1 -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Word) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Generics.V1 -- Defined in ‘GHC.Internal.Generics’ instance forall (mn :: GHC.Internal.Maybe.Maybe GHC.Internal.Types.Symbol) (su :: GHC.Internal.Generics.SourceUnpackedness) (ss :: GHC.Internal.Generics.SourceStrictness) (ds :: GHC.Internal.Generics.DecidedStrictness). (GHC.Internal.Generics.SingI mn, GHC.Internal.Generics.SingI su, GHC.Internal.Generics.SingI ss, GHC.Internal.Generics.SingI ds) => GHC.Internal.Generics.Selector (GHC.Internal.Generics.MetaSel mn su ss ds) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.SingI GHC.Internal.Generics.LeftAssociative -- Defined in ‘GHC.Internal.Generics’ @@ -13424,11 +13424,11 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Show.Show (f p) => GHC.In instance GHC.Internal.Show.Show GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Show.Show GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.UAddr p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Show.Show GHC.Internal.IO.Device.SeekMode -- Defined in ‘GHC.Internal.IO.Device’ ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -11274,12 +11274,12 @@ instance forall i (c :: GHC.Internal.Generics.Meta) (f :: * -> *). GHC.Internal. instance GHC.Internal.Base.Functor GHC.Internal.Generics.Par1 -- Defined in ‘GHC.Internal.Generics’ instance forall (f :: * -> *). GHC.Internal.Base.Functor f => GHC.Internal.Base.Functor (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Generics.U1 -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ -instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Word) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ +instance GHC.Internal.Base.Functor (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Generics.V1 -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Base.Functor GHC.Internal.Text.ParserCombinators.ReadP.P -- Defined in ‘GHC.Internal.Text.ParserCombinators.ReadP’ instance GHC.Internal.Base.Functor GHC.Internal.Text.ParserCombinators.ReadP.ReadP -- Defined in ‘GHC.Internal.Text.ParserCombinators.ReadP’ @@ -11703,12 +11703,12 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Classes.Eq (f p) => GHC.I instance GHC.Internal.Classes.Eq GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Eq GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Eq (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Eq GHC.Internal.IO.Buffer.BufferState -- Defined in ‘GHC.Internal.IO.Buffer’ instance GHC.Internal.Classes.Eq GHC.Internal.IO.Device.IODeviceType -- Defined in ‘GHC.Internal.IO.Device’ @@ -11868,12 +11868,12 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Classes.Ord (f p) => GHC. instance GHC.Internal.Classes.Ord GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Ord GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Classes.Ord (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Classes.Ord GHC.Internal.IO.Device.SeekMode -- Defined in ‘GHC.Internal.IO.Device’ instance GHC.Internal.Classes.Ord GHC.Internal.IO.Handle.Types.BufferMode -- Defined in ‘GHC.Internal.IO.Handle.Types’ @@ -12493,12 +12493,12 @@ instance forall a b c d e f g. GHC.Internal.Generics.Generic (a, b, c, d, e, f, instance forall a b c d e f g h. GHC.Internal.Generics.Generic (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Internal.Generics’ instance forall a b c d e f g h i. GHC.Internal.Generics.Generic (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ()) p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.Generic () -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Generics.Generic (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.Generic GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Generics’ @@ -12571,12 +12571,12 @@ instance forall i (c :: GHC.Internal.Generics.Meta) k (f :: k -> *). GHC.Interna instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Generics’ instance forall k (f :: k -> *). GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Generics.U1 -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ -instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Word) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Int) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Float) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Double) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec GHC.Internal.Types.Char) -- Defined in ‘GHC.Internal.Generics’ +instance forall k. GHC.Internal.Generics.Generic1 (GHC.Internal.Generics.URec (GHC.Internal.Ptr.Ptr ())) -- Defined in ‘GHC.Internal.Generics’ instance forall k. GHC.Internal.Generics.Generic1 GHC.Internal.Generics.V1 -- Defined in ‘GHC.Internal.Generics’ instance forall (mn :: GHC.Internal.Maybe.Maybe GHC.Internal.Types.Symbol) (su :: GHC.Internal.Generics.SourceUnpackedness) (ss :: GHC.Internal.Generics.SourceStrictness) (ds :: GHC.Internal.Generics.DecidedStrictness). (GHC.Internal.Generics.SingI mn, GHC.Internal.Generics.SingI su, GHC.Internal.Generics.SingI ss, GHC.Internal.Generics.SingI ds) => GHC.Internal.Generics.Selector (GHC.Internal.Generics.MetaSel mn su ss ds) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Generics.SingI GHC.Internal.Generics.LeftAssociative -- Defined in ‘GHC.Internal.Generics’ @@ -13155,11 +13155,11 @@ instance forall k (f :: k -> *) (p :: k). GHC.Internal.Show.Show (f p) => GHC.In instance GHC.Internal.Show.Show GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Show.Show GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.U1 p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ -instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Word p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Int p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Float p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Double p) -- Defined in ‘GHC.Internal.Generics’ +instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.URec GHC.Internal.Types.Char p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.UAddr p) -- Defined in ‘GHC.Internal.Generics’ instance forall k (p :: k). GHC.Internal.Show.Show (GHC.Internal.Generics.V1 p) -- Defined in ‘GHC.Internal.Generics’ instance GHC.Internal.Show.Show GHC.Internal.IO.Device.SeekMode -- Defined in ‘GHC.Internal.IO.Device’ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4563d5f429436a4f0c6eb9890ac41bb4de37ceee -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4563d5f429436a4f0c6eb9890ac41bb4de37ceee You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/1ac26379/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 14:42:50 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 15 Mar 2025 10:42:50 -0400 Subject: [Git][ghc/ghc][wip/T25647] fix order Message-ID: <67d591ea5622f_1b7059062a885ec@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: 6ea2e274 by Patrick at 2025-03-15T22:42:40+08:00 fix order - - - - - 2 changed files: - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -259,11 +259,13 @@ quantifyFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] -- See Note [Type variables in type families instance decl] ; (dvs, outer_wcs_imp_dvs) <- candidateQTyVarsWithBinders outer_exp_tvs (outer_imp_tvs ++ wcs) lhs_ty - ; (qtvs, outer_wcs_imp_qtvs) <- quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs + ; (qtvs, outer_wcs_imp_qtvs') <- quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs -- Have to make a same defaulting choice for result kind here -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] + ; let outer_wcs_imp_qtvs_set = mkVarSet outer_wcs_imp_qtvs' + ; let outer_wcs_imp_qtvs = [v | v <- outer_wcs_imp_qtvs, v `elemVarSet` outer_wcs_imp_qtvs_set] ; let final_tvs = scopedSort (qtvs ++ outer_wcs_imp_qtvs ++ outer_exp_tvs) -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1790,7 +1790,6 @@ quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs ; undefaulted <- defaultTyVars DefaultNonStandardTyVars dvs ; undefaulted_outer_wcs_imp_tvs <- defaultTyVars TryNotToDefaultNonStandardTyVars outer_wcs_imp_dvs ; (final_qtvs, final_outer_wcs_imp_qtvs) <- liftZonkM $ do - -- resume order and then skolemise qtvs <- mapMaybeM zonk_quant $ undefaulted outer_wcs_imp_qtvs <- mapMaybeM zonk_quant $ undefaulted_outer_wcs_imp_tvs return (qtvs, outer_wcs_imp_qtvs) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ea2e274405f3a35a3478efb93b3ed0f38985b71 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ea2e274405f3a35a3478efb93b3ed0f38985b71 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/1e265bef/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 15:00:14 2025 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sat, 15 Mar 2025 11:00:14 -0400 Subject: [Git][ghc/ghc][wip/T25647] fix ordering Message-ID: <67d595fef21f_1b7058ef8a013241@gitlab.mail> Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC Commits: b390a34c by Patrick at 2025-03-15T23:00:02+08:00 fix ordering - - - - - 2 changed files: - compiler/GHC/Tc/TyCl.hs - testsuite/tests/dependent/should_compile/T14066a.stderr Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -259,13 +259,11 @@ quantifyFamInstLHSBinders tclvl skol_info outer_bndrs hs_outer_bndrs wcs lhs_ty -- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] -- See Note [Type variables in type families instance decl] ; (dvs, outer_wcs_imp_dvs) <- candidateQTyVarsWithBinders outer_exp_tvs (outer_imp_tvs ++ wcs) lhs_ty - ; (qtvs, outer_wcs_imp_qtvs') <- quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs + ; (qtvs, outer_wcs_imp_qtvs) <- quantifyTyVarsWithBinders skol_info dvs outer_wcs_imp_dvs -- Have to make a same defaulting choice for result kind here -- and the `kindGeneralizeAll` in `tcConDecl`. -- see (GT4) in -- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts] - ; let outer_wcs_imp_qtvs_set = mkVarSet outer_wcs_imp_qtvs' - ; let outer_wcs_imp_qtvs = [v | v <- outer_wcs_imp_qtvs, v `elemVarSet` outer_wcs_imp_qtvs_set] ; let final_tvs = scopedSort (qtvs ++ outer_wcs_imp_qtvs ++ outer_exp_tvs) -- This scopedSort is important: the qtvs may be /interleaved/ with -- the outer_tvs. See Note [Generalising in tcTyFamInstEqnGuts] ===================================== testsuite/tests/dependent/should_compile/T14066a.stderr ===================================== @@ -1,5 +1,5 @@ - T14066a.hs:13:3: warning: [GHC-28129] [-Winaccessible-code (in -Wdefault)] Type family instance equation is overlapped: - forall {c} {x :: c} {d} {y :: d}. + forall {c} {d} {x :: c} {y :: d}. Bar x y = Bool -- Defined at T14066a.hs:13:3 + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b390a34ca53ea7d7a74fcdc52c8ebd6cd4878112 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b390a34ca53ea7d7a74fcdc52c8ebd6cd4878112 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/47f72d96/attachment-0001.html> From gitlab at gitlab.haskell.org Sat Mar 15 23:47:29 2025 From: gitlab at gitlab.haskell.org (Matthew Craven (@clyring)) Date: Sat, 15 Mar 2025 19:47:29 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/clyring/ghc-bignum-exports Message-ID: <67d611912a85c_df7dc3a148433579@gitlab.mail> Matthew Craven pushed new branch wip/clyring/ghc-bignum-exports at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/clyring/ghc-bignum-exports You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/47767427/attachment.html> From gitlab at gitlab.haskell.org Sun Mar 16 00:04:58 2025 From: gitlab at gitlab.haskell.org (Matthew Craven (@clyring)) Date: Sat, 15 Mar 2025 20:04:58 -0400 Subject: [Git][ghc/ghc][wip/clyring/ghc-bignum-exports] 2 commits: Add interface-stability test for ghc-bignum Message-ID: <67d615aa3ec47_df7dc6cbe0c35273@gitlab.mail> Matthew Craven pushed to branch wip/clyring/ghc-bignum-exports at Glasgow Haskell Compiler / GHC Commits: bf61735f by Matthew Craven at 2025-03-15T19:59:38-04:00 Add interface-stability test for ghc-bignum As with ghc-prim, it makes sense to have some protection against accidental interface changes to this package caused by changes in ghc-internal. - - - - - 95c7cd9e by Matthew Craven at 2025-03-15T20:02:04-04:00 Add README reference for the interface-stability tests - - - - - 4 changed files: - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - + testsuite/tests/interface-stability/ghc-bignum-exports.stdout - utils/dump-decls/Main.hs Changes: ===================================== testsuite/tests/interface-stability/README.mkd ===================================== @@ -9,6 +9,7 @@ following packages: * `ghc-experimental` * `template-haskell` * `ghc-prim` + * `ghc-bignum` These are compared against the expected exports in the test's corresponding `.stdout` file. ===================================== testsuite/tests/interface-stability/all.T ===================================== @@ -7,7 +7,9 @@ def check_package(pkg_name): makefile_test, [f'exports_{pkg_name}']) +# About these tests: see README.mkd in this directory check_package('base') check_package('ghc-experimental') check_package('template-haskell') check_package('ghc-prim') +check_package('ghc-bignum') ===================================== testsuite/tests/interface-stability/ghc-bignum-exports.stdout ===================================== @@ -0,0 +1,502 @@ + +module GHC.Num.Backend where + +-- ignored + + +module GHC.Num.Backend.Native where + -- Safety: None + backendName :: [GHC.Internal.Types.Char] + bignat_add :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + bignat_add_word :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_and :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_and_not :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_compare :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Int# + bignat_encode_double :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# + bignat_gcd :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + bignat_gcd_word :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bignat_gcd_word_word :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bignat_mul :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_mul_word :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_or :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_popcount :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# + bignat_powmod :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_powmod_word :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bignat_powmod_words :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bignat_quot :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_quot_word :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + bignat_quotrem :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + bignat_quotrem_normalized :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + bignat_quotrem_word :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + bignat_rem :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + bignat_rem_word :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bignat_shiftl :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + bignat_shiftr :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + bignat_shiftr_neg :: forall s. GHC.Internal.Bignum.WordArray.MutableWordArray# s -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + bignat_sub :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld, GHC.Internal.Bignum.Primitives.Bool# #) + bignat_sub_word :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld, GHC.Internal.Bignum.Primitives.Bool# #) + bignat_xor :: GHC.Internal.Bignum.WordArray.MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + count_words_bits :: GHC.Internal.Prim.Word# -> (# GHC.Internal.Prim.Word#, GHC.Internal.Prim.Word# #) + count_words_bits_int :: GHC.Internal.Prim.Word# -> (# GHC.Internal.Prim.Int#, GHC.Internal.Prim.Int# #) + integer_gcde :: GHC.Internal.Bignum.Integer.Integer -> GHC.Internal.Bignum.Integer.Integer -> (# GHC.Internal.Bignum.Integer.Integer, GHC.Internal.Bignum.Integer.Integer, GHC.Internal.Bignum.Integer.Integer #) + integer_powmod :: GHC.Internal.Bignum.Integer.Integer -> GHC.Internal.Bignum.Natural.Natural -> GHC.Internal.Bignum.Natural.Natural -> GHC.Internal.Bignum.Natural.Natural + integer_recip_mod :: GHC.Internal.Bignum.Integer.Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) + +module GHC.Num.Backend.Selected where + +-- ignored + + +module GHC.Num.BigNat where + -- Safety: None + type BigNat :: * + data BigNat = BN# {unBigNat :: BigNat#} + type BigNat# :: GHC.Internal.Types.UnliftedType + type BigNat# = GHC.Internal.Bignum.WordArray.WordArray# + bigNatAdd :: BigNat# -> BigNat# -> BigNat# + bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# + bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatAnd :: BigNat# -> BigNat# -> BigNat# + bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat# + bigNatAndNot :: BigNat# -> BigNat# -> BigNat# + bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatBit :: GHC.Internal.Types.Word -> BigNat# + bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat# + bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool + bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering + bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering + bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering + bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatCtz :: BigNat# -> GHC.Internal.Types.Word + bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word# + bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word + bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word# + bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# + bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool + bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat# + bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) + bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) + bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) + bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) + bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) + bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) + bigNatFromWord :: GHC.Internal.Types.Word -> BigNat# + bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat# + bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat# + bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat + bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat# + bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray# + bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat# + bigNatGcd :: BigNat# -> BigNat# -> BigNat# + bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool + bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool + bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool + bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word + bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# + bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool + bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) + bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool + bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool + bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatLcm :: BigNat# -> BigNat# -> BigNat# + bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool + bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool + bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word + bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word# + bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word + bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# + bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word + bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# + bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool + bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatMul :: BigNat# -> BigNat# -> BigNat# + bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# + bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool + bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatOne :: BigNat + bigNatOne# :: (# #) -> BigNat# + bigNatOr :: BigNat# -> BigNat# -> BigNat# + bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word + bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word# + bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat# + bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bigNatQuot :: BigNat# -> BigNat# -> BigNat# + bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #) + bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #) + bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# + bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatRem :: BigNat# -> BigNat# -> BigNat# + bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word + bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat# + bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat# + bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatSize :: BigNat# -> GHC.Internal.Types.Word + bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int# + bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word + bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# + bigNatSqr :: BigNat# -> BigNat# + bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #) + bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat# + bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #) + bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat# + bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool + bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# + bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word + bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + bigNatToInt :: BigNat# -> GHC.Internal.Types.Int + bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int# + bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + bigNatToWord :: BigNat# -> GHC.Internal.Types.Word + bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word# + bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64# + bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word] + bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) + bigNatXor :: BigNat# -> BigNat# -> BigNat# + bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# + bigNatZero :: BigNat + bigNatZero# :: (# #) -> BigNat# + gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int + gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word + gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + raiseDivZero_BigNat :: (# #) -> BigNat# + +module GHC.Num.Integer where + -- Safety: None + type Integer :: * + data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray# + integerAbs :: Integer -> Integer + integerAdd :: Integer -> Integer -> Integer + integerAnd :: Integer -> Integer -> Integer + integerBit :: GHC.Internal.Types.Word -> Integer + integerBit# :: GHC.Internal.Prim.Word# -> Integer + integerCheck :: Integer -> GHC.Internal.Types.Bool + integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# + integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering + integerComplement :: Integer -> Integer + integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #) + integerDiv :: Integer -> Integer -> Integer + integerDivMod :: Integer -> Integer -> (Integer, Integer) + integerDivMod# :: Integer -> Integer -> (# Integer, Integer #) + integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double + integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# + integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# + integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool + integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# + integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer + integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) + integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer + integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer + integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer + integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer + integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) + integerFromInt :: GHC.Internal.Types.Int -> Integer + integerFromInt# :: GHC.Internal.Prim.Int# -> Integer + integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer + integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer + integerFromWord :: GHC.Internal.Types.Word -> Integer + integerFromWord# :: GHC.Internal.Prim.Word# -> Integer + integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer + integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer + integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer + integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer + integerGcd :: Integer -> Integer -> Integer + integerGcde :: Integer -> Integer -> (Integer, Integer, Integer) + integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #) + integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool + integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# + integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool + integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# + integerIsNegative :: Integer -> GHC.Internal.Types.Bool + integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# + integerIsOne :: Integer -> GHC.Internal.Types.Bool + integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #) + integerIsZero :: Integer -> GHC.Internal.Types.Bool + integerLcm :: Integer -> Integer -> Integer + integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool + integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# + integerLog2 :: Integer -> GHC.Internal.Types.Word + integerLog2# :: Integer -> GHC.Internal.Prim.Word# + integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word + integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word# + integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word + integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# + integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool + integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# + integerMod :: Integer -> Integer -> Integer + integerMul :: Integer -> Integer -> Integer + integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool + integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# + integerNegate :: Integer -> Integer + integerOne :: Integer + integerOr :: Integer -> Integer -> Integer + integerPopCount# :: Integer -> GHC.Internal.Prim.Int# + integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) + integerQuot :: Integer -> Integer -> Integer + integerQuotRem :: Integer -> Integer -> (Integer, Integer) + integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #) + integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) + integerRem :: Integer -> Integer -> Integer + integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer + integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer + integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer + integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer + integerSignum :: Integer -> Integer + integerSignum# :: Integer -> GHC.Internal.Prim.Int# + integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# + integerSqr :: Integer -> Integer + integerSub :: Integer -> Integer -> Integer + integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool + integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# + integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word + integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat# + integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #) + integerToInt :: Integer -> GHC.Internal.Types.Int + integerToInt# :: Integer -> GHC.Internal.Prim.Int# + integerToInt64# :: Integer -> GHC.Internal.Prim.Int64# + integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word + integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural + integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural + integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural + integerToWord :: Integer -> GHC.Internal.Types.Word + integerToWord# :: Integer -> GHC.Internal.Prim.Word# + integerToWord64# :: Integer -> GHC.Internal.Prim.Word64# + integerXor :: Integer -> Integer -> Integer + integerZero :: Integer + +module GHC.Num.Natural where + -- Safety: None + type Natural :: * + data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray# + naturalAdd :: Natural -> Natural -> Natural + naturalAnd :: Natural -> Natural -> Natural + naturalAndNot :: Natural -> Natural -> Natural + naturalBit :: GHC.Internal.Types.Word -> Natural + naturalBit# :: GHC.Internal.Prim.Word# -> Natural + naturalCheck :: Natural -> GHC.Internal.Types.Bool + naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool# + naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural + naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural + naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering + naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural + naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural + naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# + naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# + naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool + naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# + naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural + naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) + naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural + naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) + naturalFromWord :: GHC.Internal.Types.Word -> Natural + naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural + naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural + naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural + naturalGcd :: Natural -> Natural -> Natural + naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool + naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# + naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool + naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# + naturalIsOne :: Natural -> GHC.Internal.Types.Bool + naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) + naturalIsZero :: Natural -> GHC.Internal.Types.Bool + naturalLcm :: Natural -> Natural -> Natural + naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool + naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# + naturalLog2 :: Natural -> GHC.Internal.Types.Word + naturalLog2# :: Natural -> GHC.Internal.Prim.Word# + naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word + naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word# + naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word + naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# + naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool + naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# + naturalMul :: Natural -> Natural -> Natural + naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool + naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# + naturalNegate :: Natural -> Natural + naturalOne :: Natural + naturalOr :: Natural -> Natural -> Natural + naturalPopCount :: Natural -> GHC.Internal.Types.Word + naturalPopCount# :: Natural -> GHC.Internal.Prim.Word# + naturalPowMod :: Natural -> Natural -> Natural -> Natural + naturalQuot :: Natural -> Natural -> Natural + naturalQuotRem :: Natural -> Natural -> (Natural, Natural) + naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #) + naturalRem :: Natural -> Natural -> Natural + naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural + naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural + naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural + naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural + naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural + naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural + naturalSignum :: Natural -> Natural + naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# + naturalSqr :: Natural -> Natural + naturalSub :: Natural -> Natural -> (# (# #) | Natural #) + naturalSubThrow :: Natural -> Natural -> Natural + naturalSubUnsafe :: Natural -> Natural -> Natural + naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool + naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# + naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word + naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat# + naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + naturalToWord :: Natural -> GHC.Internal.Types.Word + naturalToWord# :: Natural -> GHC.Internal.Prim.Word# + naturalToWordClamp :: Natural -> GHC.Internal.Types.Word + naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word# + naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) + naturalXor :: Natural -> Natural -> Natural + naturalZero :: Natural + +module GHC.Num.Primitives where + -- Safety: None + (&&#) :: Bool# -> Bool# -> Bool# + type Bool# :: TYPE GHC.Internal.Types.IntRep + type Bool# = GHC.Internal.Prim.Int# + absI# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + andNot# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + bitW# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# + cmpI# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + cmpW# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering + intEncodeDouble# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# + ioBool :: GHC.Internal.Types.IO GHC.Internal.Types.Bool -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld, Bool# #) + ioInt# :: GHC.Internal.Types.IO GHC.Internal.Types.Int -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld, GHC.Internal.Prim.Int# #) + ioVoid :: forall a. GHC.Internal.Types.IO a -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld + ioWord# :: GHC.Internal.Types.IO GHC.Internal.Types.Word -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld, GHC.Internal.Prim.Word# #) + maxI# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + maxW# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + minI# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + minW# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + notB# :: Bool# -> Bool# + plusWord12# :: GHC.Internal.Prim.Word# -> (# GHC.Internal.Prim.Word#, GHC.Internal.Prim.Word# #) -> (# GHC.Internal.Prim.Word#, GHC.Internal.Prim.Word# #) + plusWord3# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> (# GHC.Internal.Prim.Word#, GHC.Internal.Prim.Word# #) + popCntI# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# + quotRemWord3# :: (# GHC.Internal.Prim.Word#, GHC.Internal.Prim.Word# #) -> GHC.Internal.Prim.Word# -> (# (# GHC.Internal.Prim.Word#, GHC.Internal.Prim.Word# #), GHC.Internal.Prim.Word# #) + raiseDivZero :: forall a. a + raiseDivZero_Word# :: (# #) -> GHC.Internal.Prim.Word# + raiseUnderflow :: forall a. a + raiseUnderflow_Word# :: (# #) -> GHC.Internal.Prim.Word# + sgnI# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + shiftRW# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + testBitI# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Bool# + testBitW# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Bool# + unexpectedValue :: forall a. a + unexpectedValue_Int# :: (# #) -> GHC.Internal.Prim.Int# + unexpectedValue_Word# :: (# #) -> GHC.Internal.Prim.Word# + wordEncodeDouble# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# + wordFromAbsInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# + wordFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordFromByteArray# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> Bool# -> GHC.Internal.Prim.Word# + wordFromByteArrayBE# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + wordFromByteArrayLE# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + wordIsPowerOf2# :: GHC.Internal.Prim.Word# -> (# (# #) | GHC.Internal.Prim.Word# #) + wordLog2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + wordLogBase# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + wordReverseBits# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + wordReverseBits32# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + wordReverseBytes# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + wordSizeInBase# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# + wordToAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordToAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordToAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordToMutableByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordToMutableByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordToMutableByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + wordWriteAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + wordWriteAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + wordWriteMutableByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + wordWriteMutableByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + (||#) :: Bool# -> Bool# -> Bool# + +module GHC.Num.WordArray where + -- Safety: None + type role MutableWordArray nominal + type MutableWordArray :: * -> * + data MutableWordArray s = MutableWordArray (MutableWordArray# s) + type MutableWordArray# :: * -> GHC.Internal.Types.UnliftedType + type MutableWordArray# = GHC.Internal.Prim.MutableByteArray# + type WordArray :: * + data WordArray = WordArray WordArray# + type WordArray# :: GHC.Internal.Types.UnliftedType + type WordArray# = GHC.Internal.Prim.ByteArray# + bytesToWords# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + mwaAddInplaceArray :: forall d. MutableWordArray# d -> GHC.Internal.Prim.Int# -> WordArray# -> GHC.Internal.Prim.State# d -> GHC.Internal.Prim.State# d + mwaAddInplaceWord# :: forall d. MutableWordArray# d -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# d -> GHC.Internal.Prim.State# d + mwaArrayCopy# :: forall s. GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Int# -> WordArray# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaClz :: forall s. MutableWordArray# s -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Int# #) + mwaClzAt :: forall s. MutableWordArray# s -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Int# #) + mwaFill# :: forall s. MutableWordArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaInitArrayBinOp :: forall s. MutableWordArray# s -> WordArray# -> WordArray# -> (GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#) -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaInitArrayPlusWord :: forall s. MutableWordArray# s -> WordArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaInitCopyShrink# :: forall s. GHC.Internal.Prim.MutableByteArray# s -> WordArray# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaRead# :: forall s. MutableWordArray# s -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + mwaReadOrZero :: forall s. MutableWordArray# s -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) + mwaSetSize# :: forall s. GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaShrink# :: forall s. GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaSize# :: forall s. MutableWordArray# s -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Int# #) + mwaSubInplaceArray :: forall d. MutableWordArray# d -> GHC.Internal.Prim.Int# -> WordArray# -> GHC.Internal.Prim.State# d -> (# GHC.Internal.Prim.State# d, GHC.Internal.Bignum.Primitives.Bool# #) + mwaSubInplaceArrayTrim :: forall d. MutableWordArray# d -> GHC.Internal.Prim.Int# -> WordArray# -> GHC.Internal.Prim.State# d -> GHC.Internal.Prim.State# d + mwaSubInplaceMutableArray :: forall d. MutableWordArray# d -> GHC.Internal.Prim.Int# -> MutableWordArray# d -> GHC.Internal.Prim.State# d -> (# GHC.Internal.Prim.State# d, GHC.Internal.Bignum.Primitives.Bool# #) + mwaSubInplaceWord# :: forall d. MutableWordArray# d -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# d -> (# GHC.Internal.Prim.State# d, GHC.Internal.Bignum.Primitives.Bool# #) + mwaTrimCompare :: forall s. GHC.Internal.Prim.Int# -> MutableWordArray# s -> WordArray# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Types.Ordering #) + mwaTrimZeroes# :: forall s. GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaWrite# :: forall s. MutableWordArray# s -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaWriteMostSignificant :: forall s. MutableWordArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + mwaWriteOrShrink :: forall s. MutableWordArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.State# s -> GHC.Internal.Prim.State# s + newWordArray# :: forall s. GHC.Internal.Prim.Int# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, MutableWordArray# s #) + waClzAt :: WordArray# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + withNewWordArray# :: GHC.Internal.Prim.Int# -> (MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld) -> WordArray# + withNewWordArray2# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> (MutableWordArray# GHC.Internal.Prim.RealWorld -> MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld) -> (# WordArray#, WordArray# #) + withNewWordArray2Trimmed# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> (MutableWordArray# GHC.Internal.Prim.RealWorld -> MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld) -> (# WordArray#, WordArray# #) + withNewWordArrayTrimmed# :: GHC.Internal.Prim.Int# -> (MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld) -> WordArray# + withNewWordArrayTrimmedMaybe# :: GHC.Internal.Prim.Int# -> (MutableWordArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld, GHC.Internal.Bignum.Primitives.Bool# #)) -> (# (# #) | WordArray# #) + wordArrayCompareMSWords :: WordArray# -> WordArray# -> GHC.Internal.Types.Ordering + wordArrayFromWord# :: GHC.Internal.Prim.Word# -> WordArray# + wordArrayFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> WordArray# + wordArrayLast# :: WordArray# -> GHC.Internal.Prim.Word# + wordArraySize# :: WordArray# -> GHC.Internal.Prim.Int# + wordsToBytes# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# + + +-- Instances: +instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in ‘GHC.Internal.Bignum.BigNat’ +instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Integer.Integer -- Defined in ‘GHC.Internal.Bignum.Integer’ +instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’ +instance GHC.Internal.Classes.Ord GHC.Internal.Bignum.BigNat.BigNat -- Defined in ‘GHC.Internal.Bignum.BigNat’ +instance GHC.Internal.Classes.Ord GHC.Internal.Bignum.Integer.Integer -- Defined in ‘GHC.Internal.Bignum.Integer’ +instance GHC.Internal.Classes.Ord GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’ ===================================== utils/dump-decls/Main.hs ===================================== @@ -77,6 +77,8 @@ ignoredModules = platformDependentModules = [ "System.Posix.Types" , "Foreign.C.Types" + , "GHC.Num.Backend" + , "GHC.Num.Backend.Selected" ] ignoredOccNames :: [OccName] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/100c39f685427470a5f4910f0f8c73a5988bab96...95c7cd9e303267d1d932c74f064df20a7f50821a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/100c39f685427470a5f4910f0f8c73a5988bab96...95c7cd9e303267d1d932c74f064df20a7f50821a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250315/5d935386/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 12:21:00 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Mar 2025 08:21:00 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: cpuinfo Zvl* extensions Message-ID: <67d6c22c92c5d_1cef2e625dcc838bf@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: 6d1ff74f by Sven Tennie at 2025-03-16T13:20:52+01:00 WIP: cpuinfo Zvl* extensions - - - - - 1 changed file: - testsuite/driver/cpuinfo.py Changes: ===================================== testsuite/driver/cpuinfo.py ===================================== @@ -2129,7 +2129,28 @@ def _get_cpu_info_from_riscv_isa(): Returns the CPU info gathered from 'cat /proc/device-tree/cpus/cpu at 0/riscv,isa' Returns {} if this file does not exist (i.e. we're not on RISC-V Linux) ''' - g_trace.header('Tying to get info from lsprop ...') + + def remove_prefix(prefix, text): + if text.startswith(prefix): + return text[len(prefix):] + return text + + def run_asm(*machine_code): + asm = ASM(ctypes.c_uint32, (), machine_code) + asm.compile() + retval = asm.run() + asm.free() + return retval + + def unique_items(original_list): + unique_list = [] + seen = set() + for item in original_list: + if item not in seen: + unique_list.append(item) + seen.add(item) + + g_trace.header('Tying to get info from device-tree ...') try: returncode, output = DataSource.riscv_isa() @@ -2137,8 +2158,49 @@ def _get_cpu_info_from_riscv_isa(): g_trace.fail('Failed to cat /proc/device-tree/cpus/cpu at 0/riscv,isa. Skipping ...') return {} + flags = output.split('_') + + # The usage of the Zvl* extensions in the industry is very + # inconsistent. Though, they are useful to communicate the VLEN. So, if + # they are not provided by the system, we try to figure them out on our + # own. + + # E.g. rv64imafdcvh + arch_string = flags[0] + profile_features = remove_prefix('rv64', remove_prefix('rv32', arch_string)) + additional_flags = [] + if profile_features.contains('v') and not output.contains('_zvl'): + g_trace.header('Figure out VLEN and Zvl* extensions ...') + + vlen = 0 + + if arch_string.startswith('rv32'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x00\x80\x67" # ret + ) + elif arch_string.startswith('rv64'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x05\x05\x1b", # sext.w a0, a0 + b"\x00\x00\x80\x67" # ret + ) + + if vlen >= 32: + additional_flags.append('zvl32b') + if vlen >= 64: + additional_flags.append('zvl64b') + if vlen >= 128: + additional_flags.append('zvl128b') + if vlen >= 256: + additional_flags.append('zvl256b') + if vlen >= 512: + additional_flags.append('zvl512b') + if vlen >= 1024: + additional_flags.append('zvl1024b') + info = { - 'flags' : output.split('_') + 'flags' : unique_items(flags.append(additional_flags)) } info = _filter_dict_keys_with_empty_values(info) g_trace.success() View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d1ff74f191e388b95dfe6878b0019186ad4d2eb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d1ff74f191e388b95dfe6878b0019186ad4d2eb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/cfe090c1/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 12:28:01 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Mar 2025 08:28:01 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: cpuinfo Zvl* extensions Message-ID: <67d6c3d1de23c_1cef2e7f93b0842e7@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: b35680f1 by Sven Tennie at 2025-03-16T13:27:52+01:00 WIP: cpuinfo Zvl* extensions - - - - - 1 changed file: - testsuite/driver/cpuinfo.py Changes: ===================================== testsuite/driver/cpuinfo.py ===================================== @@ -277,7 +277,7 @@ class DataSource: @staticmethod def riscv_isa(): - # Expect all cores to support an equal ISA. + # Expect all cores to support an equal ISA. riscv_isa = '/proc/device-tree/cpus/cpu at 0/riscv,isa' return _run_and_get_stdout(['cat', riscv_isa]) @@ -2129,7 +2129,28 @@ def _get_cpu_info_from_riscv_isa(): Returns the CPU info gathered from 'cat /proc/device-tree/cpus/cpu at 0/riscv,isa' Returns {} if this file does not exist (i.e. we're not on RISC-V Linux) ''' - g_trace.header('Tying to get info from lsprop ...') + + def remove_prefix(prefix, text): + if text.startswith(prefix): + return text[len(prefix):] + return text + + def run_asm(*machine_code): + asm = ASM(ctypes.c_uint32, (), machine_code) + asm.compile() + retval = asm.run() + asm.free() + return retval + + def unique_items(original_list): + unique_list = [] + seen = set() + for item in original_list: + if item not in seen: + unique_list.append(item) + seen.add(item) + + g_trace.header('Tying to get info from device-tree ...') try: returncode, output = DataSource.riscv_isa() @@ -2137,8 +2158,49 @@ def _get_cpu_info_from_riscv_isa(): g_trace.fail('Failed to cat /proc/device-tree/cpus/cpu at 0/riscv,isa. Skipping ...') return {} + flags = output.split('_') + + # The usage of the Zvl* extensions in the industry is very + # inconsistent. Though, they are useful to communicate the VLEN. So, if + # they are not provided by the system, we try to figure them out on our + # own. + + # E.g. rv64imafdcvh + arch_string = flags[0] + profile_features = remove_prefix('rv64', remove_prefix('rv32', arch_string)) + additional_flags = [] + if profile_features.contains('v') and not output.contains('_zvl'): + g_trace.header('Figure out VLEN and Zvl* extensions ...') + + vlen = 0 + + if arch_string.startswith('rv32'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x00\x80\x67" # ret + ) + elif arch_string.startswith('rv64'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x05\x05\x1b", # sext.w a0, a0 + b"\x00\x00\x80\x67" # ret + ) + + if vlen >= 32: + additional_flags.append('zvl32b') + if vlen >= 64: + additional_flags.append('zvl64b') + if vlen >= 128: + additional_flags.append('zvl128b') + if vlen >= 256: + additional_flags.append('zvl256b') + if vlen >= 512: + additional_flags.append('zvl512b') + if vlen >= 1024: + additional_flags.append('zvl1024b') + info = { - 'flags' : output.split('_') + 'flags' : unique_items(flags.append(additional_flags)) } info = _filter_dict_keys_with_empty_values(info) g_trace.success() View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b35680f169a6a5fa8586338af2253262a2d68218 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b35680f169a6a5fa8586338af2253262a2d68218 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/62c11d35/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 12:32:31 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Mar 2025 08:32:31 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: cpuinfo Zvl* extensions Message-ID: <67d6c4df6ac3c_1cef2e93dce484676@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: 74169e80 by Sven Tennie at 2025-03-16T13:32:24+01:00 WIP: cpuinfo Zvl* extensions - - - - - 1 changed file: - testsuite/driver/cpuinfo.py Changes: ===================================== testsuite/driver/cpuinfo.py ===================================== @@ -277,7 +277,7 @@ class DataSource: @staticmethod def riscv_isa(): - # Expect all cores to support an equal ISA. + # Expect all cores to support an equal ISA. riscv_isa = '/proc/device-tree/cpus/cpu at 0/riscv,isa' return _run_and_get_stdout(['cat', riscv_isa]) @@ -2129,7 +2129,28 @@ def _get_cpu_info_from_riscv_isa(): Returns the CPU info gathered from 'cat /proc/device-tree/cpus/cpu at 0/riscv,isa' Returns {} if this file does not exist (i.e. we're not on RISC-V Linux) ''' - g_trace.header('Tying to get info from lsprop ...') + + def remove_prefix(prefix, text): + if text.startswith(prefix): + return text[len(prefix):] + return text + + def run_asm(*machine_code): + asm = ASM(ctypes.c_uint32, (), machine_code) + asm.compile() + retval = asm.run() + asm.free() + return retval + + def unique_items(original_list): + unique_list = [] + seen = set() + for item in original_list: + if item not in seen: + unique_list.append(item) + seen.add(item) + + g_trace.header('Tying to get info from device-tree ...') try: returncode, output = DataSource.riscv_isa() @@ -2137,8 +2158,49 @@ def _get_cpu_info_from_riscv_isa(): g_trace.fail('Failed to cat /proc/device-tree/cpus/cpu at 0/riscv,isa. Skipping ...') return {} + flags = output.split('_') + + # The usage of the Zvl* extensions in the industry is very + # inconsistent. Though, they are useful to communicate the VLEN. So, if + # they are not provided by the system, we try to figure them out on our + # own. + + # E.g. rv64imafdcvh + arch_string = flags[0] + profile_features = remove_prefix('rv64', remove_prefix('rv32', arch_string)) + additional_flags = [] + if 'v' profile_features and not '_zvl' in output: + g_trace.header('Figure out VLEN and Zvl* extensions ...') + + vlen = 0 + + if arch_string.startswith('rv32'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x00\x80\x67" # ret + ) + elif arch_string.startswith('rv64'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x05\x05\x1b", # sext.w a0, a0 + b"\x00\x00\x80\x67" # ret + ) + + if vlen >= 32: + additional_flags.append('zvl32b') + if vlen >= 64: + additional_flags.append('zvl64b') + if vlen >= 128: + additional_flags.append('zvl128b') + if vlen >= 256: + additional_flags.append('zvl256b') + if vlen >= 512: + additional_flags.append('zvl512b') + if vlen >= 1024: + additional_flags.append('zvl1024b') + info = { - 'flags' : output.split('_') + 'flags' : unique_items(flags.append(additional_flags)) } info = _filter_dict_keys_with_empty_values(info) g_trace.success() View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/74169e800547f6e9875f51f6e4e5c77cd901241a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/74169e800547f6e9875f51f6e4e5c77cd901241a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/6463f608/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 12:33:42 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Mar 2025 08:33:42 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: cpuinfo Zvl* extensions Message-ID: <67d6c526b101b_1cef2e93dcbc85049@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: 1a5d8cd9 by Sven Tennie at 2025-03-16T13:33:34+01:00 WIP: cpuinfo Zvl* extensions - - - - - 1 changed file: - testsuite/driver/cpuinfo.py Changes: ===================================== testsuite/driver/cpuinfo.py ===================================== @@ -277,7 +277,7 @@ class DataSource: @staticmethod def riscv_isa(): - # Expect all cores to support an equal ISA. + # Expect all cores to support an equal ISA. riscv_isa = '/proc/device-tree/cpus/cpu at 0/riscv,isa' return _run_and_get_stdout(['cat', riscv_isa]) @@ -2129,7 +2129,28 @@ def _get_cpu_info_from_riscv_isa(): Returns the CPU info gathered from 'cat /proc/device-tree/cpus/cpu at 0/riscv,isa' Returns {} if this file does not exist (i.e. we're not on RISC-V Linux) ''' - g_trace.header('Tying to get info from lsprop ...') + + def remove_prefix(prefix, text): + if text.startswith(prefix): + return text[len(prefix):] + return text + + def run_asm(*machine_code): + asm = ASM(ctypes.c_uint32, (), machine_code) + asm.compile() + retval = asm.run() + asm.free() + return retval + + def unique_items(original_list): + unique_list = [] + seen = set() + for item in original_list: + if item not in seen: + unique_list.append(item) + seen.add(item) + + g_trace.header('Tying to get info from device-tree ...') try: returncode, output = DataSource.riscv_isa() @@ -2137,8 +2158,49 @@ def _get_cpu_info_from_riscv_isa(): g_trace.fail('Failed to cat /proc/device-tree/cpus/cpu at 0/riscv,isa. Skipping ...') return {} + flags = output.split('_') + + # The usage of the Zvl* extensions in the industry is very + # inconsistent. Though, they are useful to communicate the VLEN. So, if + # they are not provided by the system, we try to figure them out on our + # own. + + # E.g. rv64imafdcvh + arch_string = flags[0] + profile_features = remove_prefix('rv64', remove_prefix('rv32', arch_string)) + additional_flags = [] + if 'v' in profile_features and not '_zvl' in output: + g_trace.header('Figure out VLEN and Zvl* extensions ...') + + vlen = 0 + + if arch_string.startswith('rv32'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x00\x80\x67" # ret + ) + elif arch_string.startswith('rv64'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x05\x05\x1b", # sext.w a0, a0 + b"\x00\x00\x80\x67" # ret + ) + + if vlen >= 32: + additional_flags.append('zvl32b') + if vlen >= 64: + additional_flags.append('zvl64b') + if vlen >= 128: + additional_flags.append('zvl128b') + if vlen >= 256: + additional_flags.append('zvl256b') + if vlen >= 512: + additional_flags.append('zvl512b') + if vlen >= 1024: + additional_flags.append('zvl1024b') + info = { - 'flags' : output.split('_') + 'flags' : unique_items(flags.append(additional_flags)) } info = _filter_dict_keys_with_empty_values(info) g_trace.success() View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1a5d8cd9311b1ae52801c23c802489e95c4124bb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1a5d8cd9311b1ae52801c23c802489e95c4124bb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/874c8a26/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 12:41:58 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Mar 2025 08:41:58 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: cpuinfo Zvl* extensions Message-ID: <67d6c7168008c_1eeae3c5e2c8733f@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: 929d1508 by Sven Tennie at 2025-03-16T13:41:48+01:00 WIP: cpuinfo Zvl* extensions - - - - - 1 changed file: - testsuite/driver/cpuinfo.py Changes: ===================================== testsuite/driver/cpuinfo.py ===================================== @@ -277,7 +277,7 @@ class DataSource: @staticmethod def riscv_isa(): - # Expect all cores to support an equal ISA. + # Expect all cores to support an equal ISA. riscv_isa = '/proc/device-tree/cpus/cpu at 0/riscv,isa' return _run_and_get_stdout(['cat', riscv_isa]) @@ -2129,7 +2129,28 @@ def _get_cpu_info_from_riscv_isa(): Returns the CPU info gathered from 'cat /proc/device-tree/cpus/cpu at 0/riscv,isa' Returns {} if this file does not exist (i.e. we're not on RISC-V Linux) ''' - g_trace.header('Tying to get info from lsprop ...') + + def remove_prefix(prefix, text): + if text.startswith(prefix): + return text[len(prefix):] + return text + + def run_asm(*machine_code): + asm = ASM(ctypes.c_uint32, (), machine_code) + asm.compile() + retval = asm.run() + asm.free() + return retval + + def unique_items(original_list): + unique_list = [] + seen = set() + for item in original_list: + if item not in seen: + unique_list.append(item) + seen.add(item) + + g_trace.header('Tying to get info from device-tree ...') try: returncode, output = DataSource.riscv_isa() @@ -2137,8 +2158,50 @@ def _get_cpu_info_from_riscv_isa(): g_trace.fail('Failed to cat /proc/device-tree/cpus/cpu at 0/riscv,isa. Skipping ...') return {} + flags = output.split('_') + + # The usage of the Zvl* extensions in the industry is very + # inconsistent. Though, they are useful to communicate the VLEN. So, if + # they are not provided by the system, we try to figure them out on our + # own. + + # E.g. rv64imafdcvh + arch_string = flags[0] + profile_features = remove_prefix('rv64', remove_prefix('rv32', arch_string)) + additional_flags = [] + if 'v' in profile_features and not '_zvl' in output: + g_trace.command_output('Figure out VLEN and Zvl* extensions ...') + + vlen = 0 + + if arch_string.startswith('rv32'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x00\x80\x67" # ret + ) + elif arch_string.startswith('rv64'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x05\x05\x1b", # sext.w a0, a0 + b"\x00\x00\x80\x67" # ret + ) + + if vlen >= 32: + additional_flags.append('zvl32b') + if vlen >= 64: + additional_flags.append('zvl64b') + if vlen >= 128: + additional_flags.append('zvl128b') + if vlen >= 256: + additional_flags.append('zvl256b') + if vlen >= 512: + additional_flags.append('zvl512b') + if vlen >= 1024: + additional_flags.append('zvl1024b') + + flags.append(additional_flags) info = { - 'flags' : output.split('_') + 'flags' : unique_items(flags) } info = _filter_dict_keys_with_empty_values(info) g_trace.success() View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/929d150855080c21bcbf28e6a57029a0a4ac8d84 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/929d150855080c21bcbf28e6a57029a0a4ac8d84 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/08b4a744/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 12:47:01 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Mar 2025 08:47:01 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: cpuinfo Zvl* extensions Message-ID: <67d6c845733e9_1eeae31dd210877fb@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: ca1dfbba by Sven Tennie at 2025-03-16T13:46:52+01:00 WIP: cpuinfo Zvl* extensions - - - - - 1 changed file: - testsuite/driver/cpuinfo.py Changes: ===================================== testsuite/driver/cpuinfo.py ===================================== @@ -277,7 +277,7 @@ class DataSource: @staticmethod def riscv_isa(): - # Expect all cores to support an equal ISA. + # Expect all cores to support an equal ISA. riscv_isa = '/proc/device-tree/cpus/cpu at 0/riscv,isa' return _run_and_get_stdout(['cat', riscv_isa]) @@ -2129,7 +2129,29 @@ def _get_cpu_info_from_riscv_isa(): Returns the CPU info gathered from 'cat /proc/device-tree/cpus/cpu at 0/riscv,isa' Returns {} if this file does not exist (i.e. we're not on RISC-V Linux) ''' - g_trace.header('Tying to get info from lsprop ...') + + def remove_prefix(prefix, text): + if text.startswith(prefix): + return text[len(prefix):] + return text + + def run_asm(*machine_code): + asm = ASM(ctypes.c_uint32, (), machine_code) + asm.compile() + retval = asm.run() + asm.free() + return retval + + def unique_items(original_list): + unique_list = [] + seen = set() + for item in original_list: + if item not in seen: + unique_list.append(item) + seen.add(item) + return unique_list + + g_trace.header('Tying to get info from device-tree ...') try: returncode, output = DataSource.riscv_isa() @@ -2137,8 +2159,50 @@ def _get_cpu_info_from_riscv_isa(): g_trace.fail('Failed to cat /proc/device-tree/cpus/cpu at 0/riscv,isa. Skipping ...') return {} + flags = output.split('_') + + # The usage of the Zvl* extensions in the industry is very + # inconsistent. Though, they are useful to communicate the VLEN. So, if + # they are not provided by the system, we try to figure them out on our + # own. + + # E.g. rv64imafdcvh + arch_string = flags[0] + profile_features = remove_prefix('rv64', remove_prefix('rv32', arch_string)) + additional_flags = [] + if 'v' in profile_features and not '_zvl' in output: + g_trace.command_output('Figure out VLEN and Zvl* extensions ...') + + vlen = 0 + + if arch_string.startswith('rv32'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x00\x80\x67" # ret + ) + elif arch_string.startswith('rv64'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x05\x05\x1b", # sext.w a0, a0 + b"\x00\x00\x80\x67" # ret + ) + + if vlen >= 32: + additional_flags.append('zvl32b') + if vlen >= 64: + additional_flags.append('zvl64b') + if vlen >= 128: + additional_flags.append('zvl128b') + if vlen >= 256: + additional_flags.append('zvl256b') + if vlen >= 512: + additional_flags.append('zvl512b') + if vlen >= 1024: + additional_flags.append('zvl1024b') + + flags.extend(additional_flags) info = { - 'flags' : output.split('_') + 'flags' : unique_items(flags) } info = _filter_dict_keys_with_empty_values(info) g_trace.success() View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ca1dfbbabbd9a79fe73487a2cfeeff1769334d08 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ca1dfbbabbd9a79fe73487a2cfeeff1769334d08 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/784626e3/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 13:11:55 2025 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Mar 2025 09:11:55 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: cpuinfo Zvl* extensions Message-ID: <67d6ce1b2263a_1eeae34782e089454@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC Commits: ee6ccb02 by Sven Tennie at 2025-03-16T14:11:46+01:00 WIP: cpuinfo Zvl* extensions - - - - - 1 changed file: - testsuite/driver/cpuinfo.py Changes: ===================================== testsuite/driver/cpuinfo.py ===================================== @@ -277,7 +277,7 @@ class DataSource: @staticmethod def riscv_isa(): - # Expect all cores to support an equal ISA. + # Expect all cores to support an equal ISA. riscv_isa = '/proc/device-tree/cpus/cpu at 0/riscv,isa' return _run_and_get_stdout(['cat', riscv_isa]) @@ -2129,7 +2129,29 @@ def _get_cpu_info_from_riscv_isa(): Returns the CPU info gathered from 'cat /proc/device-tree/cpus/cpu at 0/riscv,isa' Returns {} if this file does not exist (i.e. we're not on RISC-V Linux) ''' - g_trace.header('Tying to get info from lsprop ...') + + def remove_prefix(prefix, text): + if text.startswith(prefix): + return text[len(prefix):] + return text + + def run_asm(*machine_code): + asm = ASM(ctypes.c_uint32, (), machine_code) + asm.compile() + retval = asm.run() + asm.free() + return retval + + def unique_items(original_list): + unique_list = [] + seen = set() + for item in original_list: + if item not in seen: + unique_list.append(item) + seen.add(item) + return unique_list + + g_trace.header('Tying to get info from device-tree ...') try: returncode, output = DataSource.riscv_isa() @@ -2137,8 +2159,48 @@ def _get_cpu_info_from_riscv_isa(): g_trace.fail('Failed to cat /proc/device-tree/cpus/cpu at 0/riscv,isa. Skipping ...') return {} + flags = output.split('_') + + # The usage of the Zvl* extensions in the industry is very + # inconsistent. Though, they are useful to communicate the VLEN. So, if + # they are not provided by the system, we try to figure them out on our + # own. + + # E.g. rv64imafdcvh + arch_string = flags[0] + profile_features = remove_prefix('rv64', remove_prefix('rv32', arch_string)) + additional_flags = [] + if 'v' in profile_features and not '_zvl' in output: + vlen = 0 + + if arch_string.startswith('rv32'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x00\x80\x67" # ret + ) + elif arch_string.startswith('rv64'): + vlen = run_asm( + b"\xc2\x20\x25\x73", # csrr a0, 0xc22 + b"\x00\x05\x05\x1b", # sext.w a0, a0 + b"\x00\x00\x80\x67" # ret + ) + + if vlen >= 32: + additional_flags.append('zvl32b') + if vlen >= 64: + additional_flags.append('zvl64b') + if vlen >= 128: + additional_flags.append('zvl128b') + if vlen >= 256: + additional_flags.append('zvl256b') + if vlen >= 512: + additional_flags.append('zvl512b') + if vlen >= 1024: + additional_flags.append('zvl1024b') + + flags.extend(additional_flags) info = { - 'flags' : output.split('_') + 'flags' : unique_items(flags) } info = _filter_dict_keys_with_empty_values(info) g_trace.success() View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ee6ccb0244bc4a9c33fbdd55a4e4efbd1070360c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ee6ccb0244bc4a9c33fbdd55a4e4efbd1070360c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/b67c8f45/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 13:58:53 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 16 Mar 2025 09:58:53 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] 8 commits: iface: Store logical parts of ModIface together Message-ID: <67d6d91d7801d_1eeae3b37d1093060@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: b15fca2b by Matthew Pickering at 2025-03-15T05:36:40-04:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore ------------------------- - - - - - c758cb71 by Ben Gamari at 2025-03-15T05:37:17-04:00 configure: Fix incorrect SettingsLlvmAsFlags value Previously this was set to `LlvmAsCmd` rather than `LlvmAsFlags`, resulting in #25856. - - - - - ce533b94 by Cheng Shao at 2025-03-16T13:39:03+00:00 rts: add hs_try_putmvar_with_value to RTS API This commit adds hs_try_putmvar_with_value to rts. It allows more flexibility than hs_try_putmvar by taking an additional value argument as a closure to be put into the MVar. This function is used & tested by the wasm backend runtime, though it makes sense to expose it as a public facing RTS API function as well. - - - - - c2acab3e by Cheng Shao at 2025-03-16T13:42:05+00:00 wasm: use MVar as JSFFI import blocking mechanism Previously, when blocking on a JSFFI import, we push a custom stg_jsffi_block stack frame and arrange the `promise.then` callback to write to that stack frame. It turns out we can simply use the good old MVar to implement the blocking logic, with a few benefits: - Less maintenance burden. We can drop the stg_jsffi_block related Cmm code without loss of functionality. - It interacts better with existing async exception mechanism. throwTo would properly block the caller if the target thread is masking async exceptions. - - - - - 88fee776 by Cheng Shao at 2025-03-16T13:49:17+00:00 wasm: properly pin the raiseJSException closure We used to use keepAlive# to pin the raiseJSException closure when blocking on a JSFFI import thunk, since it can potentially be used by RTS. But raiseJSException may be used in other places as well (e.g. the promise.throwTo logic), and it's better to simply unconditionally pin it in the JSFFI initialization logic. - - - - - ca21de13 by Cheng Shao at 2025-03-16T13:52:36+00:00 wasm: implement promise.throwTo() for async JSFFI exports This commit implements promise.throwTo() for wasm backend JSFFI exports. This allows the JavaScript side to interrupt Haskell computation by raising an async exception. See subsequent docs/test commits for more details. - - - - - f01ca1c1 by Cheng Shao at 2025-03-16T13:55:05+00:00 testsuite: add test for wasm promise.throwTo() logic This commit adds a test case to test the wasm backend promise.throwTo() logic. - - - - - c0e17bd4 by Cheng Shao at 2025-03-16T13:56:33+00:00 docs: document the wasm backend promise.throwTo() feature - - - - - 33 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - docs/users_guide/exts/ffi.rst - docs/users_guide/wasm.rst - ghc/Main.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - m4/fp_settings.m4 - rts/RtsAPI.c - rts/RtsSymbols.c - rts/include/HsFFI.h - rts/wasm/JSFFI.c - rts/wasm/blocker.cmm - rts/wasm/scheduler.cmm - testsuite/tests/jsffi/all.T - + testsuite/tests/jsffi/cancel.hs - + testsuite/tests/jsffi/cancel.mjs - + testsuite/tests/jsffi/cancel.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a01000cc2d785627f3e98d561e28ba35de202ea6...c0e17bd4af6f2ecfe9ed721886b290780b93b6f8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a01000cc2d785627f3e98d561e28ba35de202ea6...c0e17bd4af6f2ecfe9ed721886b290780b93b6f8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/679793d7/attachment.html> From gitlab at gitlab.haskell.org Sun Mar 16 14:40:38 2025 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Sun, 16 Mar 2025 10:40:38 -0400 Subject: [Git][ghc/ghc][wip/az/ghc-cpp] 2 commits: Working on getting check-exact to work properly Message-ID: <67d6e2e62cce3_213b4a2f821c3321@gitlab.mail> Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC Commits: 7c43e50c by Alan Zimmerman at 2025-03-16T13:04:52+00:00 Working on getting check-exact to work properly - - - - - 90e47997 by Alan Zimmerman at 2025-03-16T14:40:15+00:00 Passes CppCommentPlacement test - - - - - 6 changed files: - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PreProcess.hs - + testsuite/tests/printer/CppCommentPlacement.hs - utils/check-cpp/PreProcess.hs - utils/check-exact/Main.hs - utils/check-exact/Preprocess.hs Changes: ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -1006,7 +1006,7 @@ data Token | ITblockComment String PsSpan -- ^ comment in {- -} -- GHC CPP extension. See Note [GhcCPP Token] - | ITcpp Bool FastString -- ^ CPP #-prefixed line, or continuation. + | ITcpp Bool FastString PsSpan -- ^ CPP #-prefixed line, or continuation. deriving Show instance Outputable Token where @@ -1262,6 +1262,7 @@ cppTokenCont = doCppToken Nothing doCppToken :: (Maybe Int) -> Action p doCppToken code span buf len _buf2 = do + lt <- getLastLocIncludingComments let pushLexStateMaybe Nothing = return () pushLexStateMaybe (Just code) = pushLexState code @@ -1275,7 +1276,8 @@ doCppToken code span buf len _buf2 = ('\n':_) -> return (len - 1, False) _ -> return (len, False) let span' = cppSpan span len0 - return (L span' (ITcpp continue $! lexemeToFastString buf len0)) + let !s = lexemeToFastString buf len0 + return (L span' (ITcpp continue s lt)) -- cppToken :: Int -> Action p @@ -1313,10 +1315,12 @@ cppSpan span len = mkPsSpan start_loc end_loc BufPos sb = psBufPos start_loc end_loc = PsLoc real_loc (BufPos (sb + len + 1)) -cppTokenPop :: (FastString -> Token)-> Action p +cppTokenPop :: (FastString -> PsSpan -> Token)-> Action p cppTokenPop t span buf len _buf2 = do _ <- popLexState - return (L span (t $! lexemeToFastString buf len)) + lt <- getLastLocIncludingComments + let !s = lexemeToFastString buf len + return (L span (t s lt)) -- See Note [Nested comment line pragmas] failLinePrag1 :: Action p @@ -3821,6 +3825,7 @@ commentToAnnotation (L l (ITdocComment s ll)) = mkLEpaComment l ll (EpaDocComm commentToAnnotation (L l (ITdocOptions s ll)) = mkLEpaComment l ll (EpaDocOptions s) commentToAnnotation (L l (ITlineComment s ll)) = mkLEpaComment l ll (EpaLineComment s) commentToAnnotation (L l (ITblockComment s ll)) = mkLEpaComment l ll (EpaBlockComment s) +commentToAnnotation (L l (ITcpp _ s ll)) = mkLEpaComment l ll (EpaLineComment (unpackFS s)) commentToAnnotation _ = panic "commentToAnnotation" -- see Note [PsSpan in Comments] ===================================== compiler/GHC/Parser/PreProcess.hs ===================================== @@ -201,7 +201,7 @@ ppLexer queueComments cont = Just inp -> do Lexer.setInput inp ppLexer queueComments cont - L l (ITcpp continuation s) -> do + L l (ITcpp continuation s sp) -> do ghcpp <- ghcCppEnabled -- Only process the directive if GhcCpp is explicitly enabled. -- Otherwise we are scanning for pragmas @@ -216,7 +216,7 @@ ppLexer queueComments cont = case mdump of Just dump -> -- We have a dump of the state, put it into an ignored token - contIgnoreTok (L l (ITcpp continuation (appendFS s (fsLit dump)))) + contIgnoreTok (L l (ITcpp continuation (appendFS s (fsLit dump)) sp)) Nothing -> contIgnoreTok tk else contInner tk _ -> do @@ -232,7 +232,7 @@ ppLexer queueComments cont = processCppToks :: FastString -> PP (Maybe String) processCppToks fs = do let - get (L _ (ITcpp _ s)) = s + get (L _ (ITcpp _ s _)) = s get _ = error "should not" -- Combine any prior continuation tokens cs <- popContinuation ===================================== testsuite/tests/printer/CppCommentPlacement.hs ===================================== @@ -0,0 +1,26 @@ +-- | Top comment + +{-# LANGUAGE CPP #-} +module CppCommentPlacement where + +#ifndef CONDITION + +--8----------------------------------------------------------------------------- +-- * comment1 + +fn :: Integer +fn = 1 + +--14---------------------------------------------------------------------------- + +#else + +--18---------------------------------------------------------------------------- +-- * comment2 + +fn :: Integer +fn = 2 + +#endif + +--26---------------------------------------------------------------------------- ===================================== utils/check-cpp/PreProcess.hs ===================================== @@ -49,6 +49,8 @@ dumpGhcCpp dflags pst = output ++ sepa ++ show bare_toks ++ sepa + ++ show lll + ++ sepa -- ++ show all_toks ++ sepa -- Note: pst is the state /before/ the parser runs, so we can use it to lex. (pst_final, bare_toks) = lexAll pst @@ -67,6 +69,9 @@ dumpGhcCpp dflags pst = output toks = addSourceToTokens startLoc buf1 all_toks final = renderCombinedToks toks + lll = case Lexer.lexTokenStream () (options pst) (buffer pst) startLoc of + POk _ x -> x + _ -> error $ "wtf" cmpBs :: Located Token -> Located Token -> Ordering cmpBs (L (RealSrcSpan _ (Strict.Just bs1)) _) (L (RealSrcSpan _ (Strict.Just bs2)) _) = @@ -158,8 +163,9 @@ showDefines defines = Map.foldlWithKey' (\acc k d -> acc ++ "\n" ++ renderDefine "#define " ++ n ++ "(" ++ (intercalate "," args) ++ ") " ++ (intercalate " " (map PM.t_str rhs)) lexAll :: Lexer.PState PpState -> (Lexer.PState PpState, [Located Token]) --- lexAll state = case unP (lexer True return) state of -lexAll state = case unP (lexerDbg True return) state of +lexAll state = case unP (lexer True return) state of +-- lexAll state = case unP (lexerDbg True return) state of +-- lexAll state = case unP (Lexer.lexerDbg True return) state of POk s t@(L _ ITeof) -> (s, [t]) -- POk state' t -> (ss, t : rest) POk state' t -> (ss, trace ("lexAll:" ++ show t) t : rest) ===================================== utils/check-exact/Main.hs ===================================== @@ -218,7 +218,8 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/worktree/bisect/_b -- "../../testsuite/tests/printer/Test22771.hs" Nothing -- "../../testsuite/tests/printer/Test23465.hs" Nothing -- "../../testsuite/tests/printer/Test25454.hs" Nothing - "../../testsuite/tests/printer/Test25467.hs" Nothing + -- "../../testsuite/tests/printer/Test25467.hs" Nothing + "../../testsuite/tests/printer/CppCommentPlacement.hs" Nothing -- cloneT does not need a test, function can be retired ===================================== utils/check-exact/Preprocess.hs ===================================== @@ -44,10 +44,6 @@ import Utils import qualified Data.Set as Set import qualified GHC.Data.Strict as Strict - --- import Debug.Trace --- - -- --------------------------------------------------------------------- data CppOptions = CppOptions @@ -106,9 +102,10 @@ getCppTokensAsComments cppOptions sourceFile = do source <- GHC.liftIO $ GHC.hGetStringBuffer sourceFile let startLoc = GHC.mkRealSrcLoc (GHC.mkFastString sourceFile) 1 1 (_txt,strSrcBuf,flags2') <- getPreprocessedSrcDirectPrim cppOptions sourceFile + let flags2 = GHC.initParserOpts flags2' -- hash-ifdef tokens - directiveToks <- GHC.liftIO $ getPreprocessorAsComments sourceFile + directiveToks <- GHC.liftIO $ getPreprocessorAsComments (GHC.enableGhcCpp flags2) source startLoc -- Tokens without hash-ifdef nonDirectiveToks <- tokeniseOriginalSrc startLoc flags2 source case GHC.lexTokenStream () flags2 strSrcBuf startLoc of @@ -131,7 +128,7 @@ goodComment c = isGoodComment (tokComment c) toRealLocated :: GHC.Located a -> GHC.PsLocated a toRealLocated (GHC.L (GHC.RealSrcSpan s (Strict.Just b)) x) = GHC.L (GHC.PsSpan s b) x -toRealLocated (GHC.L _ _) = GHC.panic "toRealLocated" +toRealLocated (GHC.L l _) = GHC.panic $ "toRealLocated:" ++ show l -- --------------------------------------------------------------------- @@ -264,22 +261,21 @@ alterToolSettings f dynFlags = dynFlags { GHC.toolSettings = f (GHC.toolSettings -- | Get the preprocessor directives as comment tokens from the -- source. -getPreprocessorAsComments :: FilePath -> IO [(GHC.Located GHC.Token, String)] -getPreprocessorAsComments srcFile = do - fcontents <- readFileGhc srcFile - let directives = filter (\(_lineNum,line) -> case line of '#' : _ -> True; _ -> False) - $ zip [1..] (lines fcontents) - - let mkTok (lineNum,line) = (GHC.L l (GHC.ITlineComment line (makeBufSpan l)),line) - where - start = GHC.mkSrcLoc (GHC.mkFastString srcFile) lineNum 1 - end = GHC.mkSrcLoc (GHC.mkFastString srcFile) lineNum (length line) - l = GHC.mkSrcSpan start end - - let toks = map mkTok directives - return toks +getPreprocessorAsComments :: GHC.ParserOpts -> GHC.StringBuffer -> GHC.RealSrcLoc -> IO [(GHC.Located GHC.Token, String)] +getPreprocessorAsComments opts source startLoc = do + case GHC.lexTokenStream () opts source startLoc of + GHC.POk _ ts -> + do + let + isCppTok (GHC.L _ (GHC.ITcpp _ _ _)) = True + isCppTok _ = False + toks = GHC.addSourceToTokens startLoc source ts + directiveToks = filter (\(t,_) -> isCppTok t) toks + return directiveToks + GHC.PFailed pst -> parseError pst makeBufSpan :: GHC.SrcSpan -> GHC.PsSpan +makeBufSpan (GHC.RealSrcSpan s (Strict.Just bs)) = GHC.PsSpan s bs makeBufSpan ss = pspan where bl = GHC.BufPos 0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a1904adb2edd1efd1f70707e7317a47d32dc4f0...90e47997dca940879720928e75c5f361ac2b5f29 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a1904adb2edd1efd1f70707e7317a47d32dc4f0...90e47997dca940879720928e75c5f361ac2b5f29 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/f7bc5064/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 14:40:56 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 16 Mar 2025 10:40:56 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] 6 commits: rts: add hs_try_putmvar_with_value to RTS API Message-ID: <67d6e2f87c3b2_213b4a2f725435f@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: e2a4f6e2 by Cheng Shao at 2025-03-16T14:40:41+00:00 rts: add hs_try_putmvar_with_value to RTS API This commit adds hs_try_putmvar_with_value to rts. It allows more flexibility than hs_try_putmvar by taking an additional value argument as a closure to be put into the MVar. This function is used & tested by the wasm backend runtime, though it makes sense to expose it as a public facing RTS API function as well. - - - - - 17c23017 by Cheng Shao at 2025-03-16T14:40:45+00:00 wasm: use MVar as JSFFI import blocking mechanism Previously, when blocking on a JSFFI import, we push a custom stg_jsffi_block stack frame and arrange the `promise.then` callback to write to that stack frame. It turns out we can simply use the good old MVar to implement the blocking logic, with a few benefits: - Less maintenance burden. We can drop the stg_jsffi_block related Cmm code without loss of functionality. - It interacts better with existing async exception mechanism. throwTo would properly block the caller if the target thread is masking async exceptions. - - - - - 05abc48c by Cheng Shao at 2025-03-16T14:40:45+00:00 wasm: properly pin the raiseJSException closure We used to use keepAlive# to pin the raiseJSException closure when blocking on a JSFFI import thunk, since it can potentially be used by RTS. But raiseJSException may be used in other places as well (e.g. the promise.throwTo logic), and it's better to simply unconditionally pin it in the JSFFI initialization logic. - - - - - 1215cfb1 by Cheng Shao at 2025-03-16T14:40:45+00:00 wasm: implement promise.throwTo() for async JSFFI exports This commit implements promise.throwTo() for wasm backend JSFFI exports. This allows the JavaScript side to interrupt Haskell computation by raising an async exception. See subsequent docs/test commits for more details. - - - - - 676498d0 by Cheng Shao at 2025-03-16T14:40:45+00:00 testsuite: add test for wasm promise.throwTo() logic This commit adds a test case to test the wasm backend promise.throwTo() logic. - - - - - d9e4701f by Cheng Shao at 2025-03-16T14:40:45+00:00 docs: document the wasm backend promise.throwTo() feature - - - - - 15 changed files: - docs/users_guide/exts/ffi.rst - docs/users_guide/wasm.rst - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/RtsAPI.c - rts/RtsSymbols.c - rts/include/HsFFI.h - rts/wasm/JSFFI.c - rts/wasm/blocker.cmm - rts/wasm/scheduler.cmm - testsuite/tests/jsffi/all.T - + testsuite/tests/jsffi/cancel.hs - + testsuite/tests/jsffi/cancel.mjs - + testsuite/tests/jsffi/cancel.stdout Changes: ===================================== docs/users_guide/exts/ffi.rst ===================================== @@ -976,6 +976,8 @@ wake up a Haskell thread from C/C++. void hs_try_putmvar (int capability, HsStablePtr sp); + void hs_try_putmvar_with_value (int capability, HsStablePtr sp, StgClosure *value); + The C call ``hs_try_putmvar(cap, mvar)`` is equivalent to the Haskell call ``tryPutMVar mvar ()``, except that it is @@ -988,6 +990,15 @@ call ``tryPutMVar mvar ()``, except that it is the ``MVar`` is empty; if it is full, ``hs_try_putmvar()`` will have no effect. +The C call ``hs_try_putmvar_with_value(cap, mvar, value)`` takes an +additional ``value`` argument, which is an RTS closure pointer of the +value to be put into the MVar. It works the same way as +``hs_try_putmvar`` while offering a bit more flexibility: for a C +value to be passed to Haskell, you can directly call one of the +``rts_mk`` functions to wrap the C value and put it into the MVar, +instead of writing it to a heap location and peeking it from a pointer +in Haskell. + **Example**. Suppose we have a C/C++ function to call that will return and then invoke a callback at some point in the future, passing us some data. We want to wait in Haskell for the callback to be called, and retrieve ===================================== docs/users_guide/wasm.rst ===================================== @@ -444,18 +444,11 @@ caveats: registered on that ``Promise`` will no longer be invoked. For simplicity of implementation, we aren’t using those for the time being. -- Normally, ``throwTo`` would block until the async exception has been - delivered. In the case of JSFFI, ``throwTo`` would always return - successfully immediately, while the target thread is still left in a - suspended state. The target thread will only be waken up when the - ``Promise`` actually resolves or rejects, though the ``Promise`` - result will be discarded at that point. - -The current way async exceptions are handled in JSFFI is subject to -change though. Ideally, once the exception is delivered, the target -thread can be waken up immediately and continue execution, and the -pending ``Promise`` will drop reference to that thread and no longer -invoke any continuations. +- When a thread blocks for a ``Promise`` to settle while masking + async exceptions, ``throwTo`` would block the caller until the + ``Promise`` is settled. If the target thread isn't masking async + exceptions, ``throwTo`` would cancel its blocking on the + ``Promise`` and resume its execution. .. _wasm-jsffi-cffi: @@ -584,3 +577,14 @@ JavaScript. Finally, in JavaScript, you can use ``await __exports.my_func()`` to call your exported ``my_func`` function and get its result, pass arguments, do error handling, etc etc. + +For each async export, the returned ``Promise`` value contains a +``promise.throwTo()`` callback. The value passed to +``promise.throwTo()`` will be wrapped as a ``JSException`` and raised +as an async exception in that thread. This can be useful for +interrupting Haskell computation in JavaScript. ``promise.throwTo()`` +doesn't block the JavaScript caller like Haskell ``throwTo``. It +doesn't necessarily result in ``promise`` being rejected since the +Haskell thread can handle the async exception, and it can be called +multiple time. It has no effect when the respective Haskell thread has +already run to completion. ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs ===================================== @@ -34,6 +34,7 @@ import GHC.Internal.Base import GHC.Internal.Exception.Type import GHC.Internal.Exts import GHC.Internal.IO +import GHC.Internal.IORef import GHC.Internal.Int import GHC.Internal.Stable import GHC.Internal.TopHandler (flushStdHandles) @@ -65,9 +66,14 @@ runIO res m = do let tmp@(JSString tmp_v) = toJSString $ displayException err js_promiseReject p tmp freeJSVal tmp_v - IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles) s0 of - (# s1, _ #) -> case stg_scheduler_loop# s1 of - (# s2, _ #) -> (# s2, p #) + post_action_ref <- newIORef $ pure () + IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles *> join (readIORef post_action_ref)) s0 of + (# s1, tso# #) -> case mkWeakNoFinalizer# tso# () s1 of + (# s2, w# #) -> case makeStablePtr# w# s2 of + (# s3, sp# #) -> case unIO (writeIORef post_action_ref $ js_promiseDelThrowTo p *> freeStablePtr (StablePtr $ unsafeCoerce# sp#)) s3 of + (# s4, _ #) -> case unIO (js_promiseAddThrowTo p $ StablePtr $ unsafeCoerce# sp#) s4 of + (# s5, _ #) -> case stg_scheduler_loop# s5 of + (# s6, _ #) -> (# s6, p #) runNonIO :: (JSVal -> a -> IO ()) -> a -> IO JSVal runNonIO res a = runIO res $ pure a @@ -75,6 +81,12 @@ runNonIO res a = runIO res $ pure a foreign import javascript unsafe "let res, rej; const p = new Promise((resolve, reject) => { res = resolve; rej = reject; }); p.resolve = res; p.reject = rej; return p;" js_promiseWithResolvers :: IO JSVal +foreign import javascript unsafe "$1.throwTo = (err) => __exports.rts_promiseThrowTo($2, err);" + js_promiseAddThrowTo :: JSVal -> StablePtr Any -> IO () + +foreign import javascript unsafe "$1.throwTo = () => {};" + js_promiseDelThrowTo :: JSVal -> IO () + foreign import prim "stg_scheduler_loopzh" stg_scheduler_loop# :: State# RealWorld -> (# State# RealWorld, () #) ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -5,6 +5,7 @@ {-# LANGUAGE UnliftedFFITypes #-} module GHC.Internal.Wasm.Prim.Imports ( + raiseJSException, stg_blockPromise, stg_messagePromiseUnit, stg_messagePromiseJSVal, @@ -67,23 +68,19 @@ function. At this point, the Promise fulfill logic that resumes the thread in the future has been set up, we can drop the Promise eagerly, then arrange the current thread to block. -Blocking is done by calling stg_jsffi_block: it pushes a -stg_jsffi_block frame and suspends the thread. The payload of -stg_jsffi_block frame is a single pointer field that holds the return -value. When the Promise is resolved with the result, the RTS fetches -the TSO indexed by the stable pointer passed earlier, checks for the -top stack frame to see if it's still a stg_jsffi_block frame (could be -stripped by an async exception), fills in the boxed result and -restarts execution. In case of a Promise rejection, the closure being -filled is generated via raiseJSException. +Blocking is done by readMVar. stg_blockPromise allocates an empty MVar +and pins it under a stable pointer, then finally blocks by readMVar. +The stable pointer is captured in the promise.then callback. When the +Promise is settled in the future, the promise.then callback writes the +result (or exception) to the MVar and then resumes Haskell execution. -} stg_blockPromise :: String -> JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> case stg_jsffi_check (unsafeCoerce# $ toException $ WouldBlockException err_msg) s0 of - (# s1 #) -> case myThreadId# s1 of - (# s2, tso #) -> case makeStablePtr# tso s2 of + (# s1 #) -> case newMVar# s1 of + (# s2, mv# #) -> case makeStablePtr# mv# s2 of (# s3, sp #) -> case unIO (msg_p p $ StablePtr $ unsafeCoerce# sp) s3 of -- Since we eagerly free the Promise here, we must return @@ -98,21 +95,11 @@ stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> -- and prevents dmdanal from being naughty (# s4, _ #) -> case unIO (freeJSVal p) s4 of (# s5, _ #) -> - -- raiseJSException_closure is used by the RTS in case - -- the Promise is rejected, and it is likely a CAF. So - -- we need to keep it alive when we block waiting for - -- the Promise to resolve or reject, and also mark it - -- as OPAQUE just to be sure. - keepAlive# raiseJSException s5 $ - stg_jsffi_block $ - throw PromisePendingException + readMVar# mv# s5 foreign import prim "stg_jsffi_check" stg_jsffi_check :: Any -> State# RealWorld -> (# State# RealWorld #) -foreign import prim "stg_jsffi_block" - stg_jsffi_block :: Any -> State# RealWorld -> (# State# RealWorld, r #) - foreign import javascript unsafe "$1.then(() => __exports.rts_promiseResolveUnit($2), err => __exports.rts_promiseReject($2, err))" stg_messagePromiseUnit :: JSVal -> StablePtr Any -> IO () ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -15,8 +15,7 @@ module GHC.Internal.Wasm.Prim.Types ( fromJSString, toJSString, JSException (..), - WouldBlockException (..), - PromisePendingException (..) + WouldBlockException (..) ) where import GHC.Internal.Base @@ -255,9 +254,3 @@ newtype WouldBlockException deriving (Show) instance Exception WouldBlockException - -data PromisePendingException - = PromisePendingException - deriving (Show) - -instance Exception PromisePendingException ===================================== rts/RtsAPI.c ===================================== @@ -942,12 +942,21 @@ void rts_done (void) it would be very difficult for the caller to arrange to free the StablePtr in all circumstances. + There's also hs_try_putmvar_with_value(cap, mvar, value) which + allows putting a custom value other than () in the MVar, typically + a closure created by one of rts_mk*() functions. + For more details, see the section "Waking up Haskell threads from C" in the User's Guide. -------------------------------------------------------------------------- */ -void hs_try_putmvar (/* in */ int capability, - /* in */ HsStablePtr mvar) +void hs_try_putmvar (int capability, HsStablePtr sp) { + hs_try_putmvar_with_value(capability, sp, TAG_CLOSURE(1, Unit_closure)); +} + +void hs_try_putmvar_with_value (/* in */ int capability, + /* in */ HsStablePtr mvar, + /* in */ StgClosure *value) { Task *task = getMyTask(); Capability *cap; @@ -963,7 +972,7 @@ void hs_try_putmvar (/* in */ int capability, #if !defined(THREADED_RTS) - performTryPutMVar(cap, (StgMVar*)deRefStablePtr(mvar), Unit_closure); + performTryPutMVar(cap, (StgMVar*)deRefStablePtr(mvar), value); freeStablePtr(mvar); #else @@ -976,7 +985,7 @@ void hs_try_putmvar (/* in */ int capability, task->cap = cap; RELEASE_LOCK(&cap->lock); - performTryPutMVar(cap, (StgMVar*)deRefStablePtr(mvar), Unit_closure); + performTryPutMVar(cap, (StgMVar*)deRefStablePtr(mvar), value); freeStablePtr(mvar); ===================================== rts/RtsSymbols.c ===================================== @@ -597,6 +597,7 @@ extern char **environ; SymI_HasProto(hs_hpc_module) \ SymI_HasProto(hs_thread_done) \ SymI_HasProto(hs_try_putmvar) \ + SymI_HasProto(hs_try_putmvar_with_value) \ SymI_HasProto(defaultRtsConfig) \ SymI_HasProto(initLinker) \ SymI_HasProto(initLinker_) \ ===================================== rts/include/HsFFI.h ===================================== @@ -21,6 +21,7 @@ extern "C" { /* get types from GHC's runtime system */ #include "ghcconfig.h" +#include "rts/Types.h" #include "stg/Types.h" /* get limits for floating point types */ @@ -138,6 +139,7 @@ extern int hs_spt_keys(StgPtr keys[], int szKeys); extern int hs_spt_key_count (void); extern void hs_try_putmvar (int capability, HsStablePtr sp); +extern void hs_try_putmvar_with_value (int capability, HsStablePtr sp, StgClosure *value); /* -------------------------------------------------------------------------- */ ===================================== rts/wasm/JSFFI.c ===================================== @@ -1,12 +1,15 @@ #include "Rts.h" #include "Prelude.h" +#include "RaiseAsync.h" #include "Schedule.h" +#include "Threads.h" #include "sm/Sanity.h" #if defined(__wasm_reference_types__) extern HsBool rts_JSFFI_flag; extern HsStablePtr rts_threadDelay_impl; +extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure; int __main_void(void); @@ -20,6 +23,7 @@ int __main_argc_argv(int argc, char *argv[]) { hs_init_ghc(&argc, &argv, __conf); // See Note [threadDelay on wasm] for details. rts_JSFFI_flag = HS_BOOL_TRUE; + getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure); rts_threadDelay_impl = getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure); return 0; } @@ -144,9 +148,7 @@ INLINE_HEADER void pushClosure (StgTSO *tso, StgWord c) { tso->stackobj->sp[0] = (W_) c; } -extern const StgInfoTable stg_jsffi_block_info; extern const StgInfoTable stg_scheduler_loop_info; -extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; // schedule a future round of RTS scheduler loop via setImmediate(), // to avoid jamming the JavaScript main thread @@ -173,19 +175,7 @@ void rts_schedulerLoop(void) { #define mk_rtsPromiseCallback(obj) \ { \ Capability *cap = &MainCapability; \ - StgTSO *tso = (StgTSO*)deRefStablePtr(sp); \ - IF_DEBUG(sanity, checkTSO(tso)); \ - hs_free_stable_ptr(sp); \ - \ - StgStack *stack = tso->stackobj; \ - IF_DEBUG(sanity, checkSTACK(stack)); \ - \ - if (stack->sp[0] == (StgWord)&stg_jsffi_block_info) { \ - dirty_TSO(cap, tso); \ - dirty_STACK(cap, stack); \ - stack->sp[1] = (StgWord)(obj); \ - } \ - scheduleThreadNow(cap, tso); \ + hs_try_putmvar_with_value(cap->no, sp, obj); \ rts_schedulerLoop(); \ } @@ -224,6 +214,27 @@ void rts_promiseReject(HsStablePtr, HsJSVal); void rts_promiseReject(HsStablePtr sp, HsJSVal js_err) mk_rtsPromiseCallback(rts_apply(cap, &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, rts_mkJSVal(cap, js_err))) +__attribute__((export_name("rts_promiseThrowTo"))) +void rts_promiseThrowTo(HsStablePtr, HsJSVal); +void rts_promiseThrowTo(HsStablePtr sp, HsJSVal js_err) { + Capability *cap = &MainCapability; + StgWeak *w = (StgWeak *)deRefStablePtr(sp); + if (w->header.info == &stg_DEAD_WEAK_info) { + return; + } + ASSERT(w->header.info == &stg_WEAK_info); + StgTSO *tso = (StgTSO *)w->key; + ASSERT(tso->header.info == &stg_TSO_info); + throwToSelf( + cap, tso, + rts_apply( + cap, + &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, + rts_mkJSVal(cap, js_err))); + tryWakeupThread(cap, tso); + rts_schedulerLoop(); +} + __attribute__((export_name("rts_freeStablePtr"))) void rts_freeStablePtr(HsStablePtr); void rts_freeStablePtr(HsStablePtr sp) { ===================================== rts/wasm/blocker.cmm ===================================== @@ -1,35 +1,5 @@ #include "Cmm.h" -#if !defined(UnregisterisedCompiler) -import CLOSURE STK_CHK_ctr; -import CLOSURE stg_jsffi_block_info; -#endif - -// The ret field will be the boxed result that the JSFFI async import -// actually returns. Or a bottom closure that throws JSException in -// case of Promise rejection. -INFO_TABLE_RET ( stg_jsffi_block, RET_SMALL, W_ info_ptr, P_ ret ) - return () -{ - jump %ENTRY_CODE(Sp(0)) (ret); -} - -// Push a stg_jsffi_block frame and suspend the current thread. bottom -// is a placeholder that throws PromisePendingException, though in -// theory the user should never see PromisePendingException since that -// indicates a thread blocked for async JSFFI is mistakenly resumed -// somehow. -stg_jsffi_block (P_ bottom) -{ - Sp_adj(-2); - Sp(0) = stg_jsffi_block_info; - Sp(1) = bottom; - - ASSERT(SpLim - WDS(RESERVED_STACK_WORDS) <= Sp); - - jump stg_block_noregs (); -} - // Check that we're in a forked thread at the moment, since main // threads that are bound to an InCall frame cannot block waiting for // a Promise to fulfill. err is the SomeException closure of ===================================== rts/wasm/scheduler.cmm ===================================== @@ -61,13 +61,13 @@ // 3. The main thread "scheduler loop" does one simple thing: check if // the thread run queue is non-empty and if so, yield to other // threads for execution, otherwise exit the loop. -// 4. When a thread blocks for a JSFFI async import result, it pins -// the current TSO via a stable pointer, and calls Promise.then() -// on the particular Promise it's blocked on. When that Promise is -// fulfilled in the future, it will call back into the RTS, fetches -// the TSO indexed by that stable pointer, passes the result and -// wakes up the TSO, then finally does another round of scheduler -// loop. This is handled by stg_blockPromise. +// 4. When a thread blocks for a JSFFI async import result, it pins an +// MVar to a stable pointer, calls Promise.then() on the particular +// Promise it's blocked on, then finally blocks by readMVar. When +// that Promise is fulfilled in the future, the Promise.then() +// callback writes the result to MVar and wakes up the TSO, then +// finally does another round of scheduler loop. This is handled by +// stg_blockPromise. // // The async JSFFI scheduler is idempotent, it's safe to run it // multiple times, now or later, though it's not safe to forget to run ===================================== testsuite/tests/jsffi/all.T ===================================== @@ -11,6 +11,8 @@ setTestOpts([ extra_ways(['compacting_gc', 'nonmoving', 'sanity']) ]) +test('cancel', [], compile_and_run, ['-optl-Wl,--export=setTimeout']) + test('gameover', [], compile_and_run, ['-optl-Wl,--export=testJSException,--export=testHSException']) test('http', [], compile_and_run, ['-optl-Wl,--export=main']) ===================================== testsuite/tests/jsffi/cancel.hs ===================================== @@ -0,0 +1,12 @@ +module Test where + +import Control.Exception + +foreign import javascript safe "new Promise(res => setTimeout(res, $1))" + js_setTimeout :: Int -> IO () + +setTimeout :: Int -> IO () +setTimeout t = evaluate =<< js_setTimeout t + +foreign export javascript "setTimeout" + setTimeout :: Int -> IO () ===================================== testsuite/tests/jsffi/cancel.mjs ===================================== @@ -0,0 +1,13 @@ +export default async (__exports) => { + const test = new Promise((res) => { + const p = __exports.setTimeout(114514); + p.throwTo("1919810"); + p.catch((err) => { + console.log(`${err}`.split("\n")[0]); + res(); + }); + }); + + await test; + process.exit(); +}; ===================================== testsuite/tests/jsffi/cancel.stdout ===================================== @@ -0,0 +1 @@ +RuntimeError: JSException "1919810" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c0e17bd4af6f2ecfe9ed721886b290780b93b6f8...d9e4701f0da3c5e301e3967748f1c00755bba04a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c0e17bd4af6f2ecfe9ed721886b290780b93b6f8...d9e4701f0da3c5e301e3967748f1c00755bba04a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/29fcb450/attachment-0001.html> From gitlab at gitlab.haskell.org Sun Mar 16 14:47:22 2025 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 16 Mar 2025 10:47:22 -0400 Subject: [Git][ghc/ghc][wip/wasm-jsffi-interruptible] 6 commits: rts: add hs_try_putmvar_with_value to RTS API Message-ID: <67d6e47a3c0f9_213b4a4ac1d0403f@gitlab.mail> Cheng Shao pushed to branch wip/wasm-jsffi-interruptible at Glasgow Haskell Compiler / GHC Commits: a86c50fa by Cheng Shao at 2025-03-16T14:47:06+00:00 rts: add hs_try_putmvar_with_value to RTS API This commit adds hs_try_putmvar_with_value to rts. It allows more flexibility than hs_try_putmvar by taking an additional value argument as a closure to be put into the MVar. This function is used & tested by the wasm backend runtime, though it makes sense to expose it as a public facing RTS API function as well. - - - - - 310af641 by Cheng Shao at 2025-03-16T14:47:11+00:00 wasm: use MVar as JSFFI import blocking mechanism Previously, when blocking on a JSFFI import, we push a custom stg_jsffi_block stack frame and arrange the `promise.then` callback to write to that stack frame. It turns out we can simply use the good old MVar to implement the blocking logic, with a few benefits: - Less maintenance burden. We can drop the stg_jsffi_block related Cmm code without loss of functionality. - It interacts better with existing async exception mechanism. throwTo would properly block the caller if the target thread is masking async exceptions. - - - - - b87ff1d8 by Cheng Shao at 2025-03-16T14:47:11+00:00 wasm: properly pin the raiseJSException closure We used to use keepAlive# to pin the raiseJSException closure when blocking on a JSFFI import thunk, since it can potentially be used by RTS. But raiseJSException may be used in other places as well (e.g. the promise.throwTo logic), and it's better to simply unconditionally pin it in the JSFFI initialization logic. - - - - - 4123dd30 by Cheng Shao at 2025-03-16T14:47:11+00:00 wasm: implement promise.throwTo() for async JSFFI exports This commit implements promise.throwTo() for wasm backend JSFFI exports. This allows the JavaScript side to interrupt Haskell computation by raising an async exception. See subsequent docs/test commits for more details. - - - - - f504bfc0 by Cheng Shao at 2025-03-16T14:47:11+00:00 testsuite: add test for wasm promise.throwTo() logic This commit adds a test case to test the wasm backend promise.throwTo() logic. - - - - - 9db7ceb4 by Cheng Shao at 2025-03-16T14:47:11+00:00 docs: document the wasm backend promise.throwTo() feature - - - - - 15 changed files: - docs/users_guide/exts/ffi.rst - docs/users_guide/wasm.rst - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - rts/RtsAPI.c - rts/RtsSymbols.c - rts/include/HsFFI.h - rts/wasm/JSFFI.c - rts/wasm/blocker.cmm - rts/wasm/scheduler.cmm - testsuite/tests/jsffi/all.T - + testsuite/tests/jsffi/cancel.hs - + testsuite/tests/jsffi/cancel.mjs - + testsuite/tests/jsffi/cancel.stdout Changes: ===================================== docs/users_guide/exts/ffi.rst ===================================== @@ -976,6 +976,8 @@ wake up a Haskell thread from C/C++. void hs_try_putmvar (int capability, HsStablePtr sp); + void hs_try_putmvar_with_value (int capability, HsStablePtr sp, StgClosure *value); + The C call ``hs_try_putmvar(cap, mvar)`` is equivalent to the Haskell call ``tryPutMVar mvar ()``, except that it is @@ -988,6 +990,15 @@ call ``tryPutMVar mvar ()``, except that it is the ``MVar`` is empty; if it is full, ``hs_try_putmvar()`` will have no effect. +The C call ``hs_try_putmvar_with_value(cap, mvar, value)`` takes an +additional ``value`` argument, which is an RTS closure pointer of the +value to be put into the MVar. It works the same way as +``hs_try_putmvar`` while offering a bit more flexibility: for a C +value to be passed to Haskell, you can directly call one of the +``rts_mk`` functions to wrap the C value and put it into the MVar, +instead of writing it to a heap location and peeking it from a pointer +in Haskell. + **Example**. Suppose we have a C/C++ function to call that will return and then invoke a callback at some point in the future, passing us some data. We want to wait in Haskell for the callback to be called, and retrieve ===================================== docs/users_guide/wasm.rst ===================================== @@ -444,18 +444,11 @@ caveats: registered on that ``Promise`` will no longer be invoked. For simplicity of implementation, we aren’t using those for the time being. -- Normally, ``throwTo`` would block until the async exception has been - delivered. In the case of JSFFI, ``throwTo`` would always return - successfully immediately, while the target thread is still left in a - suspended state. The target thread will only be waken up when the - ``Promise`` actually resolves or rejects, though the ``Promise`` - result will be discarded at that point. - -The current way async exceptions are handled in JSFFI is subject to -change though. Ideally, once the exception is delivered, the target -thread can be waken up immediately and continue execution, and the -pending ``Promise`` will drop reference to that thread and no longer -invoke any continuations. +- When a thread blocks for a ``Promise`` to settle while masking + async exceptions, ``throwTo`` would block the caller until the + ``Promise`` is settled. If the target thread isn't masking async + exceptions, ``throwTo`` would cancel its blocking on the + ``Promise`` and resume its execution. .. _wasm-jsffi-cffi: @@ -584,3 +577,14 @@ JavaScript. Finally, in JavaScript, you can use ``await __exports.my_func()`` to call your exported ``my_func`` function and get its result, pass arguments, do error handling, etc etc. + +For each async export, the returned ``Promise`` value contains a +``promise.throwTo()`` callback. The value passed to +``promise.throwTo()`` will be wrapped as a ``JSException`` and raised +as an async exception in that thread. This can be useful for +interrupting Haskell computation in JavaScript. ``promise.throwTo()`` +doesn't block the JavaScript caller like Haskell ``throwTo``. It +doesn't necessarily result in ``promise`` being rejected since the +Haskell thread can handle the async exception, and it can be called +multiple time. It has no effect when the respective Haskell thread has +already run to completion. ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs ===================================== @@ -34,6 +34,7 @@ import GHC.Internal.Base import GHC.Internal.Exception.Type import GHC.Internal.Exts import GHC.Internal.IO +import GHC.Internal.IORef import GHC.Internal.Int import GHC.Internal.Stable import GHC.Internal.TopHandler (flushStdHandles) @@ -65,9 +66,14 @@ runIO res m = do let tmp@(JSString tmp_v) = toJSString $ displayException err js_promiseReject p tmp freeJSVal tmp_v - IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles) s0 of - (# s1, _ #) -> case stg_scheduler_loop# s1 of - (# s2, _ #) -> (# s2, p #) + post_action_ref <- newIORef $ pure () + IO $ \s0 -> case fork# (unIO $ catch (res p =<< m) topHandler *> flushStdHandles *> join (readIORef post_action_ref)) s0 of + (# s1, tso# #) -> case mkWeakNoFinalizer# tso# () s1 of + (# s2, w# #) -> case makeStablePtr# w# s2 of + (# s3, sp# #) -> case unIO (writeIORef post_action_ref $ js_promiseDelThrowTo p *> freeStablePtr (StablePtr $ unsafeCoerce# sp#)) s3 of + (# s4, _ #) -> case unIO (js_promiseAddThrowTo p $ StablePtr $ unsafeCoerce# sp#) s4 of + (# s5, _ #) -> case stg_scheduler_loop# s5 of + (# s6, _ #) -> (# s6, p #) runNonIO :: (JSVal -> a -> IO ()) -> a -> IO JSVal runNonIO res a = runIO res $ pure a @@ -75,6 +81,12 @@ runNonIO res a = runIO res $ pure a foreign import javascript unsafe "let res, rej; const p = new Promise((resolve, reject) => { res = resolve; rej = reject; }); p.resolve = res; p.reject = rej; return p;" js_promiseWithResolvers :: IO JSVal +foreign import javascript unsafe "$1.throwTo = (err) => __exports.rts_promiseThrowTo($2, err);" + js_promiseAddThrowTo :: JSVal -> StablePtr Any -> IO () + +foreign import javascript unsafe "$1.throwTo = () => {};" + js_promiseDelThrowTo :: JSVal -> IO () + foreign import prim "stg_scheduler_loopzh" stg_scheduler_loop# :: State# RealWorld -> (# State# RealWorld, () #) ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs ===================================== @@ -5,6 +5,7 @@ {-# LANGUAGE UnliftedFFITypes #-} module GHC.Internal.Wasm.Prim.Imports ( + raiseJSException, stg_blockPromise, stg_messagePromiseUnit, stg_messagePromiseJSVal, @@ -67,23 +68,19 @@ function. At this point, the Promise fulfill logic that resumes the thread in the future has been set up, we can drop the Promise eagerly, then arrange the current thread to block. -Blocking is done by calling stg_jsffi_block: it pushes a -stg_jsffi_block frame and suspends the thread. The payload of -stg_jsffi_block frame is a single pointer field that holds the return -value. When the Promise is resolved with the result, the RTS fetches -the TSO indexed by the stable pointer passed earlier, checks for the -top stack frame to see if it's still a stg_jsffi_block frame (could be -stripped by an async exception), fills in the boxed result and -restarts execution. In case of a Promise rejection, the closure being -filled is generated via raiseJSException. +Blocking is done by readMVar. stg_blockPromise allocates an empty MVar +and pins it under a stable pointer, then finally blocks by readMVar. +The stable pointer is captured in the promise.then callback. When the +Promise is settled in the future, the promise.then callback writes the +result (or exception) to the MVar and then resumes Haskell execution. -} stg_blockPromise :: String -> JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> case stg_jsffi_check (unsafeCoerce# $ toException $ WouldBlockException err_msg) s0 of - (# s1 #) -> case myThreadId# s1 of - (# s2, tso #) -> case makeStablePtr# tso s2 of + (# s1 #) -> case newMVar# s1 of + (# s2, mv# #) -> case makeStablePtr# mv# s2 of (# s3, sp #) -> case unIO (msg_p p $ StablePtr $ unsafeCoerce# sp) s3 of -- Since we eagerly free the Promise here, we must return @@ -98,21 +95,11 @@ stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> -- and prevents dmdanal from being naughty (# s4, _ #) -> case unIO (freeJSVal p) s4 of (# s5, _ #) -> - -- raiseJSException_closure is used by the RTS in case - -- the Promise is rejected, and it is likely a CAF. So - -- we need to keep it alive when we block waiting for - -- the Promise to resolve or reject, and also mark it - -- as OPAQUE just to be sure. - keepAlive# raiseJSException s5 $ - stg_jsffi_block $ - throw PromisePendingException + readMVar# mv# s5 foreign import prim "stg_jsffi_check" stg_jsffi_check :: Any -> State# RealWorld -> (# State# RealWorld #) -foreign import prim "stg_jsffi_block" - stg_jsffi_block :: Any -> State# RealWorld -> (# State# RealWorld, r #) - foreign import javascript unsafe "$1.then(() => __exports.rts_promiseResolveUnit($2), err => __exports.rts_promiseReject($2, err))" stg_messagePromiseUnit :: JSVal -> StablePtr Any -> IO () ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -15,8 +15,7 @@ module GHC.Internal.Wasm.Prim.Types ( fromJSString, toJSString, JSException (..), - WouldBlockException (..), - PromisePendingException (..) + WouldBlockException (..) ) where import GHC.Internal.Base @@ -255,9 +254,3 @@ newtype WouldBlockException deriving (Show) instance Exception WouldBlockException - -data PromisePendingException - = PromisePendingException - deriving (Show) - -instance Exception PromisePendingException ===================================== rts/RtsAPI.c ===================================== @@ -942,12 +942,23 @@ void rts_done (void) it would be very difficult for the caller to arrange to free the StablePtr in all circumstances. + There's also hs_try_putmvar_with_value(cap, mvar, value) which + allows putting a custom value other than () in the MVar, typically + a closure created by one of rts_mk*() functions. + For more details, see the section "Waking up Haskell threads from C" in the User's Guide. -------------------------------------------------------------------------- */ void hs_try_putmvar (/* in */ int capability, /* in */ HsStablePtr mvar) +{ + hs_try_putmvar_with_value(capability, mvar, TAG_CLOSURE(1, Unit_closure)); +} + +void hs_try_putmvar_with_value (/* in */ int capability, + /* in */ HsStablePtr mvar, + /* in */ StgClosure *value) { Task *task = getMyTask(); Capability *cap; @@ -963,7 +974,7 @@ void hs_try_putmvar (/* in */ int capability, #if !defined(THREADED_RTS) - performTryPutMVar(cap, (StgMVar*)deRefStablePtr(mvar), Unit_closure); + performTryPutMVar(cap, (StgMVar*)deRefStablePtr(mvar), value); freeStablePtr(mvar); #else @@ -976,7 +987,7 @@ void hs_try_putmvar (/* in */ int capability, task->cap = cap; RELEASE_LOCK(&cap->lock); - performTryPutMVar(cap, (StgMVar*)deRefStablePtr(mvar), Unit_closure); + performTryPutMVar(cap, (StgMVar*)deRefStablePtr(mvar), value); freeStablePtr(mvar); ===================================== rts/RtsSymbols.c ===================================== @@ -597,6 +597,7 @@ extern char **environ; SymI_HasProto(hs_hpc_module) \ SymI_HasProto(hs_thread_done) \ SymI_HasProto(hs_try_putmvar) \ + SymI_HasProto(hs_try_putmvar_with_value) \ SymI_HasProto(defaultRtsConfig) \ SymI_HasProto(initLinker) \ SymI_HasProto(initLinker_) \ ===================================== rts/include/HsFFI.h ===================================== @@ -21,6 +21,7 @@ extern "C" { /* get types from GHC's runtime system */ #include "ghcconfig.h" +#include "rts/Types.h" #include "stg/Types.h" /* get limits for floating point types */ @@ -138,6 +139,7 @@ extern int hs_spt_keys(StgPtr keys[], int szKeys); extern int hs_spt_key_count (void); extern void hs_try_putmvar (int capability, HsStablePtr sp); +extern void hs_try_putmvar_with_value (int capability, HsStablePtr sp, StgClosure *value); /* -------------------------------------------------------------------------- */ ===================================== rts/wasm/JSFFI.c ===================================== @@ -1,12 +1,15 @@ #include "Rts.h" #include "Prelude.h" +#include "RaiseAsync.h" #include "Schedule.h" +#include "Threads.h" #include "sm/Sanity.h" #if defined(__wasm_reference_types__) extern HsBool rts_JSFFI_flag; extern HsStablePtr rts_threadDelay_impl; +extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure; int __main_void(void); @@ -20,6 +23,7 @@ int __main_argc_argv(int argc, char *argv[]) { hs_init_ghc(&argc, &argv, __conf); // See Note [threadDelay on wasm] for details. rts_JSFFI_flag = HS_BOOL_TRUE; + getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure); rts_threadDelay_impl = getStablePtr((StgPtr)&ghczminternal_GHCziInternalziWasmziPrimziConcziInternal_threadDelay_closure); return 0; } @@ -144,9 +148,7 @@ INLINE_HEADER void pushClosure (StgTSO *tso, StgWord c) { tso->stackobj->sp[0] = (W_) c; } -extern const StgInfoTable stg_jsffi_block_info; extern const StgInfoTable stg_scheduler_loop_info; -extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; // schedule a future round of RTS scheduler loop via setImmediate(), // to avoid jamming the JavaScript main thread @@ -173,19 +175,7 @@ void rts_schedulerLoop(void) { #define mk_rtsPromiseCallback(obj) \ { \ Capability *cap = &MainCapability; \ - StgTSO *tso = (StgTSO*)deRefStablePtr(sp); \ - IF_DEBUG(sanity, checkTSO(tso)); \ - hs_free_stable_ptr(sp); \ - \ - StgStack *stack = tso->stackobj; \ - IF_DEBUG(sanity, checkSTACK(stack)); \ - \ - if (stack->sp[0] == (StgWord)&stg_jsffi_block_info) { \ - dirty_TSO(cap, tso); \ - dirty_STACK(cap, stack); \ - stack->sp[1] = (StgWord)(obj); \ - } \ - scheduleThreadNow(cap, tso); \ + hs_try_putmvar_with_value(cap->no, sp, obj); \ rts_schedulerLoop(); \ } @@ -224,6 +214,27 @@ void rts_promiseReject(HsStablePtr, HsJSVal); void rts_promiseReject(HsStablePtr sp, HsJSVal js_err) mk_rtsPromiseCallback(rts_apply(cap, &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, rts_mkJSVal(cap, js_err))) +__attribute__((export_name("rts_promiseThrowTo"))) +void rts_promiseThrowTo(HsStablePtr, HsJSVal); +void rts_promiseThrowTo(HsStablePtr sp, HsJSVal js_err) { + Capability *cap = &MainCapability; + StgWeak *w = (StgWeak *)deRefStablePtr(sp); + if (w->header.info == &stg_DEAD_WEAK_info) { + return; + } + ASSERT(w->header.info == &stg_WEAK_info); + StgTSO *tso = (StgTSO *)w->key; + ASSERT(tso->header.info == &stg_TSO_info); + throwToSelf( + cap, tso, + rts_apply( + cap, + &ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure, + rts_mkJSVal(cap, js_err))); + tryWakeupThread(cap, tso); + rts_schedulerLoop(); +} + __attribute__((export_name("rts_freeStablePtr"))) void rts_freeStablePtr(HsStablePtr); void rts_freeStablePtr(HsStablePtr sp) { ===================================== rts/wasm/blocker.cmm ===================================== @@ -1,35 +1,5 @@ #include "Cmm.h" -#if !defined(UnregisterisedCompiler) -import CLOSURE STK_CHK_ctr; -import CLOSURE stg_jsffi_block_info; -#endif - -// The ret field will be the boxed result that the JSFFI async import -// actually returns. Or a bottom closure that throws JSException in -// case of Promise rejection. -INFO_TABLE_RET ( stg_jsffi_block, RET_SMALL, W_ info_ptr, P_ ret ) - return () -{ - jump %ENTRY_CODE(Sp(0)) (ret); -} - -// Push a stg_jsffi_block frame and suspend the current thread. bottom -// is a placeholder that throws PromisePendingException, though in -// theory the user should never see PromisePendingException since that -// indicates a thread blocked for async JSFFI is mistakenly resumed -// somehow. -stg_jsffi_block (P_ bottom) -{ - Sp_adj(-2); - Sp(0) = stg_jsffi_block_info; - Sp(1) = bottom; - - ASSERT(SpLim - WDS(RESERVED_STACK_WORDS) <= Sp); - - jump stg_block_noregs (); -} - // Check that we're in a forked thread at the moment, since main // threads that are bound to an InCall frame cannot block waiting for // a Promise to fulfill. err is the SomeException closure of ===================================== rts/wasm/scheduler.cmm ===================================== @@ -61,13 +61,13 @@ // 3. The main thread "scheduler loop" does one simple thing: check if // the thread run queue is non-empty and if so, yield to other // threads for execution, otherwise exit the loop. -// 4. When a thread blocks for a JSFFI async import result, it pins -// the current TSO via a stable pointer, and calls Promise.then() -// on the particular Promise it's blocked on. When that Promise is -// fulfilled in the future, it will call back into the RTS, fetches -// the TSO indexed by that stable pointer, passes the result and -// wakes up the TSO, then finally does another round of scheduler -// loop. This is handled by stg_blockPromise. +// 4. When a thread blocks for a JSFFI async import result, it pins an +// MVar to a stable pointer, calls Promise.then() on the particular +// Promise it's blocked on, then finally blocks by readMVar. When +// that Promise is fulfilled in the future, the Promise.then() +// callback writes the result to MVar and wakes up the TSO, then +// finally does another round of scheduler loop. This is handled by +// stg_blockPromise. // // The async JSFFI scheduler is idempotent, it's safe to run it // multiple times, now or later, though it's not safe to forget to run ===================================== testsuite/tests/jsffi/all.T ===================================== @@ -11,6 +11,8 @@ setTestOpts([ extra_ways(['compacting_gc', 'nonmoving', 'sanity']) ]) +test('cancel', [], compile_and_run, ['-optl-Wl,--export=setTimeout']) + test('gameover', [], compile_and_run, ['-optl-Wl,--export=testJSException,--export=testHSException']) test('http', [], compile_and_run, ['-optl-Wl,--export=main']) ===================================== testsuite/tests/jsffi/cancel.hs ===================================== @@ -0,0 +1,12 @@ +module Test where + +import Control.Exception + +foreign import javascript safe "new Promise(res => setTimeout(res, $1))" + js_setTimeout :: Int -> IO () + +setTimeout :: Int -> IO () +setTimeout t = evaluate =<< js_setTimeout t + +foreign export javascript "setTimeout" + setTimeout :: Int -> IO () ===================================== testsuite/tests/jsffi/cancel.mjs ===================================== @@ -0,0 +1,13 @@ +export default async (__exports) => { + const test = new Promise((res) => { + const p = __exports.setTimeout(114514); + p.throwTo("1919810"); + p.catch((err) => { + console.log(`${err}`.split("\n")[0]); + res(); + }); + }); + + await test; + process.exit(); +}; ===================================== testsuite/tests/jsffi/cancel.stdout ===================================== @@ -0,0 +1 @@ +RuntimeError: JSException "1919810" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9e4701f0da3c5e301e3967748f1c00755bba04a...9db7ceb4fc9c47b3fa923b8f99839e81b319e698 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9e4701f0da3c5e301e3967748f1c00755bba04a...9db7ceb4fc9c47b3fa923b8f99839e81b319e698 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250316/09baf511/attachment-0001.html>