"README.md" did not exist on "a743761479ef0815975efb9a660b6c4b597c2e2f"
- Mar 25, 2025
-
-
Cheng Shao authored
This commit adds support for using puppeteer/playwright for automatically launching a headless browser that backs the ghci browser mode. This is useful for testing the ghci browser mode as a part of GHC testsuite, and it's also convenient for local development since the step to start iserv can be automated away.
-
Cheng Shao authored
This commit implements the rest of dyld logic that delivers the ghci browser mode: - The dyld script can now fully run in the browser. It communicates back with dyld-on-nodejs via WebSockets and also plain HTTP 1.1 requests. - The host dyld starts a server and acts as a broker between the GHC process and the browser side. GHC doesn't need to know anything about the browser mode; no driver flags need to be added and no recompilation needs to happen, the GHC driver continues to use the original iserv binary messages protocol. - The dyld broker doesn't need to parse any message between the browser dyld and GHC; it merely sets up WebSockets connections to redirect these messages as well as ^C signals. - Plain HTTP 1.1 is used for IPC requests (e.g. downloading a wasm module). - The dyld broker serves a main.js script that bootstraps iserv in the browser, and a main.html empty page playground for testing. CORS is enabled so it could be possible to inject iserv into other websites and use ghci to play with them. - All the RPC logic is opaque to the DyLD class, the majority of the wasm dynamic linker code is already portable and runs fine in firefox/chrome/webkit. Closes #25399.
-
Cheng Shao authored
This commit spins out a DyLDHost class from DyLD that handles side effects that must be run in the same host environment that runs wasm32-wasi-ghc. When the dyld script runs in the browser, it'll need to do IPC to find libraries, fetch wasm library, etc, and the other side of dyld that runs on nodejs would simply expose the DyLDHost methods as endpoints for WebSockets/HTTP.
-
Cheng Shao authored
As we move towards supporting running the dyld script in the browser, this commit implements the isNode module-level binding which is true if dyld is running in nodejs. The nodejs-specific bits are gated under isNode. For the browser case, this commit introduces @bjorn3/browser_wasi_shim as the wasi implementation; we already use it in quite a few projects and it simply works.
-
Cheng Shao authored
The wasm dyld downsweep logic used to rely on nodejs path module to handle filepaths. That's not available in browsers, so this commit implements poor man's filepath handling in js, which is not elegant for sure but works for both nodejs and the browser.
-
Cheng Shao authored
The wasm dyld script used to only run in node and directly uses setImmediate in globalThis. In case of browsers, it needs to import setImmediate from the prelude, hence this commit.
-
Cheng Shao authored
This commit refactors the simple binary parser in the dyld script in charge of parsing the dylink.0 custom section. Previously the parser was synchronous and operated on the entire input buffer; this was simple and easy and worked well enough when the input wasm modules are instantly read from local filesystem. However, when running dyld in the browser, the wasm modules are transferred via fetch() requests. The host ghc and the browser might not be on the same machine, so slow network uplink does need to be considered. We only need to parse dylink.0 custom section to extract dependency info, and dylink.0 is the very first custom section in the wasm shared library binary payload, so the parsing process should not require fetch() to complete and should return the parsing result asap. Hence the refactorings in this commit: asyncify the parser, make it only consume as many bytes as needed by invoking an async consumer callback. The input is a readable stream from the fetch() response; once the response is available, the async wasm compilation can start in the background, and dylink.0 parsing shall end asap which results in more wasm shared libraries to be loaded earlier. Profit.
-
Cheng Shao authored
This commit uses console.assert() instead of node-specific strict assert in the dyld script, in order to make it runnable in the browser. console.assert() only warns and doesn't crash upon assertion failure, but this is fine; we can always trivially define a strict assert function shall it be necessary when debugging, and there hasn't been such an assertion failure seen in the wild for long enough.
-
Cheng Shao authored
The wasm ghci browser mode needs to run dyld.mjs in the browser which imports post-link.mjs. This script makes post-link.mjs runnable in the browser by deferring node-specific module imports to their actual use sites.
-
Cheng Shao authored
This commit fixes ^C handling for wasm iserv. Previously we didn't handle it at all, so ^C would kill the node process and host ghc would then crash as well. But native ghc with external interpreter can handle ^C just fine and wasm should be no different. Hence the fix: wasm iserv exports its signal handler as a js callback to be handled by the dyld script. Also see added note for details.
-
Cheng Shao authored
This commit makes wasm iserv take advantage of the Pipe refactoring by passing binary receiver/sender js callbacks from the dyld script. This paves the way for piping the binary messages through WebSockets in order to run wasm iserv in the browser, but more importantly, it allows us to get rid of a horrible hack in the dyld script: we no longer have to fake magical wasi file descriptors that are backed by nodejs blocking I/O! The legacy hack was due to these facts: - iserv only supported exchanging binary messages via handles backed by file descriptors - In wasi you can't access host file descriptors passed by host ghc - The nodejs wasi implementation only allows mapping host directories into the wasi vfs, not host file descriptors - Named pipes with file paths (mkfifo) doesn't work well with nodejs wasi implementation, causes spurious testsuite failures on macos But starting from this point, we can fully take advantage of non-blocking I/O on the js side.
-
Cheng Shao authored
This commit makes the Pipe type in ghci opaque, and introduce the mkPipeFromHandles constructor for creating a Pipe from a pair of Handles. Pipe is now just a pair of receiver/sender continuations under the hood. This allows a Pipe to be potentially backed by other IPC mechanisms (e.g. WebSockets) which is essential for wasm ghci browser mode.
-
Previously it was not made clear that the directory name is significant.
-
-- see CLC #289
-
-- see CLC #289
-
- Mar 24, 2025
-
-
sheaf authored
This commit refactors the 'childGREPriority' function which is used when renaming subordinate items in export lists and class declarations. Instead of having a complicated LookupChild parameter, we now simply pass the GREInfo of the parent, which allows us to decide what is a valid child: - classes can have children that are in the type constructor namespace, - promoted data constructors should be treated the same as normal data constructors. Fixes #24027
- Mar 22, 2025
-
-
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 !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
- Mar 21, 2025
-
- Mar 20, 2025
-
-
This commit ensures we do not add solved Wanted constraints that mention HasCallStack or HasExceptionContext constraints to the set of solved Wanted dictionary constraints: caching them is invalid, because re-using such cached dictionaries means using an old call-stack instead of constructing a new one, as was reported in #25529. Fixes #25529.
-
T7919 may also fail i386 CI jobs with test timeout.
-
This commit modifies rnClsInstDecl so that, when renaming, we reject a class instance declaration in which the head is not a class. Before this change, it would get rejected in the type-checker, but that meant that the renamer could emit unhelpful error messages, e.g.: data Foo m a instance Foo m where fmap _ x = case x of would rather unhelpfully say: ‘fmap’ is not a (visible) method of class ‘Foo’ when of course 'Foo' is not even a class. We now reject the above program with the following error message: Illegal instance for data type ‘Foo’. Instance heads must be of the form C ty_1 ... ty_n where ‘C’ is a class. Fixes #22688
-
This commit removes the remaining SDocs from the HsDocContext data type. It adds the following constructors: ClassInstanceCtx -- Class instances ClassMethodSigCtx -- Class method signatures SpecialiseSigCtx -- SPECIALISE pragmas PatSynSigCtx -- Pattern synonym signatures We now report a bit more information for errors while renaming class instances, which slightly improves renamer-emitted error messages.
-
This commit replaces unstructured SDoc arguments in error message constructors with uses of the following two datatypes: - SigLike: for different kinds of signatures (e.g. standalone kind signatures, fixity signatures, COMPLETE pragmas, etc) - Subordinate: for class methods, associated types, and record fields The following error message constructors now no longer have any SDocs in them: - TcRnIllegalBuiltinSyntax: SDoc -> SigLike - MissingBinding: SDoc -> SigLike - UnknownSubordinate: SDoc -> (Name, Subordinate) - SuggestMoveToDeclarationSite: SDoc -> SigLike
-
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
- Mar 19, 2025
-
-
-
As with ghc-prim, it makes sense to have some protection against accidental interface changes to this package caused by changes in ghc-internal.
-
Ensure that GHC-driver builds default to mcmodel=medium, so that GHC passes this default parameter to CC without having to add it to the compiled project. Commit e70d4140 does not ensure that all GHC-built object files have a default model of medium, and will raise an R_LARCH_B26 overflow error.
-
As noted in #25838, previously `selectIOManager` failed to set `rts_IOManagerIsWin32Native` in its `IO_MNGR_FLAG_AUTO`. This meant that the MIO path was taken when WinIO was supposedly selected, resulting in chaos. Fixes #25838.
-
CentOS 7 is EoL and moreover we cannot even build images for it. See #25061.
-
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.
-
Fixes #25867. (Ben-raytrace being broken by library changes)
-
The new implementation generates correct code even if the registers overlap. Closes #25859
-
This also revealed that `readProcessEnvWithExitCode` and its local helpers were dead code.
-
This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work.
-
This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog,
-