Skip to content
Snippets Groups Projects
  1. Mar 26, 2025
  2. Mar 25, 2025
    • Cheng Shao's avatar
      wasm: add brotli compression for ghci browser mode · 731217ce
      Cheng Shao authored
      This commit adds brotli compression for wasm shared libraries for ghci
      browser mode. With BROTLI_MIN_QUALITY, the overhead is negligible, and
      it helps reducing amount of transferred data when the browser connects
      to the server over a slow connection.
      731217ce
    • Cheng Shao's avatar
      wasm: support wasi console redirect for the ghci browser mode · ad7e271d
      Cheng Shao authored
      This commit adds optional support for redirecting wasi console
      stdout/stderr back to the host when running wasm ghci browser mode. By
      default, the wasi console outputs are only available under F12
      devtools console, but in case of testing against a mobile browser, the
      devtools console may not be readily available, and it would be more
      convenient to at least get wasi console output on the host side.
      
      The redirection logic is simple, just adding another two WebSockets
      connections that pump the line-buffered textual messages back to
      host.
      ad7e271d
    • Cheng Shao's avatar
      wasm: add puppeteer/playwright support for ghci browser mode · fc576798
      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.
      fc576798
    • Cheng Shao's avatar
      wasm: implement wasm ghci browser mode · e93fc33d
      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.
      e93fc33d
    • Cheng Shao's avatar
      wasm: isolate dyld side effects that might require IPC · 22ba2a78
      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.
      22ba2a78
    • Cheng Shao's avatar
      wasm: isolate nodejs-specific logic with the isNode flag in dyld · 7003a399
      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.
      7003a399
    • Cheng Shao's avatar
      wasm: fix dyld downsweep filepath handling in browser · d9b71e82
      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.
      d9b71e82
    • Cheng Shao's avatar
      wasm: fix dyld setImmediate usage in browser · 9a697181
      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.
      9a697181
    • Cheng Shao's avatar
      wasm: asyncify the dylink.0 custom section parser · 929df0ba
      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.
      929df0ba
    • Cheng Shao's avatar
      wasm: use console.assert in dyld script · 27bb73c6
      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.
      27bb73c6
    • Cheng Shao's avatar
      wasm: fix post-link.mjs for browser · efcebed6
      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.
      efcebed6
    • Cheng Shao's avatar
      ghci: fix ^C handling for wasm iserv · fa2fbd2b
      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.
      fa2fbd2b
    • Cheng Shao's avatar
      ghci: use improved Pipe logic for wasm iserv · a2103fd2
      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.
      a2103fd2
    • Cheng Shao's avatar
      ghci: make the Pipe type opaque · 7d18c19b
      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.
      7d18c19b
    • Ben Gamari's avatar
      rel_eng/upload: Clarify usage directions · cd9e6605
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Previously it was not made clear that the directory name is significant.
      cd9e6605
    • jeffrey young's avatar
      base: construct compat GHC.Stats · 730e6f77
      jeffrey young authored and jeffrey young's avatar jeffrey young committed
      -- see CLC #289
      730e6f77
    • jeffrey young's avatar
      base: construct compat RTSFlags · 6941c825
      jeffrey young authored and jeffrey young's avatar jeffrey young committed
      -- see CLC #289
      6941c825
  3. Mar 24, 2025
  4. Mar 22, 2025
    • Alan Zimmerman's avatar
      EPA: Fix exact printing of SPECIALISE pragma · 3bc507db
      Alan Zimmerman authored and Marge Bot's avatar Marge Bot committed
      This commit fixes two minor issues with exactprinting of the
      SPECIALISE pragma after !12319 landed
      
      - The span for the RHS did not include the optional signature type
      - The `::` was printed twice when the legacy path was used
      
      Closes #25885
      3bc507db
    • Teo Camarasu's avatar
      template-haskell: remove Language.Haskell.TH.Lib.Internal · 1745c749
      Teo Camarasu authored and Marge Bot's avatar Marge Bot committed
      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
      1745c749
  5. Mar 21, 2025
  6. Mar 20, 2025
    • Bodigrim's avatar
      Improve haddock-visible documentation for GHC.Driver.Flags · 47646ce2
      Bodigrim authored and Marge Bot's avatar Marge Bot committed
      47646ce2
    • sheaf's avatar
      Don't cache solved [W] HasCallStack constraints · 256ac29c
      sheaf authored and Marge Bot's avatar Marge Bot committed
      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.
      256ac29c
    • Cheng Shao's avatar
      testsuite: mark T7919 as fragile on i386 as well · a8f543a9
      Cheng Shao authored and Marge Bot's avatar Marge Bot committed
      T7919 may also fail i386 CI jobs with test timeout.
      a8f543a9
    • sheaf's avatar
      Reject instance with non-class head in renamer · 75c29aa1
      sheaf authored and Marge Bot's avatar Marge Bot committed
      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
      75c29aa1
    • sheaf's avatar
      Remove SDocs from HsDocContext · 4329f3b6
      sheaf authored and Marge Bot's avatar Marge Bot committed
      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.
      4329f3b6
    • sheaf's avatar
      Remove SDoc from UnknownSubordinate/MissingBinding · 9003ef0a
      sheaf authored and Marge Bot's avatar Marge Bot committed
      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
      9003ef0a
    • Simon Peyton Jones's avatar
      Remove the Core flattener · 5d65393e
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      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
      5d65393e
  7. Mar 19, 2025
Loading