- Mar 09, 2025
-
-
The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers.
-
- Mar 08, 2025
-
-
The relative metric is already in %, so no need to multiply by 100.
-
This reverts commit 643dd3d8. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale.
-
This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003
-
https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite
-
- Mar 07, 2025
-
-
Matthew Pickering authored
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
-
- Mar 06, 2025
-
-
-
-
-
Matthew Pickering authored
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.
-
Matthew Pickering authored
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.
-
- Mar 05, 2025
-
-
Fixes #25799
-
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
-
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.
-
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.
-
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.
-
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.
-
`@...@` syntax doesn't seem to work in synposes and is just kept by Haddock verbatim.
-
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
-
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)
-
- Mar 04, 2025
-
-
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.
-
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.
-
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
-
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.
-
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.
-
- Mar 03, 2025
-
-
Cheng Shao authored
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.
-
Cheng Shao authored
This commit updates wasm backend documentation to reflect the new JSFFI sync exports feature.
-
Cheng Shao authored
This commit repurposes some existing JSFFI test cases to make them cover JSFFI sync exports as well.
-
Cheng Shao authored
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)
-
Cheng Shao authored
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.
-
Cheng Shao authored
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.
-
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 -------------------------
-
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)
-
Since bd82ac9f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS.
-
- Mar 01, 2025
-
-
Fixes #25771
-
As noted in #25793, this is necessary due to potential ambiguity on Apple machines with Rosetta.
-
-
- Feb 28, 2025
-
-
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...).
-
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
-
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.
-