Commits on Source (95)
-
Zubin authored
Also bump `binaryInterfaceVersion` to 45 to detect binary version changes.
-
We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 (cherry picked from commit da20cac1)
-
When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). (cherry picked from commit e9dc2690)
-
(cherry picked from commit 92976985)
-
Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 (cherry picked from commit 2293c0b7)
-
Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 (cherry picked from commit 64e876bc)
-
(cherry picked from commit bcb293f2)
-
Solves documentaion issue #25084. (cherry picked from commit 535a2117)
-
(cherry picked from commit c9590ba0)
-
The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 (cherry picked from commit a49e66fc)
-
The C calling convention / standard requires that arguments and their values are of the same type. (cherry picked from commit 5fd320da)
-
This commit updates the section of the user's guide pertaining to X86 feature flags with the following changes: - the NCG backend now supports SIMD, so remove all text that says the contrary, - the LLVM backend does not "automatically detect" features, so remove any text that makes that claim. (cherry picked from commit 9c9c790d)
-
This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 (cherry picked from commit 50490075)
-
This patch makes GHC bail out with an proper error message when it's not configured with LLVM but users attempt to pass -fllvm, see #25011 and added comment for details. Fixes #25011 Co-authored-by:
Rodrigo Mesquita <rodrigo.m.mesquita@gmail.com> (cherry picked from commit 2338a971)
-
(cherry picked from commit 0dfaeb66)
-
(cherry picked from commit 09d24d82)
-
(cherry picked from commit 0060ece7)
-
The type variables in the holes fit output from `abstract_refinement_hole_fits` is quite sensitive to compiler configuration. Specifically, a slight change in the inlining behavior of `throw` changes type variable naming in `(>>=)` and a few others. Ideally we would make hole fits output more deterministic but in the meantime we simply normalise this difference away as it not relevant to the test's goal. (cherry picked from commit d029f170)
-
(cherry picked from commit da5d7d0d)
-
As noted in #25066, the exception backtrace proposal introduced a rather subtle performance regression due to simplification producing Core which the demand analyser concludes may diverge with a precise exception. The nature of the problem is more completely described in the new Note [Hiding precise exception signature in throw]. The (rather hacky) solution we use here hides the problematic optimisation through judicious use of `noinline`. Ultimately however we will want a more principled solution (e.g. #23847). Fixes #255066 CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290 Metric Decrease: T9872d (cherry picked from commit eb7ddae1)
-
Also, fix a bug in RST with missing newline before a listing. Co-authored-by:
Arnaud Spiwack <arnaud@spiwack.net> (cherry picked from commit 4dd30cba)
-
As proposed in core-libraries-committee#275. (cherry picked from commit 876d6e0e)
-
Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> (cherry picked from commit ac004028)
-
(cherry picked from commit 0e5cff66)
-
(cherry picked from commit e44e448e)
-
We never populate it, so remove it. (cherry picked from commit 4a2f0f13)
-
EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA` from `Parser.y`, it is the same as `glR` EPA: Remove unused annotation from XOpApp EPA: Use EpToken for XNPat and XNegApp EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens. EPA: Use specific annotation for MultiIf EPA: Move annotations into FunRhs EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig EPA: Remove [AddEpAnn] from ArithSeq EPA: Remove [AddEpAnn] from HsProc EPA: Remove [AddEpAnn] from HsStatic EPA: Remove [AddEpAnn] from BindStmt EPA: Remove [AddEpAnn] from TransStmt EPA: Remove [AddEpAnn] from HsTypedSplice EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr (cherry picked from commit ef481813)
-
If we have a broken symlink in the repository, don't try to `need` the symlink or the target of the symlink. Attempting to do so has `shake` attempt to read the target to compute its hash, which fails because the target doesn't exist. (cherry picked from commit 8b402da2)
-
Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately, this broke our source distribution as we use use `tar --dereference` to avoid issues with symlink compatibility on windows, and `tar --dereference` chokes when it encounters any broken symlinks. We can't get rid of `--dereference` because symlinks are generally broken on windows, so the only option is to exclude this file from source archives. see also https://github.com/haskell/cabal/issues/10442 (cherry picked from commit 16f97667)
-
Zubin authored
including the filename in the key. Ideally we would use `ghc -M` output to do a proper toposort Partially addresses #25372
-
Zubin authored
-
Zubin authored
-
Zubin authored
-
Zubin authored
-
Zubin authored
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences
-
Zubin authored
-
Zubin authored
-
Zubin authored
-
EPA: Remove [AddEpAnn] from LazyPat EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat EPA: Remove [AddEpAnn] from HsFieldBind EPA: Remove [AddEpAnn] from PatSynBind EPA: Remove [AddEpAnn] from IPBind EPA: Remove [AddEpAnn] from FixSig EPA: Remove [AddEpAnn] from activation rules EPA: Remove [AddEpann] from SpecInstSig EPA: Remove [AddEpAnn] from MinimalSig EPA: Remove [AddEpAnn] from SCCFunSig EPA: Remove [AddEpAnn] from CompleteMatchSig EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig EPA: Remove [AddEpAnn] from IEThingAbs EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith EPA: Remove [AddEpAnn] from IEModuleContents EPA: Remove [AddEpAnn] from HsOpTy EPA: Remove [AddEpAnn] for various binders EPA: Remove [AddEpAnn] for HsIParamTy (cherry picked from commit e9cc4699)
-
EPA: Remove [AddEpAnn] from HsDocTy EPA: Remove [AddEpAnn] from HsBangTy EPA: Remove [AddEpAnn] from HsExplicitListTy EPA: Remove [AddEpAnn] from HsExplicitTupleTy EPA: Remove [AddEpAnn] from HsTypedBracket EPA: Remove [AddEpAnn] from HsUntypedBracket EPA: Remove [AddEpAnn] from PatBuilderOpApp EPA: break out 'EpToken "|"' from ClassDecl anns EPA: Remove [AddEpAnn] from ClassDecl EPA: Remove [AddEpAnn] from SynDecl (cherry picked from commit 5f67db48)
-
This patch fixes an unnoticed undefined behavior in the bytecode interpreter. It can be caught by building `rts/Interpreter.c` with `-fsanitize=pointer-overflow`, the warning message is something like: ``` rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658 SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13 rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658 SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13 rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0 SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13 ``` Whenever we do something like `SpW(-1)`, the negative argument is implicitly converted to an unsigned integer type and causes pointer arithmetic overflow. It happens to be harmless for most targets since overflowing would wrap the result to desired value, but it's still coincidental and undefined behavior. Furthermore, it causes real damage to the wasm backend, given clang-20 will emit invalid wasm code that crashes at run-time for this kind of C code! (see https://github.com/llvm/llvm-project/issues/108770) The fix here is adding some explicit casts to ensure we always use the signed `ptrdiff_t` type as right hand operand of pointer arithmetic. (cherry picked from commit 5bcfefd5)
-
EPA: Remove [AddEpAnn] from DataDecl This is quite a big change. The most important part is moving the annotations into HsDataDefn, using a specific annotation data type. It has a knock-on to everything that uses HsDataDefn EPA: Remove [AddEpAnn] for FunDep EPA: Remove [AddEpann] from FamilyDecl EPA: Remove [AddEpAnn] From InjectivityAnn EPA: Remove [AddEpAnn] from DefaultDecl EPA: Remove [AddEpAnn] from RuleDecls EPA: Remove [AddEpAnn] from Warnings (cherry picked from commit 25edf849)
-
(cherry picked from commit fbbbd010)
-
This commit renames prelude.js to prelude.mjs for wasm backend rts jsbits, and slightly adjusts the jsbits contents. This is for preparing the implementation of dyld.mjs that contains wasm dynamic linker logic, which needs to import prelude.mjs as a proper ESM module. (cherry picked from commit 71a471e7) (cherry picked from commit 1d5a2ff8)
-
This commit wraps imported freeJSVal in a __wrapped_freeJSVal C function for wasm backend RTS. In general, wasm imports are only supposed to be directly called by C; they shouldn't be used as function pointers, which confuses wasm-ld at link-time when generating shared libraries. (cherry picked from commit 33d9db17) (cherry picked from commit 151017ca)
-
This commit drops interpretBCO support from non dynamic rts ways on wasm. The bytecode interpreter is only useful when the RTS linker also works, and on wasm it only works for dynamic ways anyway. An additional benefit of dropping interpretBCO is reduction in code size of linked wasm modules, especially since interpretBCO references ffi_call which is an auto-generated large function in libffi-wasm and unused by most user applications. (cherry picked from commit 90a35c41) (cherry picked from commit 21dff5ba)
-
This commit wraps the predefined GlobalRegs in Wasm.S under a CPP guard to prevent building for PIC mode. When building dynamic ways of RTS, the wasm globals that represent STG GlobalRegs will be created and supplied by dyld.mjs. The current wasm dylink convention doesn't properly support exporting relocatable wasm globals at all, any wasm global exported by a .so is assumed to be a GOT.mem entry. (cherry picked from commit 98a32ec5) (cherry picked from commit 70f75b0d)
-
This commit changes the hostSupportsRPaths predicate to targetSupportsRPaths and use that to decide whether to pass RPATH-related link-time options. It's not applied to stage0, we should just use the default link-time options of stageBoot ghc. (cherry picked from commit a6a82cdb) (cherry picked from commit 7e1f1b07)
-
This commit adds -fvisibility=default to CFLAGS of gmp when building for wasm. This is required to generate the ghc-bignum shared library without linking errors. Clang defaults to -fvisibility=hidden for wasm targets, which will cause issues when a symbol is expected to be exported in a shared library but without explicit visibility attribute annotation. (cherry picked from commit c247f2ee) (cherry picked from commit 18e53833)
-
This commit adds the host_fully_static flavour transformer to hadrian, which ensures stage0 is fully statically linked while still permitting stage1 libdir to contain shared libraries. This is intended to be used by the wasm backend to build portable linux bindists that contain wasm shared libraries. (cherry picked from commit b45080a3) (cherry picked from commit c12980bf)
-
This commit implements the config.cross field in the testsuite driver. It comes from the "cross compiling" ghc info field for both in-tree/out-of-tree GHC, and is an accurate predicate of whether we're cross-compiling or not (compared to the precense of target emulator), and is useful to implement predicates to assert the precense of internal interpreter (only available on non-cross GHC) for tests that do require it (e.g. plugins). (cherry picked from commit 2956a3f7) (cherry picked from commit 00fef7bc)
-
This patch implements the targetRTSLinkerOnlySupportsSharedLibs predicate in hadrian. Its definition in hadrian is the single source of truth, and the information propagates to ghc settings file, ghc driver and testsuite driver. It is used in various places to ensure dynamic dependency is selected when the target RTS linker only supports loading dynamic code. (cherry picked from commit 8c74a0ed) (cherry picked from commit 9d2e02f9)
-
This commit fixes shared library size tests (e.g. array_so in testsuite/tests/perf/size/all.T) when testing cross ghc. Previously, if shared library file extension of host and target differs, those tests will fail with framework errors due to not finding the right files. (cherry picked from commit 05e40406) (cherry picked from commit d00c26a5)
-
This commit use the interpreterDynamic predicate in preloadLib to decide if we should do dynLoadObjs instead of loadObj. Previously we used hostIsDynamic which was only written with non-cross internal interpreter in mind. The testsuite is also adjusted to remove hard-wired -fPIC flag for cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and properly pass ghc_th_way_flags to ghc. (cherry picked from commit 80aa8983) (cherry picked from commit 1b30373d)
Showing
- .gitlab-ci.yml 3 additions, 1 deletion.gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs 12 additions, 4 deletions.gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml 186 additions, 58 deletions.gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py 1 addition, 0 deletions.gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py 5 additions, 1 deletion.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC.hs 18 additions, 18 deletionscompiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs 10 additions, 0 deletionscompiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs 4 additions, 0 deletionscompiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs 13 additions, 0 deletionscompiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs 4 additions, 0 deletionscompiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs 4 additions, 6 deletionscompiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs 19 additions, 13 deletionscompiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs 150 additions, 89 deletionscompiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/DynFlags.hs 3 additions, 0 deletionscompiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Errors/Ppr.hs 13 additions, 0 deletionscompiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs 8 additions, 0 deletionscompiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Hooks.hs 0 additions, 2 deletionscompiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs 0 additions, 3 deletionscompiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs 5 additions, 1 deletioncompiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs 5 additions, 1 deletioncompiler/GHC/Driver/Pipeline/Execute.hs