Skip to content
Snippets Groups Projects
Commit 317a915b authored by Ben Gamari's avatar Ben Gamari
Browse files

Expose GHC.Wasm.Prim from ghc-experimental

Previously this was only exposed from `ghc-internal` which violates our
agreement that users shall not rely on things exposed from that package.

Fixes #24479.
parent 64150911
No related branches found
No related tags found
No related merge requests found
......@@ -165,7 +165,7 @@ types in JSFFI. Some caveats to keep in mind:
In addition to the above types, JSFFI supports the ``JSVal`` type and
its ``newtype``\ s as argument/result types. ``JSVal`` is defined in
``GHC.Wasm.Prim`` in ``ghc-internal``, which represents an opaque
``GHC.Wasm.Prim`` in ``ghc-experimental``, which represents an opaque
reference to a JavaScript value.
``JSVal``\ s are first-class Haskell values on the Haskell heap. You can
......
......@@ -23,6 +23,8 @@ common warnings
library
import: warnings
exposed-modules: GHC.Profiling.Eras
if arch(wasm32)
exposed-modules: GHC.Wasm.Prim
other-extensions:
build-depends: base ^>=4.19,
ghc-internal >= 0.1 && < 0.2
......
{-# LANGUAGE NoImplicitPrelude #-}
module GHC.Wasm.Prim (
-- User-facing JSVal type and freeJSVal
JSVal (..),
freeJSVal,
-- The JSString type and conversion from/to Haskell String
JSString (..),
fromJSString,
toJSString,
-- Exception types related to JSFFI
JSException (..),
WouldBlockException (..),
PromisePendingException (..),
-- Is JSFFI used in the current wasm module?
isJSFFIUsed
) where
import GHC.Internal.Wasm.Prim
......@@ -22,7 +22,7 @@ at all, so we can't pretend the old posix style polling works at all.
Since we can do JSFFI async imports now, it's super easy to implement
threadDelay using setTimeout() in JavaScript, and an implementation
has indeed been added in GHC.Wasm.Prim.Conc.Internal. But how do we
has indeed been added in GHC.Internal.Wasm.Prim.Conc.Internal. But how do we
make the user-facing GHC.Internal.Conc.IO.threadDelay switch to it in browser
environments and fall back to the stg_delay# implementation otherwise?
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment