[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: DmdAnal: Make `prompt#` lazy (#25439)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Nov 13 20:53:09 UTC 2024



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
00d58ae1 by Sebastian Graf at 2024-11-13T15:21:23-05:00
DmdAnal: Make `prompt#` lazy (#25439)

This applies the same treatment to `prompt#` as for `catch#`.
See `Note [Strictness for mask/unmask/catch/prompt]`.

Fixes #25439.

- - - - -
93233a66 by Ben Gamari at 2024-11-13T15:21:59-05:00
boot: Do not attempt to update config.sub

While Apple ARM hardware was new we found that the autoconf scripts
included in some boot packages were too old. As a mitigation for this,
we introduced logic in the `boot` script to update the `config.sub`
with that from the GHC tree. However, this causes submodules which
have `config.sub` committted to appear to be dirty. This is a
considerable headache.

Now since `config.sub` with full platform support is more common we can
remove `boot`'s `config.sub` logic.

Fixes #19574.

- - - - -
330f3301 by Ryan Scott at 2024-11-13T15:52:54-05:00
Add regression test for #16234

Issue #16234 was likely fixed by !9765. This adds a regression test to ensure
that it remains fixed.

Fixes #16234.

- - - - -
ea9e0879 by Cheng Shao at 2024-11-13T15:52:55-05:00
misc: improve clangd compile_flags.txt flags

This patch improves the compile_flags.txt config used to power clangd
for the rts C codebase. The flags in the file are sampled & deduped
from a real stage1 build with clang-19 and vastly improves the IDE
accuracy when hacking the rts.

For maximum code coverage under the default settings,
compile_flags.txt defaults to threaded+profiled+dynamic+debug way.
This does not mean profdyn needs to be actually built in _build/stage1
for IDE to work. To activate IDE for other RTS ways, simply remove one
of the -D flags at the end of compile_flags.txt and restart clangd.

- - - - -
40e356c1 by Cheng Shao at 2024-11-13T15:52:55-05:00
testsuite: add regression test T25473

This commit adds regression test T25473 marked as broken due to #25473.
It will be fixed in the subsequent commit.

- - - - -
58c591e4 by Cheng Shao at 2024-11-13T15:52:55-05:00
wasm: fix foreign import javascript "wrapper" in TH/ghci

This patch fixes foreign import javascript "wrapper" in wasm backend's
TH/ghci by fixing the handling of dyld/finalization_registry magic
variables. Fixes T25473 and closes #25473.

- - - - -


21 changed files:

- boot
- compile_flags.txt
- compiler/GHC/Builtin/primops.txt.pp
- libraries/ghci/GHCi/ObjLink.hs
- + testsuite/tests/dmdanal/should_run/T25439.hs
- + testsuite/tests/dmdanal/should_run/T25439.stdout
- testsuite/tests/dmdanal/should_run/all.T
- + testsuite/tests/th/wasm/T25473A.hs
- + testsuite/tests/th/wasm/T25473B.hs
- + testsuite/tests/th/wasm/all.T
- + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClasses.hs
- + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesCore.hs
- + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesEffects.hs
- + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesReader.hs
- + testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesState.hs
- + testsuite/tests/typecheck/should_compile/T16234/ControlMonadPrimitive.hs
- + testsuite/tests/typecheck/should_compile/T16234/DataPeano.hs
- + testsuite/tests/typecheck/should_compile/T16234/Main.hs
- + testsuite/tests/typecheck/should_compile/T16234/Makefile
- + testsuite/tests/typecheck/should_compile/T16234/all.T
- utils/jsffi/dyld.mjs


Changes:

=====================================
boot
=====================================
@@ -66,9 +66,6 @@ def autoreconf():
     for dir_ in ['.', 'rts'] + glob.glob('libraries/*/'):
         if os.path.isfile(os.path.join(dir_, 'configure.ac')):
             print("Booting %s" % dir_)
-            # Update config.sub in submodules
-            if dir_ != '.' and os.path.isfile(os.path.join(dir_, 'config.sub')):
-                shutil.copyfile('config.sub', os.path.join(dir_, 'config.sub'))
             processes[dir_] = subprocess.Popen(['sh', '-c', reconf_cmd], cwd=dir_)
 
     # Wait for all child processes to finish.


=====================================
compile_flags.txt
=====================================
@@ -1,5 +1,29 @@
--xc
--Irts
+-Wimplicit
+-include
+rts/include/ghcversion.h
 -Irts/include
--I.hie-bios/stage0/lib
--I_build/stage1/rts/build/include/
+-I_build/stage1/rts/build
+-I_build/stage1/rts/build/include
+-Irts
+-Ilibraries/ghc-internal/include
+-I_build/stage1/libraries/ghc-internal/build/include
+-Ilibraries/ghc-bignum/include
+-I_build/stage1/libraries/ghc-bignum/build/include
+-Wno-unknown-pragmas
+-Wall
+-Wextra
+-Wstrict-prototypes
+-Wmissing-prototypes
+-Wmissing-declarations
+-Winline
+-Wpointer-arith
+-Wmissing-noreturn
+-Wnested-externs
+-Wredundant-decls
+-Wundef
+-DFS_NAMESPACE=rts
+-DCOMPILING_RTS
+-DTHREADED_RTS
+-DDEBUG
+-DDYNAMIC
+-DPROFILING


=====================================
compiler/GHC/Builtin/primops.txt.pp
=====================================
@@ -2663,18 +2663,45 @@ primop  CasMutVarOp "casMutVar#" GenPrimOp
 section "Exceptions"
 ------------------------------------------------------------------------
 
--- Note [Strictness for mask/unmask/catch]
--- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- Note [Strict IO wrappers]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~
 -- Consider this example, which comes from GHC.IO.Handle.Internals:
---    wantReadableHandle3 f ma b st
+--    wantReadableHandle3 f mv b st
 --      = case ... of
---          DEFAULT -> case ma of MVar a -> ...
---          0#      -> maskAsyncExceptions# (\st -> case ma of MVar a -> ...)
+--          DEFAULT -> case mv of MVar a -> ...
+--          0#      -> maskAsyncExceptions# (\st -> case mv of MVar a -> ...)
 -- The outer case just decides whether to mask exceptions, but we don't want
--- thereby to hide the strictness in 'ma'!  Hence the use of strictOnceApply1Dmd
--- in mask and unmask. But catch really is lazy in its first argument, see
--- #11555. So for IO actions 'ma' we often use a wrapper around it that is
--- head-strict in 'ma': GHC.IO.catchException.
+-- thereby to hide the strictness in `mv`!  Hence the use of strictOnceApply1Dmd
+-- in mask#, unmask# and atomically# (where we use strictManyApply1Dmd to respect
+-- that it potentially calls its action multiple times).
+--
+-- Note [Strictness for catch-style primops]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- The catch#-style primops always call their action, just like outlined
+-- in Note [Strict IO wrappers].
+-- However, it is important that we give their first arg lazyApply1Dmd and not
+-- strictOnceApply1Dmd, like for mask#. Here is why. Consider a call
+--
+--   catch# act handler s
+--
+-- If `act = raiseIO# ...`, using strictOnceApply1Dmd for `act` would mean that
+-- the call forwards the dead-end flag from `act` (see Note [Dead ends] and
+-- Note [Precise exceptions and strictness analysis]).
+-- This would cause dead code elimination to discard the continuation of the
+-- catch# call, among other things. This first came up in #11555.
+--
+-- Hence catch# uses lazyApply1Dmd in order /not/ to forward the dead-end flag
+-- from `act`. (This is a bit brutal, but the language of strictness types is
+-- not expressive enough to give it a more precise semantics that is still
+-- sound.)
+-- For perf reasons we often (but not always) choose to use a wrapper around
+-- catch# that is head-strict in `act`: GHC.IO.catchException.
+--
+-- A similar caveat applies to prompt#, which can be seen as a
+-- generalisation of catch# as explained in GHC.Prim#continuations#.
+-- The reason is that even if `act` appears dead-ending (e.g., looping)
+-- `prompt# tag ma s` might return alright due to a (higher-order) use of
+-- `control0#` in `act`. This came up in #25439.
 
 primop  CatchOp "catch#" GenPrimOp
           (State# RealWorld -> (# State# RealWorld, a_reppoly #) )
@@ -2691,7 +2718,7 @@ primop  CatchOp "catch#" GenPrimOp
    strictness  = { \ _arity -> mkClosedDmdSig [ lazyApply1Dmd
                                                  , lazyApply2Dmd
                                                  , topDmd] topDiv }
-                 -- See Note [Strictness for mask/unmask/catch]
+                 -- See Note [Strictness for catch-style primops]
    out_of_line = True
    effect = ReadWriteEffect
    -- Either inner computation might potentially raise an unchecked exception,
@@ -2757,7 +2784,7 @@ primop  MaskAsyncExceptionsOp "maskAsyncExceptions#" GenPrimOp
      in continuation-style primops\" for details. }
    with
    strictness  = { \ _arity -> mkClosedDmdSig [strictOnceApply1Dmd,topDmd] topDiv }
-                 -- See Note [Strictness for mask/unmask/catch]
+                 -- See Note [Strict IO wrappers]
    out_of_line = True
    effect = ReadWriteEffect
 
@@ -2772,6 +2799,7 @@ primop  MaskUninterruptibleOp "maskUninterruptible#" GenPrimOp
      in continuation-style primops\" for details. }
    with
    strictness  = { \ _arity -> mkClosedDmdSig [strictOnceApply1Dmd,topDmd] topDiv }
+                 -- See Note [Strict IO wrappers]
    out_of_line = True
    effect = ReadWriteEffect
 
@@ -2786,7 +2814,7 @@ primop  UnmaskAsyncExceptionsOp "unmaskAsyncExceptions#" GenPrimOp
      in continuation-style primops\" for details. }
    with
    strictness  = { \ _arity -> mkClosedDmdSig [strictOnceApply1Dmd,topDmd] topDiv }
-                 -- See Note [Strictness for mask/unmask/catch]
+                 -- See Note [Strict IO wrappers]
    out_of_line = True
    effect = ReadWriteEffect
 
@@ -2972,7 +3000,8 @@ primop  PromptOp "prompt#" GenPrimOp
      -> State# RealWorld -> (# State# RealWorld, a #)
    { See "GHC.Prim#continuations". }
    with
-   strictness = { \ _arity -> mkClosedDmdSig [topDmd, strictOnceApply1Dmd, topDmd] topDiv }
+   strictness = { \ _arity -> mkClosedDmdSig [topDmd, lazyApply1Dmd, topDmd] topDiv }
+                 -- See Note [Strictness for catch-style primops]
    out_of_line = True
    effect = ReadWriteEffect
 
@@ -3000,7 +3029,7 @@ primop  AtomicallyOp "atomically#" GenPrimOp
    -> State# RealWorld -> (# State# RealWorld, a_levpoly #)
    with
    strictness  = { \ _arity -> mkClosedDmdSig [strictManyApply1Dmd,topDmd] topDiv }
-                 -- See Note [Strictness for mask/unmask/catch]
+                 -- See Note [Strict IO wrappers]
    out_of_line = True
    effect = ReadWriteEffect
 
@@ -3029,7 +3058,7 @@ primop  CatchRetryOp "catchRetry#" GenPrimOp
    strictness  = { \ _arity -> mkClosedDmdSig [ lazyApply1Dmd
                                                  , lazyApply1Dmd
                                                  , topDmd ] topDiv }
-                 -- See Note [Strictness for mask/unmask/catch]
+                 -- See Note [Strictness for catch-style primops]
    out_of_line = True
    effect = ReadWriteEffect
 
@@ -3041,7 +3070,7 @@ primop  CatchSTMOp "catchSTM#" GenPrimOp
    strictness  = { \ _arity -> mkClosedDmdSig [ lazyApply1Dmd
                                                  , lazyApply2Dmd
                                                  , topDmd ] topDiv }
-                 -- See Note [Strictness for mask/unmask/catch]
+                 -- See Note [Strictness for catch-style primops]
    out_of_line = True
    effect = ReadWriteEffect
 
@@ -3731,6 +3760,7 @@ primop KeepAliveOp "keepAlive#" GenPrimOp
    with
    out_of_line = True
    strictness = { \ _arity -> mkClosedDmdSig [topDmd, topDmd, strictOnceApply1Dmd] topDiv }
+                 -- See Note [Strict IO wrappers]
    effect = ReadWriteEffect
    -- The invoked computation may have side effects
 


=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -76,7 +76,7 @@ loadDLL f =
       evaluate =<< js_loadDLL (toJSString f)
       pure $ Right nullPtr
 
-foreign import javascript safe "__exports.__dyld.loadDLL($1)"
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLL($1)"
   js_loadDLL :: JSString -> IO ()
 
 loadArchive :: String -> IO ()
@@ -96,7 +96,7 @@ lookupSymbol sym = do
   r <- js_lookupSymbol $ toJSString sym
   evaluate $ if r == nullPtr then Nothing else Just r
 
-foreign import javascript unsafe "__exports.__dyld.lookupSymbol($1)"
+foreign import javascript unsafe "__ghc_wasm_jsffi_dyld.lookupSymbol($1)"
   js_lookupSymbol :: JSString -> IO (Ptr a)
 
 lookupSymbolInDLL :: Ptr LoadedDLL -> String -> IO (Maybe (Ptr a))
@@ -114,7 +114,7 @@ addLibrarySearchPath p = do
   evaluate =<< js_addLibrarySearchPath (toJSString p)
   pure nullPtr
 
-foreign import javascript safe "__exports.__dyld.addLibrarySearchPath($1)"
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.addLibrarySearchPath($1)"
   js_addLibrarySearchPath :: JSString -> IO ()
 
 removeLibrarySearchPath :: Ptr () -> IO Bool
@@ -128,7 +128,7 @@ findSystemLibrary f = m `catch` \(_ :: JSException) -> pure Nothing
       p <- evaluate $ fromJSString p'
       pure $ Just p
 
-foreign import javascript safe "__exports.__dyld.findSystemLibrary($1)"
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.findSystemLibrary($1)"
   js_findSystemLibrary :: JSString -> IO JSString
 
 #else


=====================================
testsuite/tests/dmdanal/should_run/T25439.hs
=====================================
@@ -0,0 +1,25 @@
+{-# LANGUAGE MagicHash, UnboxedTuples, BlockArguments #-}
+
+import Prelude hiding (break)
+import GHC.Exts (PromptTag#, newPromptTag#, prompt#, control0#)
+import GHC.IO (IO(..), unIO)
+import Control.Monad (forever)
+
+main :: IO ()
+main = do
+  putStrLn "before"
+  broken >>= putStrLn
+  putStrLn "after"
+
+broken :: IO String
+broken = do
+  loop \l -> do
+    break l "broken"
+
+{-# NOINLINE loop #-}
+loop :: (PromptTag# a -> IO ()) -> IO a
+loop f = IO \rw0 -> case newPromptTag# rw0 of
+  (# rw1, tag #) -> prompt# tag (unIO (forever (f tag))) rw1
+
+break :: PromptTag# a -> a -> IO b
+break tag x = IO (control0# tag \_ rw1 -> (# rw1, x #))


=====================================
testsuite/tests/dmdanal/should_run/T25439.stdout
=====================================
@@ -0,0 +1,3 @@
+before
+broken
+after


=====================================
testsuite/tests/dmdanal/should_run/all.T
=====================================
@@ -33,3 +33,4 @@ test('T22475b', normal, compile_and_run, [''])
 # T22549: Do not strictify DFuns, otherwise we will <<loop>>
 test('T22549', normal, compile_and_run, ['-fdicts-strict -fno-specialise'])
 test('T23208', exit_code(1), multimod_compile_and_run, ['T23208_Lib', 'T23208'])
+test('T25439', normal, compile_and_run, [''])


=====================================
testsuite/tests/th/wasm/T25473A.hs
=====================================
@@ -0,0 +1,8 @@
+module T25473A where
+
+import GHC.Wasm.Prim
+
+type BinOp a = a -> a -> a
+
+foreign import javascript "wrapper"
+  mkJSBinOp :: BinOp Int -> IO JSVal


=====================================
testsuite/tests/th/wasm/T25473B.hs
=====================================
@@ -0,0 +1,10 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T25473B where
+
+import Language.Haskell.TH
+import T25473A
+
+$(runIO $ do
+  _ <- mkJSBinOp (+)
+  pure [])


=====================================
testsuite/tests/th/wasm/all.T
=====================================
@@ -0,0 +1,5 @@
+setTestOpts([
+  unless(arch('wasm32'), skip)
+])
+
+test('T25473', [], multimod_compile, ['T25473B', '-v0'])


=====================================
testsuite/tests/typecheck/should_compile/T16234/ControlMonadClasses.hs
=====================================
@@ -0,0 +1,7 @@
+module ControlMonadClasses
+  ( -- * Reader
+    MonadReader
+  ) where
+
+import ControlMonadClassesReader
+import ControlMonadClassesState ()


=====================================
testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesCore.hs
=====================================
@@ -0,0 +1,23 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UndecidableInstances #-}
+module ControlMonadClassesCore where
+
+import Data.Kind (Type)
+import DataPeano
+
+type family CanDo (m :: Type -> Type) (eff :: k) :: Bool
+
+type family MapCanDo (eff :: k) (stack :: Type -> Type) :: [Bool] where
+  MapCanDo eff (t m) = CanDo (t m) eff ': MapCanDo eff m
+  MapCanDo eff m = '[ CanDo m eff ]
+
+type family FindTrue
+  (bs :: [Bool])
+  :: Peano
+  where
+  FindTrue ('True ': t) = 'Zero
+  FindTrue ('False ': t) = 'Succ (FindTrue t)
+
+type Find eff (m :: Type -> Type) =
+  FindTrue (MapCanDo eff m)


=====================================
testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesEffects.hs
=====================================
@@ -0,0 +1,5 @@
+module ControlMonadClassesEffects where
+
+import Data.Kind (Type)
+
+data EffReader (e :: Type)


=====================================
testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesReader.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+module ControlMonadClassesReader where
+
+import qualified Control.Monad.Trans.State.Lazy as SL
+import ControlMonadClassesCore
+import ControlMonadClassesEffects
+import Control.Monad.Trans.Class
+import Data.Kind (Type)
+import DataPeano
+
+class Monad m => MonadReaderN (n :: Peano) (r :: Type) m
+instance Monad m => MonadReaderN 'Zero r (SL.StateT r m)
+instance (MonadTrans t, Monad (t m), MonadReaderN n r m, Monad m)
+  => MonadReaderN ('Succ n) r (t m)
+
+type MonadReader e m = MonadReaderN (Find (EffReader e) m) e m


=====================================
testsuite/tests/typecheck/should_compile/T16234/ControlMonadClassesState.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+module ControlMonadClassesState where
+
+import qualified Control.Monad.Trans.State.Lazy as SL
+import ControlMonadClassesCore
+import ControlMonadClassesEffects
+
+type instance CanDo (SL.StateT s m) eff = StateCanDo s eff
+
+type family StateCanDo s eff where
+  StateCanDo s (EffReader s) = 'True
+  StateCanDo s eff = 'False


=====================================
testsuite/tests/typecheck/should_compile/T16234/ControlMonadPrimitive.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE TypeFamilies #-}
+module ControlMonadPrimitive (PrimMonad(..)) where
+
+import Control.Monad.Trans.State (StateT)
+
+class Monad m => PrimMonad m where
+  type PrimState m
+instance PrimMonad m => PrimMonad (StateT s m) where
+  type PrimState (StateT s m) = PrimState m


=====================================
testsuite/tests/typecheck/should_compile/T16234/DataPeano.hs
=====================================
@@ -0,0 +1,3 @@
+module DataPeano where
+
+data Peano = Zero | Succ Peano


=====================================
testsuite/tests/typecheck/should_compile/T16234/Main.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE TypeFamilies #-}
+module Main where
+
+import ControlMonadClasses (MonadReader)
+--import ControlMonadPrimitive ()
+import Control.Monad.Trans.State.Lazy (StateT)
+
+main :: (n ~ StateT () IO, MonadReader () n) => IO ()
+main = undefined


=====================================
testsuite/tests/typecheck/should_compile/T16234/Makefile
=====================================
@@ -0,0 +1,17 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+clean:
+	rm -f *.o *.hi
+
+T16234:
+	$(MAKE) -s --no-print-directory clean
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c DataPeano.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c ControlMonadPrimitive.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c ControlMonadClassesCore.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c ControlMonadClassesEffects.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c ControlMonadClassesReader.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c ControlMonadClassesState.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c ControlMonadClasses.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c Main.hs


=====================================
testsuite/tests/typecheck/should_compile/T16234/all.T
=====================================
@@ -0,0 +1 @@
+test('T16234', [extra_files(['DataPeano.hs', 'ControlMonadPrimitive.hs', 'ControlMonadClassesCore.hs', 'ControlMonadClassesEffects.hs', 'ControlMonadClassesReader.hs', 'ControlMonadClassesState.hs', 'ControlMonadClasses.hs', 'Main.hs'])], makefile_test, ['T16234'])


=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -293,9 +293,13 @@ class DyLD {
   #loadedSos = new Set();
 
   // Mapping from export names to export funcs. It's also passed as
-  // __exports in JSFFI code, hence the "memory" special field. __dyld
-  // is used by ghci to call into here.
-  exportFuncs = { memory: this.#memory, __dyld: this };
+  // __exports in JSFFI code, hence the "memory" special field.
+  exportFuncs = { memory: this.#memory };
+
+  // The FinalizationRegistry used by JSFFI.
+  #finalizationRegistry = new FinalizationRegistry((sp) =>
+    this.exportFuncs.rts_freeStablePtr(sp)
+  );
 
   // The GOT.func table.
   #gotFunc = {};
@@ -623,17 +627,22 @@ class DyLD {
 
       const mod = await modp;
 
-      // Fulfill the ghc_wasm_jsffi imports
+      // Fulfill the ghc_wasm_jsffi imports. Use new Function()
+      // instead of eval() to prevent bindings in this local scope to
+      // be accessed by JSFFI code snippets.
       Object.assign(
         import_obj.ghc_wasm_jsffi,
         new Function(
-          "return (__exports) => ({".concat(
+          "__exports",
+          "__ghc_wasm_jsffi_dyld",
+          "__ghc_wasm_jsffi_finalization_registry",
+          "return {".concat(
             ...parseSections(mod).map(
               (rec) => `${rec[0]}: ${parseRecord(rec)}, `
             ),
-            "});"
+            "};"
           )
-        )()(this.exportFuncs)
+        )(this.exportFuncs, this, this.#finalizationRegistry)
       );
 
       // Fulfill the rest of the imports



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a1da8094757146c215b86bbe029b65a34151154a...58c591e44e5bc22c151a9a5b08881c45cd44ffb0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a1da8094757146c215b86bbe029b65a34151154a...58c591e44e5bc22c151a9a5b08881c45cd44ffb0
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241113/a398768d/attachment-0001.html>


More information about the ghc-commits mailing list