- Mar 19, 2025
-
-
Needing to store multiplicity annotations on records triggered a refactoring of AST of data declarations: Moved HsBangTy and HsRecTy from HsType to HsTypeGhcPsExt, the extension of HsType during parsing, since they are only needed during parsing. New HsConDeclField that stores all source data shared by all constructor declaration fields: unpackedness, strictness, multiplicity, documentation and the type of the field. Merged HsMultAnn and HsArrowOf, so all multiplicity annotations share the same data type. HsBang was no longer needed as a separate type, and was inlined into HsSrcBang.
-
This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.B...
-
- Mar 13, 2025
-
-
A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure.
-
- Mar 12, 2025
-
-
It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705
-
-
- Mar 09, 2025
-
-
This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout.
-
- Mar 05, 2025
-
-
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.
-
`@...@` 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
-
- 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.
-
Since bd82ac9f when `GHC.Pack` was deleted, it is no longer used except for one function by the RTS.
-
- Feb 26, 2025
-
-
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
-
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.
-
GHCi.BreakArray.showBreakArray is not used anywhere, hence the housecleaning.
-
- Feb 25, 2025
-
- Feb 23, 2025
-
-
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.
-
- Feb 08, 2025
-
-
Addresses #25452. Addresses core-libraries-committee#305.
-
Addresses part of #25452. Addresses core-libraries-committee#305.
-
Addresses part of #25452. Addresses core-libraries-committee#305.
-
Addresses part of #25452. Addresses core-libraries-committee#305.
-
Addresses part of #25452. Addresses core-libraries-committee#305.
-
Addresses part of #25452. Addresses core-libraries-committee#305.
-
- Feb 06, 2025
-
-
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
-
- Jan 30, 2025
-
- Jan 29, 2025
-
-
Fixes #25615.
-
-
I accidentally dropped this in !13381 - closes #25614 See: - ea458779 (the 13381 commit) - Issue #25614
-
- Jan 25, 2025
-
-
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
-
- Jan 22, 2025
-
-
Vladislav Zavialov authored
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.
-
- Jan 13, 2025
-
-
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.
-
- Dec 30, 2024
-
-
- Dec 29, 2024
-
-
Also bump various submodules. (cherry picked from commit 6fc1fa3b) Bump base bound to 4.21 for GHC 9.12 (cherry picked from commit 473a201c) Bump binary submodule to 0.8.9.2 (cherry picked from commit 7199869a) (cherry picked from commit ec2f40b4) Bump exceptions submodule to 0.10.9 (cherry picked from commit f5b5d1dc) Bump file-io submodule to 0.1.4 (cherry picked from commit ba786681) bump os-string submodule to 2.0.6 (cherry picked from commit 3a7ffdbb) bump transformers submodule to 0.6.1.2 (cherry picked from commit 53b46fd4) Bump directory submodule to v1.3.9.0 (cherry picked from commit 27dc2664) Bump Win32 submodule to v2.14.1.0 (cherry picked from commit 80df8808) Bump filepath submodule to 1.5.3.0 (cherry picked from commit 29bfae2c) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 97b0dff2) Bump unix submodule to 2.8.6.0 (cherry picked from commit a1f56d6d) Bump os-string submodule to 2.0.8 (cherry picked from commit 0121b76f) Bump file-io submodule to avoid usage of QuasiQuotes (cherry picked from commit 962ceb50) Bump filepath submodule to 1.5.4.0 (cherry picked from commit 7bc6877f) Bump file-io submodule to 0.1.5 (cherry picked from commit 9478b5ae) Bump Cabal submodule to 3.14.1.0 (cherry picked from commit 5c9c3e3f) Bump directory submodule to 0.12.2.0 (cherry picked from commit 89790626) Bump array submodule for base bump Bump stm submodule for base bump Bump process submodule for base bump
- Dec 27, 2024
-
-
Sergey Vinokurov authored
-
Sergey Vinokurov authored
The Monad instance shouldn't produce the outer :| unless f a reduces to WHNF. (Notice that the b :| bs match is implicitly lazy.)
-
Sergey Vinokurov authored
-
Sergey Vinokurov authored
Implementation of https://github.com/haskell/core-libraries-committee/issues/107
-