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: 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: 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 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 | 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 | 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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 "") + (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 = "" + , 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 "") + 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 "") 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, "") + 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 " @@ -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: 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: 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: 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 - - - - - 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: 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: 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 - - - - - 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 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 | 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 | 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: 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: 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: 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: 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: 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 "") + (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 = "" + , 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 "") + 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 "") 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, "") + 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 " @@ -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: 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 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 | 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 | 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: 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 ":" x OrigStmt x _ -> ppr_builder ":" x - OrigPat x _ -> ifPprDebug (braces (text ":" <+> 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: 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: 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: 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: 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: 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: 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: 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: 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: 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 "") + (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 = "" + , 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 "") + 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 "") 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, "") + 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 " @@ -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: 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 - - - - - 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: 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 "") + (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 = "" + , 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 "") + 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 "") 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, "") + 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 " @@ -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: 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 "") + (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 = "" + , 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 "") + 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 "") 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, "") + 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 " @@ -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: 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 - - - - - 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 "") + (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 = "" + , 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 "") + 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 "") 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, "") + 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 " @@ -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: 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: 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: 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 {} :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: 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: 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: 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 | 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 | 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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 | 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 | 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: 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: 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 - - - - - 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 - - - - - 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 ------------------------- 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 ‘’ 4 | #include "Error.h" +++ |+#include 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 ‘’ | 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 - - - - - 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 - - - - - 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 - - - - - 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 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 | 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 | 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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 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 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] + 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: 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: 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: 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 -O2 - release (same as perf with -haddock) + release (same as perf with -haddock and +no_self_recomp) -O
-H64m -O
-H64m @@ -329,6 +329,10 @@ The supported transformers are listed below: dump_stg Dump STG of all modules compiled by a stage1 compiler to a file + + no_self_recomp + Disable including self-recompilation information in interface files via -fno-write-if-self-recomp. If you are building a distribution you can enable this flag to produce more deterministic interface files. + ### 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: 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 -O2 - release (same as perf with -haddock) + release (same as perf with -haddock and +no_self_recomp) -O
-H64m -O
-H64m @@ -329,6 +329,10 @@ The supported transformers are listed below: dump_stg Dump STG of all modules compiled by a stage1 compiler to a file + + no_self_recomp + Disable including self-recompilation information in interface files via -fno-write-if-self-recomp. If you are building a distribution you can enable this flag to produce more deterministic interface files. + ### 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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. + +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. + + 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: 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. -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. 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: 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 | 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 | 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: 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: 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 | 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 | 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: 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 + +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 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. - -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. - 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: 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: 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: 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: 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: 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 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 | 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 | 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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 - - - - - 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 - - - - - 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 ------------------------- 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 ‘’ 4 | #include "Error.h" +++ |+#include 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 ‘’ | 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 - - - - - 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 - - - - - 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 - - - - - 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 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 | 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 | 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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: 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 -O2 - release (same as perf with -haddock) + release (same as perf with -haddock and +no_self_recomp) -O
-H64m -O
-H64m @@ -329,6 +329,10 @@ The supported transformers are listed below: dump_stg Dump STG of all modules compiled by a stage1 compiler to a file + + no_self_recomp + Disable including self-recompilation information in interface files via -fno-write-if-self-recomp. If you are building a distribution you can enable this flag to produce more deterministic interface files. + ### 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: 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: 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: 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 :: String -> -> Q Exp #

decl :: :: Q [ [Dec] #

  • forkTH :: :: Q Exp
  • forkTH :: :: Q Exp # 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 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 | 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 | 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: 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 specifies the style sheet to use - new option: -o

    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 ) - - - - - 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 (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 - - - - - 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
    ..
    , just use .. 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 " (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 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 and
     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 

    ..

    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 . - - - - - 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 . - - - - - 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 . - - - - - 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