From a834b03d80b64c4fa2243fd6c4640dfea21acc12 Mon Sep 17 00:00:00 2001
From: Cheng Shao <terrorjack@type.dance>
Date: Mon, 24 Feb 2025 14:12:06 +0000
Subject: [PATCH] ghc-experimental: make JSVal abstract in GHC.Wasm.Prim

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.

(cherry picked from commit 8037f487ff1721973737b01e29136c671fd25157)
---
 libraries/ghc-experimental/src/GHC/Wasm/Prim.hs | 3 +--
 testsuite/tests/jsffi/jsffigc.hs                | 2 +-
 2 files changed, 2 insertions(+), 3 deletions(-)

diff --git a/libraries/ghc-experimental/src/GHC/Wasm/Prim.hs b/libraries/ghc-experimental/src/GHC/Wasm/Prim.hs
index 4bded6b3cab..0e90fce0560 100644
--- a/libraries/ghc-experimental/src/GHC/Wasm/Prim.hs
+++ b/libraries/ghc-experimental/src/GHC/Wasm/Prim.hs
@@ -2,7 +2,7 @@
 
 module GHC.Wasm.Prim (
   -- User-facing JSVal type and freeJSVal
-  JSVal (..),
+  JSVal,
   freeJSVal,
 
   -- The JSString type and conversion from/to Haskell String
@@ -20,4 +20,3 @@ module GHC.Wasm.Prim (
 ) where
 
 import GHC.Internal.Wasm.Prim
-
diff --git a/testsuite/tests/jsffi/jsffigc.hs b/testsuite/tests/jsffi/jsffigc.hs
index 1ad8ebe6ed9..a7427cad17c 100644
--- a/testsuite/tests/jsffi/jsffigc.hs
+++ b/testsuite/tests/jsffi/jsffigc.hs
@@ -4,7 +4,7 @@ module Test where
 
 import Data.Maybe
 import GHC.Exts
-import GHC.Wasm.Prim
+import GHC.Internal.Wasm.Prim
 import GHC.Weak
 import System.Mem
 
-- 
GitLab