[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED] Align CI scripts with master
by Sven Tennie (@supersven) 02 Nov '25
by Sven Tennie (@supersven) 02 Nov '25
02 Nov '25
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED at Glasgow Haskell Compiler / GHC
Commits:
a1992c60 by Sven Tennie at 2025-11-02T15:16:40+01:00
Align CI scripts with master
- - - - -
3 changed files:
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
Changes:
=====================================
.gitlab/ci.sh
=====================================
@@ -599,6 +599,20 @@ function install_bindist() {
*)
read -r -a args <<< "${INSTALL_CONFIGURE_ARGS:-}"
+ if [[ "${CROSS_TARGET:-no_cross_target}" =~ "mingw" ]]; then
+ # We suppose that host target = build target.
+ # By the fact above it is clearly turning out which host value is
+ # for currently built compiler.
+ # The fix for #21970 will probably remove this if-branch.
+ local -r CROSS_HOST_GUESS=$($SHELL ./config.guess)
+ args+=( "--target=$CROSS_TARGET" "--host=$CROSS_HOST_GUESS" )
+
+ # FIXME: The bindist configure script shouldn't need to be reminded of
+ # the target platform. See #21970.
+ elif [ -n "${CROSS_TARGET:-}" ]; then
+ args+=( "--target=$CROSS_TARGET" "--host=$CROSS_TARGET" )
+ fi
+
run ${CONFIGURE_WRAPPER:-} ./configure \
--prefix="$instdir" \
"${args[@]+"${args[@]}"}" || fail "bindist configure failed"
@@ -636,8 +650,28 @@ function test_hadrian() {
if [[ "${CROSS_EMULATOR:-}" == "NOT_SET" ]]; then
info "Cannot test cross-compiled build without CROSS_EMULATOR being set."
return
- # If we have set CROSS_EMULATOR, then can't test using normal testsuite.
- elif [ -n "${CROSS_EMULATOR:-}" ] && [[ "${CROSS_TARGET:-}" != *"wasm"* ]]; then
+ # special case for JS backend
+ elif [ -n "${CROSS_TARGET:-}" ] && [ "${CROSS_EMULATOR:-}" == "js-emulator" ]; then
+ # The JS backend doesn't support CROSS_EMULATOR logic yet
+ unset CROSS_EMULATOR
+ # run "hadrian test" directly, not using the bindist, even though it did get installed.
+ # This is a temporary solution, See !9515 for the status of hadrian support.
+ run_hadrian \
+ test \
+ --summary-junit=./junit.xml \
+ --test-have-intree-files \
+ --docs=none \
+ "runtest.opts+=${RUNTEST_ARGS:-}" \
+ "runtest.opts+=--unexpected-output-dir=$TOP/unexpected-test-output" \
+ || fail "cross-compiled hadrian main testsuite"
+ elif [[ -n "${CROSS_TARGET:-}" ]] && [[ "${CROSS_TARGET:-}" == *"wasm"* ]]; then
+ run_hadrian \
+ test \
+ --summary-junit=./junit.xml \
+ "runtest.opts+=${RUNTEST_ARGS:-}" \
+ "runtest.opts+=--unexpected-output-dir=$TOP/unexpected-test-output" \
+ || fail "hadrian main testsuite targetting $CROSS_TARGET"
+ elif [ -n "${CROSS_TARGET:-}" ]; then
local instdir="$TOP/_build/install"
local test_compiler="$instdir/bin/${cross_prefix}ghc$exe"
install_bindist _build/bindist/ghc-*/ "$instdir"
@@ -702,18 +736,11 @@ function test_hadrian() {
rm proftest.hs
fi
- # The check-exact check-ppr programs etc can not be built when testing a cross compiler.
- if [ -z "${CROSS_TARGET:-}" ]; then
- TEST_HAVE_INTREE="--test-have-intree-files"
- else
- TEST_HAVE_INTREE=""
- fi
-
run_hadrian \
test \
--summary-junit=./junit.xml \
+ --test-have-intree-files \
--test-compiler="${test_compiler}" \
- $TEST_HAVE_INTREE \
"runtest.opts+=${RUNTEST_ARGS:-}" \
"runtest.opts+=--unexpected-output-dir=$TOP/unexpected-test-output" \
|| fail "hadrian main testsuite"
=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -173,7 +173,7 @@ configureArgsStr :: BuildConfig -> String
configureArgsStr bc = unwords $
["--enable-unregisterised"| unregisterised bc ]
++ ["--disable-tables-next-to-code" | not (tablesNextToCode bc) ]
- ++ ["--with-intree-gmp" | Just _ <- [crossTarget bc] ]
+ ++ ["--with-intree-gmp" | Just _ <- pure (crossTarget bc) ]
++ ["--with-system-libffi" | crossTarget bc == Just "wasm32-wasi" ]
++ ["--enable-ipe-data-compression" | withZstd bc ]
++ ["--enable-strict-ghc-toolchain-check"]
@@ -1155,6 +1155,7 @@ debian_x86 =
]
where
validate_debian = Debian12
+
perfProfilingJob arch sys buildConfig =
-- Rename the job to avoid conflicts
rename (<> "-perf")
@@ -1278,7 +1279,7 @@ cross_jobs = [
(validateBuilds AArch64 (Linux Debian12Wine) (winAarch64Config {llvmBootstrap = True}))
]
where
- javascriptConfig = (crossConfig "javascript-unknown-ghcjs" NoEmulatorNeeded (Just "emconfigure"))
+ javascriptConfig = (crossConfig "javascript-unknown-ghcjs" (Emulator "js-emulator") (Just "emconfigure"))
{ bignumBackend = Native }
makeWinArmJobs = modifyJobs
@@ -1317,6 +1318,7 @@ cross_jobs = [
modifyJobs
( -- See Note [Testing wasm ghci browser mode]
setVariable "FIREFOX_LAUNCH_OPTS" "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}"
+ . setVariable "HADRIAN_ARGS" "--docs=no-sphinx-pdfs --docs=no-sphinx-man"
. delVariable "INSTALL_CONFIGURE_ARGS"
)
$ addValidateRule WasmBackend $ validateBuilds Amd64 (Linux AlpineWasm) cfg
=====================================
.gitlab/jobs.yaml
=====================================
@@ -1730,6 +1730,7 @@
"CROSS_STAGE": "2",
"CROSS_TARGET": "wasm32-wasi",
"FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
+ "HADRIAN_ARGS": "--docs=no-sphinx-pdfs --docs=no-sphinx-man",
"RUNTEST_ARGS": "",
"TEST_ENV": "x86_64-linux-alpine3_22-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
"XZ_OPT": "-9"
@@ -1795,6 +1796,7 @@
"CROSS_STAGE": "2",
"CROSS_TARGET": "wasm32-wasi",
"FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
+ "HADRIAN_ARGS": "--docs=no-sphinx-pdfs --docs=no-sphinx-man",
"RUNTEST_ARGS": "",
"TEST_ENV": "x86_64-linux-alpine3_22-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
"XZ_OPT": "-9"
@@ -1860,6 +1862,7 @@
"CROSS_STAGE": "2",
"CROSS_TARGET": "wasm32-wasi",
"FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
+ "HADRIAN_ARGS": "--docs=no-sphinx-pdfs --docs=no-sphinx-man",
"RUNTEST_ARGS": "",
"TEST_ENV": "x86_64-linux-alpine3_22-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
"XZ_OPT": "-9"
@@ -2115,6 +2118,7 @@
"BUILD_FLAVOUR": "validate",
"CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
"CONFIGURE_WRAPPER": "emconfigure",
+ "CROSS_EMULATOR": "js-emulator",
"CROSS_STAGE": "2",
"CROSS_TARGET": "javascript-unknown-ghcjs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
@@ -5839,6 +5843,7 @@
"CROSS_STAGE": "2",
"CROSS_TARGET": "wasm32-wasi",
"FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
+ "HADRIAN_ARGS": "--docs=no-sphinx-pdfs --docs=no-sphinx-man",
"RUNTEST_ARGS": "",
"TEST_ENV": "x86_64-linux-alpine3_22-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
}
@@ -5904,6 +5909,7 @@
"CROSS_STAGE": "2",
"CROSS_TARGET": "wasm32-wasi",
"FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
+ "HADRIAN_ARGS": "--docs=no-sphinx-pdfs --docs=no-sphinx-man",
"RUNTEST_ARGS": "",
"TEST_ENV": "x86_64-linux-alpine3_22-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
}
@@ -5969,6 +5975,7 @@
"CROSS_STAGE": "2",
"CROSS_TARGET": "wasm32-wasi",
"FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
+ "HADRIAN_ARGS": "--docs=no-sphinx-pdfs --docs=no-sphinx-man",
"RUNTEST_ARGS": "",
"TEST_ENV": "x86_64-linux-alpine3_22-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
}
@@ -6220,6 +6227,7 @@
"BUILD_FLAVOUR": "validate",
"CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
"CONFIGURE_WRAPPER": "emconfigure",
+ "CROSS_EMULATOR": "js-emulator",
"CROSS_STAGE": "2",
"CROSS_TARGET": "javascript-unknown-ghcjs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1992c60db33633c2d6d2e7d9242c55…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1992c60db33633c2d6d2e7d9242c55…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED] NOSMP has to be a C flag for RTS
by Sven Tennie (@supersven) 02 Nov '25
by Sven Tennie (@supersven) 02 Nov '25
02 Nov '25
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED at Glasgow Haskell Compiler / GHC
Commits:
23292e9b by Sven Tennie at 2025-11-02T12:14:18+01:00
NOSMP has to be a C flag for RTS
Otherwise building unregisterised fails. This is also in line with
master.
- - - - -
1 changed file:
- hadrian/src/Settings/Packages.hs
Changes:
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -323,7 +323,7 @@ rtsPackageArgs = package rts ? do
, "-optc-DTICKY_TICKY"]
, Profiling `wayUnit` way ? arg "-DPROFILING"
, Threaded `wayUnit` way ? arg "-DTHREADED_RTS"
- , notM (targetSupportsSMP stage) ? arg "-DNOSMP"
+ , notM (targetSupportsSMP stage) ? arg "-optc-DNOSMP"
-- See Note [AutoApply.cmm for vectors] in genapply/Main.hs
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/23292e9b8ae98a3119bfe3e5f2c0539…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/23292e9b8ae98a3119bfe3e5f2c0539…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/ani/kill-popErrCtxt] make add arg ctx print in the nth argument if the head of the application chain is user located
by Apoorv Ingle (@ani) 02 Nov '25
by Apoorv Ingle (@ani) 02 Nov '25
02 Nov '25
Apoorv Ingle pushed to branch wip/ani/kill-popErrCtxt at Glasgow Haskell Compiler / GHC
Commits:
cafe92c3 by Apoorv Ingle at 2025-11-01T23:53:11-05:00
make add arg ctx print in the nth argument if the head of the application chain is user located
- - - - -
2 changed files:
- compiler/GHC/Tc/Gen/App.hs
- testsuite/tests/rebindable/rebindable6.stderr
Changes:
=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -964,12 +964,13 @@ addArgCtxt arg_no (fun, fun_lspan) (L arg_loc arg) thing_inside
_ -> text "<USER>" <+> pprErrCtxtMsg y)
(take 4 (zip err_ctx err_ctx_msg)))
])
- ; if in_generated_code && isGeneratedSrcSpan fun_lspan
- then updCtxtForArg (L arg_loc arg) $
- thing_inside
- else do setSrcSpanA arg_loc $
- addErrCtxt (FunAppCtxt (FunAppCtxtExpr fun arg) arg_no) $
- thing_inside }
+ ; if not (isGeneratedSrcSpan fun_lspan)
+ then setSrcSpanA arg_loc $
+ addErrCtxt (FunAppCtxt (FunAppCtxtExpr fun arg) arg_no) $
+ thing_inside
+ else updCtxtForArg (L arg_loc arg) $
+ thing_inside
+ }
where
updCtxtForArg :: LHsExpr GhcRn -> TcRn a -> TcRn a
updCtxtForArg e@(L lspan _) thing_inside
=====================================
testsuite/tests/rebindable/rebindable6.stderr
=====================================
@@ -1,9 +1,8 @@
-
rebindable6.hs:110:17: error: [GHC-39999]
• Ambiguous type variable ‘t0’ arising from a do statement
prevents the constraint ‘(HasSeq
(IO a -> t0 -> IO b))’ from being solved.
- (maybe you haven't applied a function to enough arguments?)
+ (maybe you haven't applied a function to enough arguments?)
Relevant bindings include
g :: IO (Maybe b) (bound at rebindable6.hs:108:19)
f :: IO a (bound at rebindable6.hs:108:17)
@@ -28,7 +27,7 @@ rebindable6.hs:111:17: error: [GHC-39999]
• Ambiguous type variables ‘t1’, ‘t0’ arising from a do statement
prevents the constraint ‘(HasBind
(IO (Maybe b) -> (Maybe b -> t1) -> t0))’ from being solved.
- (maybe you haven't applied a function to enough arguments?)
+ (maybe you haven't applied a function to enough arguments?)
Relevant bindings include
g :: IO (Maybe b) (bound at rebindable6.hs:108:19)
test_do :: IO a -> IO (Maybe b) -> IO b
@@ -50,9 +49,9 @@ rebindable6.hs:111:17: error: [GHC-39999]
return b
rebindable6.hs:112:17: error: [GHC-39999]
- • Ambiguous type variable ‘t1’ arising from a use of ‘return’
+ • Ambiguous type variable ‘t1’ arising from a do statement
prevents the constraint ‘(HasReturn (b -> t1))’ from being solved.
- (maybe you haven't applied a function to enough arguments?)
+ (maybe you haven't applied a function to enough arguments?)
Relevant bindings include
b :: b (bound at rebindable6.hs:111:23)
g :: IO (Maybe b) (bound at rebindable6.hs:108:19)
@@ -71,3 +70,4 @@ rebindable6.hs:112:17: error: [GHC-39999]
= do f
Just (b :: b) <- g
return b
+
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cafe92c3eeba2b9a6b3195a2a7ddfa4…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cafe92c3eeba2b9a6b3195a2a7ddfa4…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] Supplant TcRnExportHiddenComponents with TcRnDodgyExports (#26534)
by Marge Bot (@marge-bot) 01 Nov '25
by Marge Bot (@marge-bot) 01 Nov '25
01 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
86c82745 by Vladislav Zavialov at 2025-11-01T07:24:29-04:00
Supplant TcRnExportHiddenComponents with TcRnDodgyExports (#26534)
Remove a bogus special case in lookup_ie_kids_all,
making TcRnExportHiddenComponents obsolete.
- - - - -
10 changed files:
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Types/Error/Codes.hs
- testsuite/tests/diagnostic-codes/codes.stdout
- + testsuite/tests/warnings/should_compile/DodgyExports02.hs
- + testsuite/tests/warnings/should_compile/DodgyExports02.stderr
- + testsuite/tests/warnings/should_compile/DodgyExports03.hs
- + testsuite/tests/warnings/should_compile/DodgyExports03.stderr
- testsuite/tests/warnings/should_compile/all.T
Changes:
=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -636,11 +636,6 @@ instance Diagnostic TcRnMessage where
$ formatExportItemError
(text "module" <+> ppr mod)
"is missing an export list"
- TcRnExportHiddenComponents export_item
- -> mkSimpleDecorated
- $ formatExportItemError
- (ppr export_item)
- "attempts to export constructors or class methods that are not visible here"
TcRnExportHiddenDefault export_item
-> mkSimpleDecorated
$ formatExportItemError
@@ -2231,8 +2226,6 @@ instance Diagnostic TcRnMessage where
-> WarningWithFlag Opt_WarnDodgyExports
TcRnMissingExportList{}
-> WarningWithFlag Opt_WarnMissingExportList
- TcRnExportHiddenComponents{}
- -> ErrorWithoutFlag
TcRnExportHiddenDefault{}
-> ErrorWithoutFlag
TcRnDuplicateExport{}
@@ -2904,8 +2897,6 @@ instance Diagnostic TcRnMessage where
-> noHints
TcRnMissingExportList{}
-> noHints
- TcRnExportHiddenComponents{}
- -> noHints
TcRnExportHiddenDefault{}
-> noHints
TcRnDuplicateExport{}
=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -1608,15 +1608,6 @@ data TcRnMessage where
-}
TcRnMissingExportList :: ModuleName -> TcRnMessage
- {-| TcRnExportHiddenComponents is an error that occurs when an export contains
- constructor or class methods that are not visible.
-
- Example(s): None
-
- Test cases: None
- -}
- TcRnExportHiddenComponents :: IE GhcPs -> TcRnMessage
-
{-| TcRnExportHiddenDefault is an error that occurs when an export contains
a class default (with language extension NamedDefaults) that is not visible.
=====================================
compiler/GHC/Tc/Gen/Export.hs
=====================================
@@ -526,7 +526,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
} (L loc ie@(IEThingAll (warn_txt_ps, ann) l doc))
= do mb_gre <- lookupGreAvailRn (ieLWrappedNameWhatLooking l) $ lieWrappedName l
for mb_gre $ \ par -> do
- all_kids <- lookup_ie_kids_all ie l par
+ all_kids <- lookup_ie_kids_all l par
let name = greName par
all_gres = par : all_kids
all_names = map greName all_gres
@@ -562,7 +562,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
wc_kids <-
case wc of
NoIEWildcard -> return []
- IEWildcard _ -> lookup_ie_kids_all ie l par
+ IEWildcard _ -> lookup_ie_kids_all l par
let name = greName par
all_kids = with_kids ++ wc_kids
@@ -595,20 +595,15 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
; kids <- lookupChildrenExport gre child_gres sub_rdrs
; return (unzip kids) }
- lookup_ie_kids_all :: IE GhcPs -> LIEWrappedName GhcPs -> GlobalRdrElt
+ lookup_ie_kids_all :: LIEWrappedName GhcPs -> GlobalRdrElt
-> RnM [GlobalRdrElt]
- lookup_ie_kids_all ie (L _loc rdr) gre =
+ lookup_ie_kids_all (L _loc rdr) gre =
do { let name = greName gre
gres = findChildren kids_env name
-- We only choose level 0 exports when filling in part of an export list implicitly.
; let kids_0 = mapMaybe pickLevelZeroGRE gres
; addUsedKids (ieWrappedName rdr) kids_0
- ; when (null kids_0) $
- if isTyConName name
- then addTcRnDiagnostic (TcRnDodgyExports gre)
- else -- This occurs when you export T(..), but
- -- only import T abstractly, or T is a synonym.
- addErr (TcRnExportHiddenComponents ie)
+ ; when (null kids_0) $ addTcRnDiagnostic (TcRnDodgyExports gre)
; return kids_0 }
-------------
=====================================
compiler/GHC/Types/Error/Codes.hs
=====================================
@@ -505,7 +505,7 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnExportedModNotImported" = 90973
GhcDiagnosticCode "TcRnNullExportedModule" = 64649
GhcDiagnosticCode "TcRnMissingExportList" = 85401
- GhcDiagnosticCode "TcRnExportHiddenComponents" = 94558
+ GhcDiagnosticCode "TcRnExportHiddenComponents" = Outdated 94558
GhcDiagnosticCode "TcRnExportHiddenDefault" = 74775
GhcDiagnosticCode "TcRnDuplicateExport" = 47854
GhcDiagnosticCode "TcRnDuplicateNamedDefaultExport" = 31584
=====================================
testsuite/tests/diagnostic-codes/codes.stdout
=====================================
@@ -50,7 +50,6 @@
[GHC-17268] is untested (constructor = TcRnCharLiteralOutOfRange)
[GHC-36495] is untested (constructor = TcRnTagToEnumMissingValArg)
[GHC-55868] is untested (constructor = TcRnArrowIfThenElsePredDependsOnResultTy)
-[GHC-94558] is untested (constructor = TcRnExportHiddenComponents)
[GHC-63055] is untested (constructor = TcRnFieldUpdateInvalidType)
[GHC-26133] is untested (constructor = TcRnForeignImportPrimSafeAnn)
[GHC-03355] is untested (constructor = TcRnIllegalForeignDeclBackend)
=====================================
testsuite/tests/warnings/should_compile/DodgyExports02.hs
=====================================
@@ -0,0 +1,7 @@
+module DodgyExports02
+ ( Identity(..) -- type constructor has out-of-scope children
+ , Void(..) -- type constructor has no children
+ ) where
+
+import Data.Void (Void)
+import Data.Functor.Identity (Identity)
=====================================
testsuite/tests/warnings/should_compile/DodgyExports02.stderr
=====================================
@@ -0,0 +1,10 @@
+DodgyExports02.hs:2:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
+ The export item ‘Identity(..)’ suggests that
+ ‘Identity’ has (in-scope) constructors or record fields,
+ but it has none
+
+DodgyExports02.hs:3:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
+ The export item ‘Void(..)’ suggests that
+ ‘Void’ has (in-scope) constructors or record fields,
+ but it has none
+
=====================================
testsuite/tests/warnings/should_compile/DodgyExports03.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE ExplicitNamespaces #-}
+
+module DodgyExports03
+ ( data MkR(..) -- data constructors never have children ('fld' belongs to 'R')
+ ) where
+
+data R = MkR { fld :: Int }
=====================================
testsuite/tests/warnings/should_compile/DodgyExports03.stderr
=====================================
@@ -0,0 +1,4 @@
+DodgyExports03.hs:4:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
+ The export item ‘MkR(..)’ suggests that
+ ‘MkR’ has children, but it is not a type constructor or a class
+
=====================================
testsuite/tests/warnings/should_compile/all.T
=====================================
@@ -54,6 +54,8 @@ test('T19564d', normal, compile, [''])
# Also, suppress uniques as one of the warnings is unstable in CI, otherwise.
test('T19296', normal, compile, ['-fdiagnostics-show-caret -Wredundant-constraints -dsuppress-uniques'])
test('DodgyExports01', normal, compile, ['-Wdodgy-exports'])
+test('DodgyExports02', normal, compile, ['-Wdodgy-exports'])
+test('DodgyExports03', normal, compile, ['-Wdodgy-exports'])
test('DerivingTypeable', normal, compile, ['-Wderiving-typeable'])
test('T18862a', normal, compile, [''])
test('T18862b', normal, compile, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/86c8274513318478b77d4286c2783ac…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/86c8274513318478b77d4286c2783ac…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] 5 commits: wasm: reformat dyld source code
by Marge Bot (@marge-bot) 01 Nov '25
by Marge Bot (@marge-bot) 01 Nov '25
01 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
f6961b02 by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: reformat dyld source code
This commit reformats dyld source code with prettier, to avoid
introducing unnecessary diffs in subsequent patches when they're
formatted before committing.
- - - - -
0c9032a0 by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: simplify _initialize logic in dyld
This commit simplifies how we _initialize a wasm shared library in
dyld and removes special treatment for libc.so, see added comment for
detailed explanation.
- - - - -
ec1b40bd by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: support running dyld fully client side in the browser
This commit refactors the wasm dyld script so that it can be used to
load and run wasm shared libraries fully client-side in the browser
without needing a wasm32-wasi-ghci backend:
- A new `DyLDBrowserHost` class is exported, which runs in the browser
and uses the in-memory vfs without any RPC calls. This meant to be
used to create a `rpc` object for the fully client side use cases.
- The exported `main` function now can be used to load user-specified
shared libraries, and the user can use the returned `DyLD` instance
to run their own exported Haskell functions.
- The in-browser wasi implementation is switched to
https://github.com/haskell-wasm/browser_wasi_shim for bugfixes and
major performance improvements not landed upstream yet.
- When being run by deno, it now correctly switches to non-nodejs code
paths, so it's more convenient to test dyld logic with deno.
See added comments for details, as well as the added `playground001`
test case for an example of using it to build an in-browser Haskell
playground.
- - - - -
8f3e481f by Cheng Shao at 2025-11-01T00:08:01+01:00
testsuite: add playground001 to test haskell playground
This commit adds the playground001 test case to test the haskell
playground in browser, see comments for details.
- - - - -
af40606a by Cheng Shao at 2025-11-01T00:08:04+01:00
Revert "testsuite: add T26431 test case"
This reverts commit 695036686f8c6d78611edf3ed627608d94def6b7. T26431
is now retired, wasm ghc internal-interpreter logic is tested by
playground001.
- - - - -
10 changed files:
- + testsuite/tests/ghc-api-browser/README.md
- + testsuite/tests/ghc-api-browser/all.T
- + testsuite/tests/ghc-api-browser/index.html
- + testsuite/tests/ghc-api-browser/playground001.hs
- + testsuite/tests/ghc-api-browser/playground001.js
- + testsuite/tests/ghc-api-browser/playground001.sh
- testsuite/tests/ghci-wasm/T26431.stdout → testsuite/tests/ghc-api-browser/playground001.stdout
- − testsuite/tests/ghci-wasm/T26431.hs
- testsuite/tests/ghci-wasm/all.T
- utils/jsffi/dyld.mjs
Changes:
=====================================
testsuite/tests/ghc-api-browser/README.md
=====================================
@@ -0,0 +1,124 @@
+# The Haskell playground browser test
+
+This directory contains the `playground001` test, which builds a fully
+client side Haskell playground in the browser, then runs a
+puppeteer-based test to actually interpret a Haskell program in a
+headless browser.
+
+## Headless testing
+
+`playground001` is tested in GHC CI. To test it locally, first ensure
+you've set up the latest
+[`ghc-wasm-meta`](https://gitlab.haskell.org/haskell-wasm/ghc-wasm-meta)
+toolchain and sourced the `~/.ghc-wasm/env` script, so the right
+`node` with the right pre-installed libraries are used. Additionally,
+you need to install latest Firefox and:
+
+```sh
+export FIREFOX_LAUNCH_OPTS='{"browser":"firefox","executablePath":"/usr/bin/firefox"}'`
+```
+
+Or on macOS:
+
+```sh
+export FIREFOX_LAUNCH_OPTS='{"browser":"firefox","executablePath":"/Applications/Firefox.app/Contents/MacOS/firefox"}'
+```
+
+Without `FIREFOX_LAUNCH_OPTS`, `playground001` is skipped.
+
+It's possible to test against Chrome as well, the
+[`playground001.js`](./playground001.js) test driver doesn't assume
+anything Firefox-specific, it just takes the
+[`puppeteer.launch`](https://pptr.dev/api/puppeteer.puppeteernode.launch)
+options as JSON passed via command line.
+
+`playground001` works on latest versions of Firefox/Chrome/Safari.
+
+## Manual testing
+
+The simplest way to build the playground manually and run it in a
+browser tab is to test it once with `--only=playground001
+--keep-test-files` passed to Hadrian, then you can find the temporary
+directory containing [`index.html`](./index.html), `rootfs.tar.zst`
+etc, then fire up a dev web server and load it.
+
+Additionally, you can build the playground in tree without invoking
+the GHC testsuite. Just build GHC with the wasm target first, then
+copy `utils/jsffi/*.mjs` here and run
+[`./playground001.sh`](./playground001.sh) script. You need to set
+`TEST_CC` to the path of `wasm32-wasi-clang` and `TEST_HC` to the path
+of `wasm32-wasi-ghc`, that's it.
+
+## Customized Haskell playground
+
+You may want to build a customized Haskell playground that uses GHC
+API to interpret Haskell code with custom packages, here are some tips
+to get started:
+
+- Read the code in this directory and figure out how `playground001`
+ itself works.
+- [`./playground001.sh`](./playground001.sh) can be used as a basis to
+ write your own build/test script.
+
+You don't need to read the full `dyld.mjs` script. The user-facing
+things that are relevant to the playground use case are:
+
+- `export class DyLDBrowserHost`: it is the `rpc` object required when
+ calling `main`. You need to pass `stdout`/`stderr` callbacks to
+ write each line of stdout/stderr, as well as a `rootfs` object that
+ represents an in-memory vfs containing the shared libraries to load.
+- `export async function main`: it eventually returns a `DyLD` object
+ that can be used like `await
+ dyld.exportFuncs.myExportedHaskellFunc(js_foo, js_bar)` to invoke
+ your exported Haskell function.
+
+Check the source code of [`index.html`](./index.html) and cross
+reference [`playground001.hs`](./playground001.hs) for the example of
+how they are used.
+
+The `rootfs` object is a
+[`PreopenDirectory`](https://github.com/haskell-wasm/browser_wasi_shim/blob/master/src/fs_mem.ts)
+object in the
+[`browser_wasi_shim`](https://github.com/haskell-wasm/browser_wasi_shim)
+library. The Haskell playground needs a complex vfs containing many
+files (shared libraries, interface files, package databases, etc), so
+to speed things up, the whole vfs is compressed into a
+`rootfs.tar.zst` archive, then that archive is extracted using
+[`bsdtar-wasm`](https://github.com/haskell-wasm/bsdtar-wasm).
+
+You don't need to read the source code of `browser_wasi_shim`; you can
+simply paste and adapt the relevant code snippet in
+[`index.html`](./index.html) to create the right `rootfs` object from
+a tarball.
+
+The main concern is what do you need to pack into `rootfs.tar.zst`.
+For `playground001`, it contains:
+
+- `/tmp/clib`: the C/C++ shared libraries
+- `/tmp/hslib/lib`: the GHC libdir
+- `/tmp/libplayground001.so`: the main shared library to start loading
+ that exports `myMain`
+
+You can read [`./playground001.sh`](./playground001.sh) to figure out
+the details of how I prepare `rootfs.tar.zst` and trim unneeded files
+to minimize the tarball size.
+
+There are multiple possible ways to install third-party packages in
+the playground:
+
+- Start from a `wasm32-wasi-ghc` installation, use `wasm32-wasi-cabal
+ v1-install --global` to install everything to the global package
+ database. In theory this is the simplest way, though I haven't tried
+ it myself and it's unclear to what extent do `v1` commands work
+ these days.
+- Use default nix-style installation, then package the cabal store and
+ `dist-newstyle` directories into `rootfs.tar.zst`, and pass the
+ right package database flags when calling GHC API.
+
+Note that cabal built packages are not relocatable! So things will
+break if you build them at a host location and then package into a
+different absolute path into the rootfs, keep this in mind.
+
+If you have any difficulties, you're welcome to the [Haskell
+Wasm](https://matrix.to/#/#haskell.wasm:matrix.org) matrix room for
+community support.
=====================================
testsuite/tests/ghc-api-browser/all.T
=====================================
@@ -0,0 +1,52 @@
+# makefile_test/run_command is skipped when config.target_wrapper is
+# not None, see test_common_work in testsuite/driver/testlib.py. for
+# now just use this workaround to run custom test script here; ideally
+# we'd fix test failures elsewhere and enable
+# makefile_test/run_command for cross targets some day.
+async def stub_run_command(name, way, cmd):
+ return await run_command(name, way, cmd)
+
+
+# config.target_wrapper is prepended when running any command when
+# testing a cross target, see simple_run in
+# testsuite/driver/testlib.py. this is problematic when running a host
+# test script. for now do this override; ideally we'd have clear
+# host/target distinction for command invocations in the testsuite
+# driver instead of just a command string.
+def override_target_wrapper(name, opts):
+ opts.target_wrapper = ""
+
+
+setTestOpts(
+ [
+ unless(arch("wasm32"), skip),
+ override_target_wrapper,
+ high_memory_usage,
+ ignore_stderr,
+ only_ways(["dyn"]),
+ extra_ways(["dyn"]),
+ ]
+)
+
+
+test(
+ "playground001",
+ [
+ # pretty heavyweight, just test one browser for now.
+ unless("FIREFOX_LAUNCH_OPTS" in ghc_env, skip),
+ extra_files(
+ [
+ "../../../.gitlab/hello.hs",
+ "../../../utils/jsffi/dyld.mjs",
+ "../../../utils/jsffi/post-link.mjs",
+ "../../../utils/jsffi/prelude.mjs",
+ "index.html",
+ "playground001.hs",
+ "playground001.js",
+ "playground001.sh",
+ ]
+ ),
+ ],
+ stub_run_command,
+ ['./playground001.sh "$FIREFOX_LAUNCH_OPTS"'],
+)
=====================================
testsuite/tests/ghc-api-browser/index.html
=====================================
@@ -0,0 +1,234 @@
+<!DOCTYPE html>
+<html lang="en">
+ <head>
+ <meta charset="utf-8" />
+ <meta name="viewport" content="width=device-width, initial-scale=1" />
+ <title>ghc-in-browser</title>
+ <link
+ rel="stylesheet"
+ href="https://cdn.jsdelivr.net/npm/modern-normalize/modern-normalize.min.css"
+ />
+ <style>
+ html,
+ body {
+ height: 100%;
+ }
+ body {
+ margin: 0;
+ font-family: system-ui, -apple-system, Segoe UI, Roboto, sans-serif;
+ background: #0f172a;
+ color: #e5e7eb;
+ }
+ .app {
+ height: 100vh;
+ display: grid;
+ gap: 0.5rem;
+ padding: 0.5rem;
+ }
+ @media (min-width: 800px) {
+ .app {
+ grid-template-columns: 1fr 1fr;
+ }
+ }
+ @media (max-width: 799.98px) {
+ .app {
+ grid-template-rows: 1fr 1fr;
+ }
+ }
+ .pane {
+ background: #111827;
+ border: 1px solid #1f2937;
+ border-radius: 12px;
+ display: flex;
+ flex-direction: column;
+ min-height: 0;
+ }
+ header {
+ padding: 0.5rem 0.75rem;
+ border-bottom: 1px solid #1f2937;
+ font-weight: 600;
+ }
+ #editor {
+ flex: 1;
+ min-height: 0;
+ }
+ .right {
+ padding: 0.6rem;
+ gap: 0.6rem;
+ }
+ .controls {
+ display: flex;
+ gap: 0.5rem;
+ flex-wrap: wrap;
+ margin-bottom: 0.4rem;
+ }
+ .controls input[type="text"] {
+ flex: 1;
+ min-width: 200px;
+ background: #0b1020;
+ color: #e5e7eb;
+ border: 1px solid #223;
+ border-radius: 8px;
+ padding: 0.55rem;
+ }
+ .controls button {
+ background: #22c55e;
+ border: none;
+ border-radius: 8px;
+ padding: 0.55rem 0.85rem;
+ font-weight: 600;
+ cursor: pointer;
+ }
+ .outputs {
+ display: block;
+ }
+ .outputs .label {
+ font-size: 0.85rem;
+ opacity: 0.8;
+ margin: 0.35rem 0;
+ }
+ .outputs textarea {
+ display: block;
+ width: 100%;
+ min-height: 30vh;
+ background: #0b1020;
+ color: #d1fae5;
+ border: 1px solid #223;
+ border-radius: 8px;
+ padding: 0.6rem;
+ resize: vertical;
+ }
+ .stderr {
+ color: #fee2e2;
+ }
+ </style>
+
+ <script async type="module">
+ import * as monaco from "https://cdn.jsdelivr.net/npm/monaco-editor/+esm";
+ import {
+ ConsoleStdout,
+ File,
+ OpenFile,
+ PreopenDirectory,
+ WASI,
+ } from "https://esm.sh/gh/haskell-wasm/browser_wasi_shim";
+ import { DyLDBrowserHost, main } from "./dyld.mjs";
+
+ const rootfs = new PreopenDirectory("/", []);
+
+ const bsdtar_wasi = new WASI(
+ ["bsdtar.wasm", "-x"],
+ [],
+ [
+ new OpenFile(new File(new Uint8Array(), { readonly: true })),
+ ConsoleStdout.lineBuffered((msg) => console.info(msg)),
+ ConsoleStdout.lineBuffered((msg) => console.warn(msg)),
+ rootfs,
+ ],
+ { debug: false }
+ );
+
+ const [{ instance }, rootfs_bytes] = await Promise.all([
+ WebAssembly.instantiateStreaming(
+ fetch("https://haskell-wasm.github.io/bsdtar-wasm/bsdtar.wasm"),
+ { wasi_snapshot_preview1: bsdtar_wasi.wasiImport }
+ ),
+ fetch("./rootfs.tar.zst").then((r) => r.bytes()),
+ ]);
+
+ bsdtar_wasi.fds[0] = new OpenFile(
+ new File(rootfs_bytes, { readonly: true })
+ );
+ bsdtar_wasi.start(instance);
+
+ if (document.readyState === "loading") {
+ await new Promise((res) =>
+ document.addEventListener("DOMContentLoaded", res, { once: true })
+ );
+ }
+
+ window.editor = monaco.editor.create(document.getElementById("editor"), {
+ value: 'main :: IO ()\nmain = putStrLn "Hello, Haskell!"\n',
+ language: "haskell",
+ automaticLayout: true,
+ minimap: { enabled: false },
+ theme: "vs-dark",
+ fontSize: 14,
+ });
+
+ const dyld = await main({
+ rpc: new DyLDBrowserHost({
+ rootfs,
+ stdout: (msg) => {
+ document.getElementById("stdout").value += `${msg}\n`;
+ },
+ stderr: (msg) => {
+ document.getElementById("stderr").value += `${msg}\n`;
+ },
+ }),
+ searchDirs: [
+ "/tmp/clib",
+ "/tmp/hslib/lib/wasm32-wasi-ghc-9.15.20251024",
+ ],
+ mainSoPath: "/tmp/libplayground001.so",
+ args: ["libplayground001.so", "+RTS", "-c", "-RTS"],
+ isIserv: false,
+ });
+ const main_func = await dyld.exportFuncs.myMain("/tmp/hslib/lib");
+
+ document.getElementById("runBtn").addEventListener("click", async () => {
+ document.getElementById("runBtn").disabled = true;
+
+ try {
+ document.getElementById("stdout").value = "";
+ document.getElementById("stderr").value = "";
+
+ await main_func(
+ document.getElementById("ghcArgs").value,
+ editor.getValue()
+ );
+ } finally {
+ document.getElementById("runBtn").disabled = false;
+ }
+ });
+
+ document.getElementById("runBtn").disabled = false;
+ </script>
+ </head>
+ <body>
+ <div class="app">
+ <section class="pane">
+ <header>Haskell Source</header>
+ <div id="editor"></div>
+ </section>
+
+ <section class="pane right">
+ <header>Controls / Output</header>
+ <div class="controls">
+ <input
+ id="ghcArgs"
+ type="text"
+ placeholder="GHC args"
+ style="font-family: ui-monospace, Menlo, Consolas, monospace"
+ />
+ <button id="runBtn" disabled="true">Run</button>
+ </div>
+ <div class="outputs">
+ <div class="label">stdout</div>
+ <textarea
+ id="stdout"
+ readonly
+ style="font-family: ui-monospace, Menlo, Consolas, monospace"
+ ></textarea>
+ <div class="label">stderr</div>
+ <textarea
+ id="stderr"
+ class="stderr"
+ readonly
+ style="font-family: ui-monospace, Menlo, Consolas, monospace"
+ ></textarea>
+ </div>
+ </section>
+ </div>
+ </body>
+</html>
=====================================
testsuite/tests/ghc-api-browser/playground001.hs
=====================================
@@ -0,0 +1,95 @@
+module Playground
+ ( myMain,
+ )
+where
+
+import Control.Monad
+import Data.Coerce
+import Data.IORef
+import GHC
+import GHC.Driver.Config.Diagnostic
+import GHC.Driver.Errors
+import GHC.Driver.Errors.Types
+import GHC.Driver.Monad
+import GHC.Plugins
+import GHC.Runtime.Interpreter
+import GHC.Utils.Exception
+import GHC.Wasm.Prim
+
+newtype JSFunction t = JSFunction JSVal
+
+type ExportedMainFunction = JSString -> JSString -> IO ()
+
+-- main entry point of playground001, returns a js async function that
+-- takes ghc args and Main.hs content, interprets Main.hs and runs
+-- Main.main.
+myMain :: JSString -> IO (JSFunction ExportedMainFunction)
+myMain js_libdir =
+ defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
+ libdir <- evaluate $ fromJSString js_libdir
+ freeJSVal $ coerce js_libdir
+ -- we don't use runGhc since we want to share a session to be
+ -- reused.
+ session <- Session <$> newIORef undefined
+ -- save a fresh default dflags, otherwise user input ghc args are
+ -- not properly reset.
+ dflags0 <- flip reflectGhc session $ do
+ initGhcMonad (Just libdir)
+ dflags0 <- getSessionDynFlags
+ setSessionDynFlags $
+ dflags0
+ { ghcMode = CompManager,
+ backend = bytecodeBackend,
+ ghcLink = LinkInMemory,
+ verbosity = 1
+ }
+ getSessionDynFlags
+ -- this is always run in a forked thread. which is fine as long as
+ -- the sesssion is not reused concurrently, but it's up to the
+ -- caller in js to ensure that. we simply disable the run button
+ -- until each run completes in the playground ui logic.
+ toMainFunc $ \js_args js_src ->
+ defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
+ args <- evaluate $ words $ fromJSString js_args
+ freeJSVal $ coerce js_args
+ writeFile f $ fromJSString js_src
+ freeJSVal $ coerce js_src
+ -- it's fine to call withCleanupSession since it just cleans up
+ -- tmpfs for now. in the future if it does more cleanup that
+ -- makes the session state invalid for reuse, just remove it;
+ -- everything will be cleaned up anyway when the browser tab is
+ -- closed
+ flip reflectGhc session $ withCleanupSession $ do
+ setSessionDynFlags dflags0
+ logger0 <- getLogger
+ (dflags1, _, dynamicFlagWarnings) <-
+ parseDynamicFlags logger0 dflags0 $ map noLoc args
+ setSessionDynFlags dflags1
+ logger1 <- getLogger
+ liftIO
+ $ printOrThrowDiagnostics
+ logger1
+ (initPrintConfig dflags1)
+ (initDiagOpts dflags1)
+ $ GhcDriverMessage
+ <$> dynamicFlagWarnings
+ setTargets =<< (: []) <$> guessTarget f Nothing Nothing
+ r <- load LoadAllTargets
+ when (failed r) $ fail "load returned Failed"
+ setContext [IIDecl $ simpleImportDecl $ mkModuleName "Main"]
+ fhv <- compileExprRemote "Main.main"
+ hsc_env <- getSession
+ liftIO $ evalIO (hscInterp hsc_env) fhv
+ where
+ f = "/tmp/Main.hs"
+
+foreign import javascript "wrapper"
+ toMainFunc ::
+ ExportedMainFunction ->
+ IO (JSFunction ExportedMainFunction)
+
+foreign export javascript "myMain"
+ myMain ::
+ JSString ->
+ IO
+ (JSFunction ExportedMainFunction)
=====================================
testsuite/tests/ghc-api-browser/playground001.js
=====================================
@@ -0,0 +1,91 @@
+#!/usr/bin/env -S node
+
+const puppeteer = require("puppeteer-core");
+const fs = require("node:fs");
+const path = require("node:path");
+
+class Playground {
+ static #token = Symbol("Playground");
+ #browser;
+ #page;
+
+ static async create({ launchOpts, artifactDir }) {
+ const playground = new Playground(Playground.#token);
+ playground.#browser = await puppeteer.launch(launchOpts);
+
+ playground.#page = await playground.#browser.newPage();
+ await playground.#page.setRequestInterception(true);
+ playground.#page.on("request", async (req) => {
+ if (!req.url().startsWith("http://localhost")) {
+ return req.continue();
+ }
+
+ try {
+ const f = req.url().replace("http://localhost", artifactDir);
+ return req.respond({
+ status: 200,
+ contentType:
+ {
+ ".html": "text/html",
+ ".mjs": "application/javascript",
+ }[path.extname(f)] || "application/octet-stream",
+ body: await fs.promises.readFile(f),
+ });
+ } catch {
+ return req.abort();
+ }
+ });
+
+ await playground.#page.goto("http://localhost/index.html");
+ await playground.#page.locator("#runBtn:enabled").wait();
+ return playground;
+ }
+
+ async close() {
+ await this.#browser.close();
+ }
+
+ async runMain({ mainSrc, ghcArgs }) {
+ await Promise.all([
+ this.#page.evaluate((mainSrc) => editor.setValue(mainSrc), mainSrc),
+ this.#page.locator("#ghcArgs").fill(ghcArgs),
+ ]);
+ await this.#page.locator("#runBtn:enabled").click();
+ await this.#page.locator("#runBtn:enabled").wait();
+
+ const [stdout, stderr] = await Promise.all(
+ ["#stdout", "#stderr"].map((el) =>
+ this.#page
+ .locator(el)
+ .map((t) => t.value)
+ .wait()
+ )
+ );
+
+ return { stdout, stderr };
+ }
+
+ constructor(token) {
+ if (token !== Playground.#token) {
+ throw new Error("new Playground() is forbidden, use Playground.create()");
+ }
+ }
+}
+
+(async () => {
+ const playground = await Playground.create({
+ launchOpts: JSON.parse(process.argv[2]),
+ artifactDir: process.cwd(),
+ });
+
+ try {
+ const { stdout, stderr } = await playground.runMain({
+ mainSrc: await fs.promises.readFile("./hello.hs", { encoding: "utf-8" }),
+ ghcArgs: "-package ghc -v0",
+ });
+ process.stdout.write(stdout);
+ process.stderr.write(stderr);
+ } finally {
+ await playground.close();
+ }
+})();
=====================================
testsuite/tests/ghc-api-browser/playground001.sh
=====================================
@@ -0,0 +1,76 @@
+#!/usr/bin/env bash
+
+set -euo pipefail
+
+# also set this when building wasm32-wasi-ghc for production
+# deployment of haskell playground, so all the .so files are
+# optimized.
+export WASM_SO_OPT="--debuginfo --low-memory-unused --strip-dwarf -Oz"
+
+# we'll build a rootfs tarball that contains everything in tmp and
+# extracts to /tmp, mapped from here
+mkdir ./tmp
+
+$TEST_HC \
+ -v0 \
+ -package ghc \
+ -shared -dynamic \
+ -no-keep-hi-files -no-keep-o-files \
+ -O2 \
+ playground001.hs -o ./tmp/libplayground001.so
+rm -f ./*_stub.h ./playground001.hs
+
+# /tmp/clib contains libc/libc++ .so files
+cp -r "$(dirname "$TEST_CC")/../share/wasi-sysroot/lib/wasm32-wasi" ./tmp/clib
+# trim unneeded stuff in c libdir
+find ./tmp/clib -type f ! -name "*.so" -delete
+rm -f \
+ ./tmp/clib/libsetjmp.so \
+ ./tmp/clib/libwasi-emulated-*.so
+
+# /tmp/hslib/lib is the ghc libdir
+mkdir ./tmp/hslib
+cp -r "$($TEST_HC --print-libdir)" ./tmp/hslib/lib
+# unregister Cabal/Cabal-syntax, too big
+$GHC_PKG --no-user-package-db --global-package-db=./tmp/hslib/lib/package.conf.d unregister Cabal Cabal-syntax
+$GHC_PKG --no-user-package-db --global-package-db=./tmp/hslib/lib/package.conf.d recache
+# we only need non-profiling .dyn_hi/.so, trim as much as we can
+find ./tmp/hslib/lib "(" \
+ -name "*.hi" \
+ -o -name "*.a" \
+ -o -name "*.p_hi" \
+ -o -name "libHS*_p.a" \
+ -o -name "*.p_dyn_hi" \
+ -o -name "libHS*_p*.so" \
+ -o -name "libHSrts*_debug*.so" \
+ ")" -delete
+rm -rf \
+ ./tmp/hslib/lib/doc \
+ ./tmp/hslib/lib/html \
+ ./tmp/hslib/lib/latex \
+ ./tmp/hslib/lib/*.mjs \
+ ./tmp/hslib/lib/*.js \
+ ./tmp/hslib/lib/*.txt
+# HS_SEARCHDIR is something like
+# /tmp/hslib/lib/wasm32-wasi-ghc-9.15.20251024 which is the
+# dynamic-library-dirs that contains all libHS*.so in one place, and
+# also static libraries in per-unit directories
+HS_SEARCHDIR=$(find ./tmp/hslib/lib -type f -name "*.so" -print0 | xargs -0 -n1 dirname | sort -u | sed "s|^\./|/|")
+# hunt down the remaining bits of Cabal/Cabal-syntax. too bad there's
+# no ghc-pkg uninstall.
+rm -rf ."$HS_SEARCHDIR"/*Cabal*
+
+# fix the hard coded search dir in index.html
+SED_IS_GNU=$(sed --version &> /dev/null && echo 1 || echo 0)
+if [[ $SED_IS_GNU == "1" ]]; then
+ sed -i "s|/tmp/hslib/lib/wasm32-wasi-ghc-9.15.20251024|$HS_SEARCHDIR|" ./index.html
+else
+ sed -i "" "s|/tmp/hslib/lib/wasm32-wasi-ghc-9.15.20251024|$HS_SEARCHDIR|" ./index.html
+fi
+
+# also set ZSTD_NBTHREADS/ZSTD_CLEVEL when building for production
+tar -cf ./rootfs.tar.zst --zstd tmp
+rm -rf ./tmp
+
+# pass puppeteer.launch() opts as json
+exec ./playground001.js "$1"
=====================================
testsuite/tests/ghci-wasm/T26431.stdout → testsuite/tests/ghc-api-browser/playground001.stdout
=====================================
=====================================
testsuite/tests/ghci-wasm/T26431.hs deleted
=====================================
@@ -1,35 +0,0 @@
-import Control.Exception
-import Control.Monad.IO.Class
-import Data.Maybe
-import GHC
-import GHC.Plugins
-import GHC.Runtime.Interpreter
-import System.Environment.Blank
-
-main :: IO ()
-main = do
- [libdir] <- getArgs
- defaultErrorHandler defaultFatalMessager defaultFlushOut $
- runGhc (Just libdir) $
- do
- dflags0 <- getSessionDynFlags
- let dflags1 =
- dflags0
- { ghcMode = CompManager,
- backend = bytecodeBackend,
- ghcLink = LinkInMemory
- }
- logger <- getLogger
- (dflags2, _, _) <-
- parseDynamicFlags logger dflags1 $
- map noLoc ["-package", "ghc"]
- _ <- setSessionDynFlags dflags2
- addTarget =<< guessTarget "hello.hs" Nothing Nothing
- _ <- load LoadAllTargets
- setContext
- [ IIDecl $ simpleImportDecl $ mkModuleName "Prelude",
- IIDecl $ simpleImportDecl $ mkModuleName "Main"
- ]
- hsc_env <- getSession
- fhv <- compileExprRemote "main"
- liftIO $ evalIO (fromJust $ hsc_interp hsc_env) fhv
=====================================
testsuite/tests/ghci-wasm/all.T
=====================================
@@ -10,11 +10,3 @@ test('T26430', [
extra_hc_opts('-L. -lT26430B')]
, compile_and_run, ['']
)
-
-test('T26431', [
- extra_files(['../../../.gitlab/hello.hs']),
- extra_hc_opts('-package ghc'),
- extra_run_opts(f'"{config.libdir}"'),
- ignore_stderr]
-, compile_and_run, ['']
-)
=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -285,7 +285,7 @@ function originFromServerAddress({ address, family, port }) {
}
// Browser/node portable code stays above this watermark.
-const isNode = Boolean(globalThis?.process?.versions?.node);
+const isNode = Boolean(globalThis?.process?.versions?.node && !globalThis.Deno);
// Too cumbersome to only import at use sites. Too troublesome to
// factor out browser-only/node-only logic into different modules. For
@@ -307,27 +307,27 @@ if (isNode) {
ws = require("ws");
} catch {}
} else {
- wasi = await import(
- "https://cdn.jsdelivr.net/npm/@bjorn3/browser_wasi_shim@0.4.2/dist/index.js"
- );
+ wasi = await import("https://esm.sh/gh/haskell-wasm/browser_wasi_shim");
}
// A subset of dyld logic that can only be run in the host node
// process and has full access to local filesystem
-class DyLDHost {
+export class DyLDHost {
// Deduped absolute paths of directories where we lookup .so files
#rpaths = new Set();
- constructor() {
- // Inherited pipe file descriptors from GHC
- const out_fd = Number.parseInt(process.argv[4]),
- in_fd = Number.parseInt(process.argv[5]);
-
+ constructor({ outFd, inFd }) {
+ // When running a non-iserv shared library with node, the DyLDHost
+ // instance is created without a pair of fds, so skip creation of
+ // readStream/writeStream, they won't be used anyway
+ if (!(typeof outFd === "number" && typeof inFd === "number")) {
+ return;
+ }
this.readStream = stream.Readable.toWeb(
- fs.createReadStream(undefined, { fd: in_fd })
+ fs.createReadStream(undefined, { fd: inFd })
);
this.writeStream = stream.Writable.toWeb(
- fs.createWriteStream(undefined, { fd: out_fd })
+ fs.createWriteStream(undefined, { fd: outFd })
);
}
@@ -377,6 +377,72 @@ class DyLDHost {
}
}
+// Runs in the browser and uses the in-memory vfs, doesn't do any RPC
+// calls
+export class DyLDBrowserHost {
+ // Deduped absolute paths of directories where we lookup .so files
+ #rpaths = new Set();
+ // The PreopenDirectory object of the root filesystem
+ rootfs;
+ // Continuations to output a single line to stdout/stderr
+ stdout;
+ stderr;
+
+ // Given canonicalized absolute file path, returns the File object,
+ // or null if absent
+ #readFile(p) {
+ const { ret, entry } = this.rootfs.dir.get_entry_for_path({
+ parts: p.split("/").filter((tok) => tok !== ""),
+ is_dir: false,
+ });
+ return ret === 0 ? entry : null;
+ }
+
+ constructor({ rootfs, stdout, stderr }) {
+ this.rootfs = rootfs
+ ? rootfs
+ : new wasi.PreopenDirectory("/", [["tmp", new wasi.Directory([])]]);
+ this.stdout = stdout ? stdout : (msg) => console.info(msg);
+ this.stderr = stderr ? stderr : (msg) => console.warn(msg);
+ }
+
+ // p must be canonicalized absolute path
+ async addLibrarySearchPath(p) {
+ this.#rpaths.add(p);
+ return null;
+ }
+
+ async findSystemLibrary(f) {
+ if (f.startsWith("/")) {
+ if (this.#readFile(f)) {
+ return f;
+ }
+ throw new Error(`findSystemLibrary(${f}): not found in /`);
+ }
+
+ for (const rpath of this.#rpaths) {
+ const r = `${rpath}/${f}`;
+ if (this.#readFile(r)) {
+ return r;
+ }
+ }
+
+ throw new Error(
+ `findSystemLibrary(${f}): not found in ${[...this.#rpaths]}`
+ );
+ }
+
+ async fetchWasm(p) {
+ const entry = this.#readFile(p);
+ const r = new Response(entry.data, {
+ headers: { "Content-Type": "application/wasm" },
+ });
+ // It's only fetched once, take the chance to prune it in vfs to save memory
+ entry.data = new Uint8Array();
+ return r;
+ }
+}
+
// Fulfill the same functionality as DyLDHost by doing fetch() calls
// to respective RPC endpoints of a host http server. Also manages
// WebSocket connections back to host.
@@ -494,7 +560,7 @@ export class DyLDRPC {
// Actual implementation of endpoints used by DyLDRPC
class DyLDRPCServer {
- #dyldHost = new DyLDHost();
+ #dyldHost;
#server;
#wss;
@@ -502,11 +568,15 @@ class DyLDRPCServer {
host,
port,
dyldPath,
- libdir,
- ghciSoPath,
+ searchDirs,
+ mainSoPath,
+ outFd,
+ inFd,
args,
redirectWasiConsole,
}) {
+ this.#dyldHost = new DyLDHost({ outFd, inFd });
+
this.#server = http.createServer(async (req, res) => {
const origin = originFromServerAddress(await this.listening);
@@ -540,7 +610,7 @@ class DyLDRPCServer {
res.end(
`
import { DyLDRPC, main } from "./fs${dyldPath}";
-const args = ${JSON.stringify({ libdir, ghciSoPath, args })};
+const args = ${JSON.stringify({ searchDirs, mainSoPath, args, isIserv: true })};
args.rpc = new DyLDRPC({origin: "${origin}", redirectWasiConsole: ${redirectWasiConsole}});
args.rpc.opened.then(() => main(args));
`
@@ -829,11 +899,37 @@ class DyLD {
),
wasi.ConsoleStdout.lineBuffered((msg) => this.#rpc.stdout(msg)),
wasi.ConsoleStdout.lineBuffered((msg) => this.#rpc.stderr(msg)),
+ // for ghci browser mode, default to an empty rootfs with
+ // /tmp
+ this.#rpc instanceof DyLDBrowserHost
+ ? this.#rpc.rootfs
+ : new wasi.PreopenDirectory("/", [["tmp", new wasi.Directory([])]]),
],
{ debug: false }
);
}
+ // Both wasi implementations we use provide
+ // wasi.initialize(instance) to initialize a wasip1 reactor
+ // module. However, instance does not really need to be a
+ // WebAssembly.Instance object; the wasi implementations only need
+ // to access instance.exports.memory for the wasi syscalls to
+ // work.
+ //
+ // Given we'll reuse the same wasi object across different
+ // WebAssembly.Instance objects anyway and
+ // wasi.initialize(instance) can't be called more than once, we
+ // use this simple trick and pass a fake instance object that
+ // contains just enough info for the wasi implementation to
+ // initialize its internal state. Later when we load each wasm
+ // shared library, we can just manually invoke their
+ // initialization functions.
+ this.#wasi.initialize({
+ exports: {
+ memory: this.#memory,
+ },
+ });
+
// Keep this in sync with rts/wasm/Wasm.S!
for (let i = 1; i <= 10; ++i) {
this.#regs[`__R${i}`] = new WebAssembly.Global({
@@ -930,10 +1026,15 @@ class DyLD {
async loadDLLs(packed) {
// Normalize input to an array of strings. When called from Haskell
// we pass a single JSString containing NUL-separated paths.
- const paths = (typeof packed === "string"
- ? (packed.length === 0 ? [] : packed.split("\0"))
- : [packed] // tolerate an accidental single path object
- ).filter((s) => s.length > 0).reverse();
+ const paths = (
+ typeof packed === "string"
+ ? packed.length === 0
+ ? []
+ : packed.split("\0")
+ : [packed]
+ ) // tolerate an accidental single path object
+ .filter((s) => s.length > 0)
+ .reverse();
// Compute a single downsweep plan for the whole batch.
// Note: #downsweep mutates #loadedSos to break cycles and dedup.
@@ -1154,22 +1255,6 @@ class DyLD {
throw new Error(`cannot handle export ${k} ${v}`);
}
- // We call wasi.initialize when loading libc.so, then reuse the
- // wasi instance globally. When loading later .so files, just
- // manually invoke _initialize().
- if (soname === "libc.so") {
- instance.exports.__wasm_apply_data_relocs();
- // wasm-ld forbits --export-memory with --shared, I don't know
- // why but this is sufficient to make things work
- this.#wasi.initialize({
- exports: {
- memory: this.#memory,
- _initialize: instance.exports._initialize,
- },
- });
- continue;
- }
-
// See
// https://gitlab.haskell.org/haskell-wasm/llvm-project/-/blob/release/21.x/ll…,
// __wasm_apply_data_relocs is now optional so only call it if
@@ -1180,7 +1265,7 @@ class DyLD {
// been called upon instantiation, see
// Writer::createStartFunction().
if (instance.exports.__wasm_apply_data_relocs) {
- instance.exports.__wasm_apply_data_relocs();
+ instance.exports.__wasm_apply_data_relocs();
}
instance.exports._initialize();
@@ -1208,15 +1293,38 @@ class DyLD {
}
}
-export async function main({ rpc, libdir, ghciSoPath, args }) {
+// The main entry point of dyld that may be run on node/browser, and
+// may run either iserv defaultMain from the ghci library or an
+// alternative entry point from another shared library
+export async function main({
+ rpc, // Handle the side effects of DyLD
+ searchDirs, // Initial library search directories
+ mainSoPath, // Could also be another shared library that's actually not ghci
+ args, // WASI argv starting with the executable name. +RTS etc will be respected
+ isIserv, // set to true when running iserv defaultServer
+}) {
try {
const dyld = new DyLD({
- args: ["dyld.so", ...args],
+ args,
rpc,
});
- await dyld.addLibrarySearchPath(libdir);
- await dyld.loadDLLs(ghciSoPath);
+ for (const libdir of searchDirs) {
+ await dyld.addLibrarySearchPath(libdir);
+ }
+ await dyld.loadDLLs(mainSoPath);
+
+ // At this point, rts/ghc-internal are loaded, perform wasm shared
+ // library specific RTS startup logic, see Note [JSFFI initialization]
+ dyld.exportFuncs.__ghc_wasm_jsffi_init();
+
+ // We're not running iserv, just return the dyld instance so user
+ // could use it to invoke their exported functions, and don't
+ // perform cleanup (see finally block)
+ if (!isIserv) {
+ return dyld;
+ }
+ // iserv-specific logic follows
const reader = rpc.readStream.getReader();
const writer = rpc.writeStream.getWriter();
@@ -1235,31 +1343,25 @@ export async function main({ rpc, libdir, ghciSoPath, args }) {
writer.write(new Uint8Array(buf));
};
- dyld.exportFuncs.__ghc_wasm_jsffi_init();
- await dyld.exportFuncs.defaultServer(cb_sig, cb_recv, cb_send);
+ return await dyld.exportFuncs.defaultServer(cb_sig, cb_recv, cb_send);
} finally {
- rpc.close();
+ if (isIserv) {
+ rpc.close();
+ }
}
}
-(async () => {
- if (!isNode) {
- return;
- }
-
- const libdir = process.argv[2];
- const ghciSoPath = process.argv[3];
- const args = process.argv.slice(6);
-
+// node-specific iserv-specific logic
+async function nodeMain({ searchDirs, mainSoPath, outFd, inFd, args }) {
if (!process.env.GHCI_BROWSER) {
- const rpc = new DyLDHost();
- await main({
+ const rpc = new DyLDHost({ outFd, inFd });
+ return await main({
rpc,
- libdir,
- ghciSoPath,
+ searchDirs,
+ mainSoPath,
args,
+ isIserv: true,
});
- return;
}
if (!ws) {
@@ -1272,8 +1374,10 @@ export async function main({ rpc, libdir, ghciSoPath, args }) {
host: process.env.GHCI_BROWSER_HOST || "127.0.0.1",
port: process.env.GHCI_BROWSER_PORT || 0,
dyldPath: import.meta.filename,
- libdir,
- ghciSoPath,
+ searchDirs,
+ mainSoPath,
+ outFd,
+ inFd,
args,
redirectWasiConsole:
process.env.GHCI_BROWSER_PUPPETEER_LAUNCH_OPTS ||
@@ -1362,6 +1466,20 @@ export async function main({ rpc, libdir, ghciSoPath, args }) {
}
console.log(
- `Open ${origin}/main.html or import ${origin}/main.js to boot ghci`
+ `Open ${origin}/main.html or import("${origin}/main.js") to boot ghci`
);
-})();
+}
+
+const isNodeMain = isNode && import.meta.filename === process.argv[1];
+
+// node iserv as invoked by
+// GHC.Runtime.Interpreter.Wasm.spawnWasmInterp
+if (isNodeMain) {
+ const clibdir = process.argv[2];
+ const mainSoPath = process.argv[3];
+ const outFd = Number.parseInt(process.argv[4]),
+ inFd = Number.parseInt(process.argv[5]);
+ const args = ["dyld.so", ...process.argv.slice(6)];
+
+ await nodeMain({ searchDirs: [clibdir], mainSoPath, outFd, inFd, args });
+}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/995dfe0d6012c2798bafe42cabbc04…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/995dfe0d6012c2798bafe42cabbc04…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED] 75 commits: T22859: Increase threadDelay for small machines
by Sven Tennie (@supersven) 01 Nov '25
by Sven Tennie (@supersven) 01 Nov '25
01 Nov '25
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED at Glasgow Haskell Compiler / GHC
Commits:
e10dcd65 by Sven Tennie at 2025-10-12T10:24:56+00:00
T22859: Increase threadDelay for small machines
The previously used thread delay led to failures on my RISC-V test
setups.
- - - - -
d59ef6b6 by Hai / @BestYeen at 2025-10-14T21:51:14-04:00
Change Alex and Happy m4 scripts to display which version was found in the system, adapt small formatting details in Happy script to be more like the Alex script again.
- - - - -
c98abb6a by Hai / @BestYeen at 2025-10-14T21:52:08-04:00
Update occurrences of return to pure and add a sample for redefining :m to mean :main
- - - - -
70ee825a by Cheng Shao at 2025-10-14T21:52:50-04:00
testsuite: fix T3586 for non-SSE3 platforms
`T3586.hs` contains `-fvia-C -optc-msse3` which I think is a
best-effort basis to harvest the C compiler's auto vectorization
optimizations via the C backend back when the test was added. The
`-fvia-C` part is now a deprecated no-op because GHC can't fall back
to the C backend on a non-unregisterised build, and `-optc-msse3`
might actually cause the test to fail on non x86/x64 platforms, e.g.
recent builds of wasi-sdk would report `wasm32-wasi-clang: error:
unsupported option '-msse3' for target 'wasm32-unknown-wasi'`.
So this patch cleans up this historical cruft. `-fvia-C` is removed,
and `-optc-msse3` is only passed when cpuid contains `pni` (which
indicates support of SSE3).
- - - - -
4be32153 by Teo Camarasu at 2025-10-15T08:06:09-04:00
Add submodules for template-haskell-lift and template-haskell-quasiquoter
These two new boot libraries expose stable subsets of the
template-haskell interface.
This is an implemenation of the GHC proposal https://github.com/ghc-proposals/ghc-proposals/pull/696
Work towards #25262
- - - - -
0c00c9c3 by Ben Gamari at 2025-10-15T08:06:51-04:00
rts: Eliminate uses of implicit constant arrays
Folding of `const`-sized variable-length arrays to a constant-length
array is a gnu extension which clang complains about.
Closes #26502.
- - - - -
bf902a1d by Fendor at 2025-10-15T16:00:59-04:00
Refactor distinct constructor tables map construction
Adds `GHC.Types.Unique.FM.alterUFM_L`, `GHC.Types.Unique.DFM.alterUDFM_L`
`GHC.Data.Word64Map.alterLookup` to support fusion of distinct
constructor data insertion and lookup during the construction of the `DataCon`
map in `GHC.Stg.Debug.numberDataCon`.
Co-authored-by: Fendor <fendor(a)posteo.de>
Co-authored-by: Finley McIlwaine <finleymcilwaine(a)gmail.com>
- - - - -
b3585ba1 by Fendor at 2025-10-15T16:00:59-04:00
Allow per constructor refinement of distinct-constructor-tables
Introduce `-fno-distinct-constructor-tables`. A distinct constructor table
configuration is built from the combination of flags given, in order. For
example, to only generate distinct constructor tables for a few specific
constructors and no others, just pass
`-fdistinct-constructor-tables-only=C1,...,CN`.
This flag can be supplied multiple times to extend the set of
constructors to generate a distinct info table for.
You can disable generation of distinct constructor tables for all
configurations by passing `-fno-distinct-constructor-tables`.
The various configurations of these flags is included in the `DynFlags`
fingerprints, which should result in the expected recompilation logic.
Adds a test that checks for distinct tables for various given or omitted
constructors.
Updates CountDepsAst and CountDepsParser tests to account for new dependencies.
Fixes #23703
Co-authored-by: Fendor <fendor(a)posteo.de>
Co-authored-by: Finley McIlwaine <finleymcilwaine(a)gmail.com>
- - - - -
e17dc695 by fendor at 2025-10-15T16:01:41-04:00
Fix typos in haddock documentation for stack annotation API
- - - - -
f85058d3 by Zubin Duggal at 2025-10-17T13:50:52+05:30
compiler: Attempt to systematize Unique tags by introducing an ADT for each different tag
Fixes #26264
Metric Decrease:
T9233
- - - - -
c85c845d by sheaf at 2025-10-17T22:35:32-04:00
Don't prematurely final-zonk PatSyn declarations
This commit makes GHC hold off on the final zonk for pattern synonym
declarations, in 'GHC.Tc.TyCl.PatSyn.tc_patsyn_finish'.
This accommodates the fact that pattern synonym declarations without a
type signature can contain unfilled metavariables, e.g. if the RHS of
the pattern synonym involves view-patterns whose type mentions promoted
(level 0) metavariables. Just like we do for ordinary function bindings,
we should allow these metavariables to be settled later, instead of
eagerly performing a final zonk-to-type.
Now, the final zonking-to-type for pattern synonyms is performed in
GHC.Tc.Module.zonkTcGblEnv.
Fixes #26465
- - - - -
ba3e5bdd by Rodrigo Mesquita at 2025-10-18T16:57:18-04:00
Move code-gen aux symbols from ghc-internal to rts
These symbols were all previously defined in ghc-internal and made the
dependency structure awkward, where the rts may refer to some of these
symbols and had to work around that circular dependency the way
described in #26166.
Moreover, the code generator will produce code that uses these symbols!
Therefore, they should be available in the rts:
PRINCIPLE: If the code generator may produce code which uses this
symbol, then it should be defined in the rts rather than, say,
ghc-internal.
That said, the main motivation is towards fixing #26166.
Towards #26166. Pre-requisite of !14892
- - - - -
f31de2a9 by Ben Gamari at 2025-10-18T16:57:18-04:00
rts: Avoid static symbol references to ghc-internal
This resolves #26166, a bug due to new constraints placed by Apple's
linker on undefined references.
One source of such references in the RTS is the many symbols referenced
in ghc-internal. To mitigate #26166, we make these references dynamic,
as described in Note [RTS/ghc-internal interface].
Fixes #26166
Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita(a)gmail.com>
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
- - - - -
43fdfddc by Ben Gamari at 2025-10-18T16:57:18-04:00
compiler: Rename isMathFun -> isLibcFun
This set includes more than just math functions.
- - - - -
4ed5138f by Ben Gamari at 2025-10-18T16:57:18-04:00
compiler: Add libc allocator functions to libc_funs
Prototypes for these are now visible from `Prim.h`, resulting in
multiple-declaration warnings in the unregisterised job.
- - - - -
9a0a076b by Ben Gamari at 2025-10-18T16:57:18-04:00
rts: Minimize header dependencies of Prim.h
Otherwise we will end up with redundant and incompatible declarations
resulting in warnings during the unregisterised build.
- - - - -
26b8a414 by Diego Antonio Rosario Palomino at 2025-10-18T16:58:10-04:00
Cmm Parser: Fix incorrect example in comment
The Parser.y file contains a comment with an incorrect example of textual
Cmm (used in .cmm files). This commit updates the comment to ensure it
reflects valid textual Cmm syntax.
Fixes #26313
- - - - -
d4a9d6d6 by ARATA Mizuki at 2025-10-19T18:43:47+09:00
Handle implications between x86 feature flags
This includes:
* Multiple -msse* options can be specified
* -mavx implies -msse4.2
* -mavx2 implies -mavx
* -mfma implies -mavx
* -mavx512f implies -mavx2 and -mfma
* -mavx512{cd,er,pf} imply -mavx512f
Closes #24989
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
c9b8465c by Cheng Shao at 2025-10-20T10:16:00-04:00
wasm: workaround WebKit bug in dyld
This patch works around a WebKit bug and allows dyld to run on WebKit
based platforms as well. See added note for detailed explanation.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
91b6be10 by Julian Ospald at 2025-10-20T18:21:03-04:00
Improve error handling in 'getPackageArchives'
When the library dirs in the package conf files are not set up correctly,
the JS linker will happily ignore such packages and not link against them,
although they're part of the link plan.
Fixes #26383
- - - - -
6c5269da by Sven Tennie at 2025-10-20T18:21:44-04:00
Align coding style
Improve readability by using the same style for all constructor calls in
this function.
- - - - -
3d305889 by Sven Tennie at 2025-10-20T18:21:44-04:00
Reduce complexity by removing joins with mempty
ldArgs, cArgs and cppArgs are all `mempty`. Thus concatenating them adds
nothing but some complexity while reading the code.
- - - - -
38d65187 by Matthew Pickering at 2025-10-21T13:12:20+01:00
Fix stack decoding when using profiled runtime
There are three fixes in this commit.
* We need to replicate the `InfoTable` and `InfoTableProf`
approach for the other stack constants (see the new Stack.ConstantsProf
file).
* Then we need to appropiately import the profiled or non-profiled
versions.
* Finally, there was an incorrect addition in `stackFrameSize`. We need
to cast after performing addition on words.
Fixes #26507
- - - - -
17231bfb by fendor at 2025-10-21T13:12:20+01:00
Add regression test for #26507
- - - - -
4f5bf93b by Simon Peyton Jones at 2025-10-25T04:05:34-04:00
Postscript to fix for #26255
This MR has comments only
- - - - -
6ef22fa0 by IC Rainbow at 2025-10-26T18:23:01-04:00
Add SIMD primops for bitwise logical operations
This adds 128-bit wide and/or/xor instructions for X86 NCG,
with both SSE and AVX encodings.
```
andFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- andps / vandps
andDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -- andpd / vandpd
andInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- pand / vpand
```
The new primops are available on ARM when using LLVM backend.
Tests added:
- simd015 (floats and doubles)
- simd016 (integers)
- simd017 (words)
Fixes #26417
- - - - -
fbdc623a by sheaf at 2025-10-26T18:23:52-04:00
Add hints for unsolved HasField constraints
This commit adds hints and explanations for unsolved 'HasField'
constraints.
GHC will now provide additional explanations for an unsolved constraint
of the form 'HasField fld_name rec_ty fld_ty'; the details are laid out in
Note [Error messages for unsolved HasField constraints], but briefly:
1. Provide similar name suggestions (e.g. mis-spelled field name)
and import suggestions (record field not in scope).
These result in actionable 'GhcHints', which is helpful to provide
code actions in HLS.
2. Explain why GHC did not solve the constraint, e.g.:
- 'fld_name' is not a string literal (e.g. a type variable)
- 'rec_ty' is a TyCon without any fields, e.g. 'Int' or 'Bool'.
- 'fld_ty' contains existentials variables or foralls.
- The record field is a pattern synonym field (GHC does not generate
HasField instances for those).
- 'HasField' is a custom 'TyCon', not actually the built-in
'HasField' typeclass from 'GHC.Records'.
On the way, we slightly refactor the mechanisms for import suggestions
in GHC.Rename.Unbound. This is to account for the fact that, for
'HasField', we don't care whether the field is imported qualified or
unqualified. 'importSuggestions' was refactored, we now have
'sameQualImportSuggestions' and 'anyQualImportSuggestions'.
Fixes #18776 #22382 #26480
- - - - -
99d5707f by sheaf at 2025-10-26T18:23:52-04:00
Rename PatSyn MatchContext to PatSynCtx to avoid punning
- - - - -
5dc2e9ea by Julian Ospald at 2025-10-27T18:17:23-04:00
Skip uniques test if sources are not available
- - - - -
544b9ec9 by Vladislav Zavialov at 2025-10-27T18:18:06-04:00
Re-export GHC.Hs.Basic from GHC.Hs
Clean up some import sections in GHC by re-exporting GHC.Hs.Basic
from GHC.Hs.
- - - - -
643ce801 by Julian Ospald at 2025-10-28T18:18:55-04:00
rts: remove unneccesary cabal flags
We perform those checks via proper autoconf macros
instead that do the right thing and then add those
libs to the rts buildinfo.
- - - - -
d69ea8fe by Vladislav Zavialov at 2025-10-28T18:19:37-04:00
Test case for #17705
Starting with GHC 9.12 (the first release to include 5745dbd3),
all examples in this ticket are handled as expected.
- - - - -
4038a28b by Andreas Klebinger at 2025-10-30T12:38:52-04:00
Add a perf test for #26425
- - - - -
f997618e by Andreas Klebinger at 2025-10-30T12:38:52-04:00
OccAnal: Be stricter for better compiler perf.
In particular we are now stricter:
* When combining usageDetails.
* When computing binder info.
In combineUsageDetails when combining the underlying adds we compute a
new `LocalOcc` for each entry by combining the two existing ones.
Rather than wait for those entries to be forced down the road we now
force them immediately. Speeding up T26425 by about 10% with little
effect on the common case.
We also force binders we put into the Core AST everywhere now.
Failure to do so risks leaking the occ env used to set the binders
OccInfo.
For T26425 compiler residency went down by a factor of ~10x.
Compile time also improved by a factor of ~1.6.
-------------------------
Metric Decrease:
T18698a
T26425
T9233
-------------------------
- - - - -
5618645b by Vladislav Zavialov at 2025-10-30T12:39:33-04:00
Fix namespace specifiers in subordinate exports (#12488)
This patch fixes an oversight in the `lookupChildrenExport` function that
caused explicit namespace specifiers of subordinate export items to be
ignored:
module M (T (type A)) where -- should be rejected
data T = A
Based on the `IEWrappedName` data type, there are 5 cases to consider:
1. Unadorned name: P(X)
2. Named default: P(default X)
3. Pattern synonym: P(pattern X)
4. Type name: P(type X)
5. Data name: P(data X)
Case 1 is already handled correctly; cases 2 and 3 are parse errors; and
it is cases 4 and 5 that we are concerned with in this patch.
Following the precedent established in `LookupExactName`, we introduce
a boolean flag in `LookupChildren` to control whether to look up in all
namespaces or in a specific one. If an export item is accompanied by an
explicit namespace specifier `type` or `data`, we restrict the lookup in
`lookupGRE` to a specific namespace.
The newly introduced diagnostic `TcRnExportedSubordinateNotFound`
provides error messages and suggestions more tailored to this context
than the previously used `reportUnboundName`.
- - - - -
f341ae29 by Matthew Pickering at 2025-10-31T15:31:53+01:00
Add missing req_interp modifier to T18441fail3 and T18441fail19
These tests require the interpreter but they were failing in a different
way with the javascript backend because the interpreter was disabled and
stderr is ignored by the test.
- - - - -
7581e62d by Matthew Pickering at 2025-10-31T15:31:53+01:00
Use explicit syntax rather than pure
- - - - -
c532fb35 by Matthew Pickering at 2025-10-31T15:31:53+01:00
packaging: correctly propagate build/host/target to bindist configure script
At the moment the host and target which we will produce a compiler for
is fixed at the initial configure time. Therefore we need to persist
the choice made at this time into the installation bindist as well so we
look for the right tools, with the right prefixes at install time.
In the future, we want to provide a bit more control about what kind of
bindist we produce so the logic about what the host/target will have to
be written by hadrian rather than persisted by the configure script. In
particular with cross compilers we want to either build a normal stage 2
cross bindist or a stage 3 bindist, which creates a bindist which has a
native compiler for the target platform.
Fixes #21970
- - - - -
e5c4aa1b by Matthew Pickering at 2025-10-31T15:31:53+01:00
hadrian: Fill in more of the default.host toolchain file
When you are building a cross compiler this file will be used to build
stage1 and it's libraries, so we need enough information here to work
accurately. There is still more work to be done (see for example, word
size is still fixed).
- - - - -
3d723daa by Matthew Pickering at 2025-10-31T15:31:53+01:00
hadrian: Disable docs when cross compiling
Before there were a variety of ad-hoc places where doc building was
disabled when cross compiling.
* Some CI jobs sets --docs=none in gen_ci.hs
* Some CI jobs set --docs=none in .gitlab/ci.sh
* There was some logic in hadrian to not need the ["docs"] target when
making a bindist.
Now the situation is simple:
* If you are cross compiling then defaultDocsTargets is empty by
default.
In theory, there is no reason why we can't build documentation for cross
compiler bindists, but this is left to future work to generalise the
documentation building rules to allow this (#24289)
- - - - -
46386af6 by Matthew Pickering at 2025-10-31T16:25:24+01:00
hadrian: Build stage 2 cross compilers
* Most of hadrian is abstracted over the stage in order to remove the
assumption that the target of all stages is the same platform. This
allows the RTS to be built for two different targets for example.
* Abstracts the bindist creation logic to allow building either normal
or cross bindists. Normal bindists use stage 1 libraries and a stage 2
compiler. Cross bindists use stage 2 libararies and a stage 2
compiler.
* hadrian: Make binary-dist-dir the default build target. This allows us
to have the logic in one place about which libraries/stages to build
with cross compilers. Fixes #24192
New hadrian target:
* `binary-dist-dir-cross`: Build a cross compiler bindist (compiler =
stage 1, libraries = stage 2)
-------------------------
Metric Decrease:
T10421a
T10858
T11195
T11276
T11374
T11822
T15630
T17096
T18478
T20261
Metric Increase:
parsing001
-------------------------
- - - - -
b0cd30b2 by Matthew Pickering at 2025-10-31T16:25:24+01:00
ci: Test cross bindists
We remove the special logic for testing in-tree cross
compilers and instead test cross compiler bindists, like we do for all
other platforms.
- - - - -
440eba45 by Matthew Pickering at 2025-10-31T16:25:24+01:00
ci: Javascript don't set CROSS_EMULATOR
There is no CROSS_EMULATOR needed to run javascript binaries, so we
don't set the CROSS_EMULATOR to some dummy value.
- - - - -
e16f1bb1 by Matthew Pickering at 2025-10-31T16:25:24+01:00
ci: Introduce CROSS_STAGE variable
In preparation for building and testing stage3 bindists we introduce the
CROSS_STAGE variable which is used by a CI job to determine what kind of
bindist the CI job should produce.
At the moment we are only using CROSS_STAGE=2 but in the future we will
have some jobs which set CROSS_STAGE=3 to produce native bindists for a
target, but produced by a cross compiler, which can be tested on by
another CI job on the native platform.
CROSS_STAGE=2: Build a normal cross compiler bindist
CROSS_STAGE=3: Build a stage 3 bindist, one which is a native compiler and library for the target
- - - - -
4d73c166 by Matthew Pickering at 2025-10-31T16:53:17+01:00
Split up system.config into host/target config files
There were a number of settings which were not applied per-stage, for
example if you specified `--ffi-include-dir` then that was applied to
both host and target. Now this will just be passed when building the
crosscompiler.
The solution for now is to separate these two files into host/target and
the host file contains very bare-bones . There isn't currently a way to
specify with configure anything in the host file, so if you are building
a cross-compiler and you need to do that, you have to modify the file
yourself.
- - - - -
f0797745 by Matthew Pickering at 2025-10-31T16:53:17+01:00
Fix location of emsdk-version
- - - - -
1bb16a1f by Matthew Pickering at 2025-10-31T16:53:17+01:00
fix distrib/configure file
- - - - -
84037672 by Matthew Pickering at 2025-10-31T16:53:17+01:00
Fix hardcoded stage1
- - - - -
def77f8c by Matthew Pickering at 2025-10-31T16:53:17+01:00
Don't recache
- - - - -
bcfd462d by Matthew Pickering at 2025-10-31T16:53:17+01:00
hadrian: Make text_simdutf flavour transformer configurable per-stage
Before it was globally enabled, which was probably not what you want as
you don't need text-simd for your boot compiler nor your boot compiler
if you're building a cross-compiler.
This brings it into line with the other modifiers.. such as ghcProfiled
etc
Fixes #25302
- - - - -
fe720ff6 by Matthew Pickering at 2025-10-31T16:53:17+01:00
hadrian: Refactor system-cxx-std-lib rules0
I noticed a few things wrong with the hadrian rules for `system-cxx-std-lib` rules.
* For `text` there is an ad-hoc check to depend on `system-cxx-std-lib` outside of `configurePackage`.
* The `system-cxx-std-lib` dependency is not read from cabal files.
* Recache is not called on the packge database after the `.conf` file is generated, a more natural place for this rule is `registerRules`.
Treating this uniformly like other packages is complicated by it not having any source code or a cabal file. However we can do a bit better by reporting the dependency firstly in `PackageData` and then needing the `.conf` file in the same place as every other package in `configurePackage`.
Fixes #25303
- - - - -
d9b3aa9e by Matthew Pickering at 2025-10-31T16:53:17+01:00
fixes for simdutf8
- - - - -
cbd932df by Matthew Pickering at 2025-10-31T16:53:17+01:00
use building for target in llvm flavour transformer
- - - - -
b133917c by Matthew Pickering at 2025-10-31T16:53:17+01:00
bindist: Pass path to package database we want to recache
This fixes recaching on cross compilers
- - - - -
25069175 by Matthew Pickering at 2025-10-31T16:53:17+01:00
testsuite: T9930fail now passes on javascript
I didn't investigate why, but the comment says it should be fixed by
building a stage2 cross compiler (and it is).
- - - - -
96c15474 by Matthew Pickering at 2025-10-31T16:53:17+01:00
hadrian: Fix predicate for building shared libraries in defaultLibraries
Obviously we should only attempt to build shared libraries if the target
supports building shared libraries.
- - - - -
16c94edd by Matthew Pickering at 2025-10-31T17:17:16+01:00
Hard-code ways in settings
- - - - -
0ac506c8 by Sven Tennie at 2025-10-31T17:17:16+01:00
Fix ghcconfig lookup error
This seems to be the fix with least friction for the issue stated below.
Though, in the long run it might be better to rename `TargetARCH_CPP` to
`TargetARCH` (the `_CPP` suffix feels a bit odd.)
Fixed error:
```
Key 'TargetARCH' not found in file '_build/test/ghcconfig'
```
- - - - -
e4b0b215 by Sven Tennie at 2025-10-31T17:17:16+01:00
target-has-libm -> use-lib-m
The flag was renamed.
- - - - -
1ebedbf0 by Sven Tennie at 2025-10-31T17:17:16+01:00
Additional SIMD flags are required for the host
The files with specific SIMD flags are built for GHC's RTS (host), not
for the programs built by it (target.) This matters when
cross-compiling, because host and target differ then.
- - - - -
b8366d11 by Sven Tennie at 2025-10-31T17:17:16+01:00
Fix path stage segment to stage mapping in generated rules
- - - - -
288b471e by Sven Tennie at 2025-10-31T17:17:16+01:00
Cleanup unused imports
- - - - -
03820841 by Sven Tennie at 2025-10-31T17:17:16+01:00
Fix out-of-tree TestCompilerArgs parsing: WORDSIZE
TestWORDSIZE is in bits, not bytes.
- - - - -
f3791da8 by Sven Tennie at 2025-10-31T17:17:16+01:00
TestCompilerArgs: Fix arch (out of tree)
- - - - -
fa633fd5 by Sven Tennie at 2025-10-31T17:17:16+01:00
Calculate "RTS ways"
The static string doesn't reflect what GHC provides in tests.
- - - - -
41122c6e by Sven Tennie at 2025-10-31T17:17:16+01:00
Fix libffi configuration
Libffi needs to be built with the config of the successor stage.
- - - - -
453a34db by Sven Tennie at 2025-10-31T17:17:16+01:00
Fix libffi ghcjs
- - - - -
b5b4210d by Sven Tennie at 2025-10-31T17:24:58+01:00
WIP: libffi: LD, OBJDUMP, STRIP staged
Removing the env variables implies using the programs from $PATH. This
kind-of works, but these values should be correctly auto-configured.
- - - - -
79a44baa by Sven Tennie at 2025-10-31T17:28:22+01:00
Make stage2 cross windows build work - somehow
Still needs some improvements.
- - - - -
05d00f35 by Sven Tennie at 2025-10-31T17:28:58+01:00
Adjust host_fully_static for stage2 cross builds
- - - - -
b400cb8f by Sven Tennie at 2025-10-31T17:28:58+01:00
Reference correct package.conf.d for cross
- - - - -
bbe9d866 by Sven Tennie at 2025-10-31T17:50:49+01:00
Fixup Rebase
- - - - -
ff34fa24 by Sven Tennie at 2025-10-31T18:00:09+01:00
Fixup: Align Settings
- - - - -
97146afc by Sven Tennie at 2025-10-31T18:02:35+01:00
Libffi - no LD for cross host stages
- - - - -
97c14acc by Sven Tennie at 2025-11-01T10:21:52+01:00
Rebase fixup
- - - - -
348 changed files:
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitmodules
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/UniqueRenamer.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Simplify/Monad.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/Word64Map/Internal.hs
- compiler/GHC/Data/Word64Map/Lazy.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Config/Stg/Debug.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Foreign/JavaScript.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Pmc/Utils.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Binary.hs
- compiler/GHC/Iface/Flags.hs
- compiler/GHC/Iface/Recomp/Flags.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/JS/JStg/Monad.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Platform/Reg.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Stg/Debug.hs
- + compiler/GHC/Stg/Debug/Types.hs
- compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/StgToCmm/ExtCode.hs
- compiler/GHC/StgToCmm/Monad.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Ids.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Types/Unique/DFM.hs
- compiler/GHC/Types/Unique/DSM.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Supply.hs
- compiler/GHC/Types/Var/Env.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/debug-info.rst
- docs/users_guide/ghci.rst
- docs/users_guide/using.rst
- hadrian/README.md
- hadrian/bindist/config.mk.in
- hadrian/cfg/default.host.target.in
- + hadrian/cfg/system.config.host.in
- hadrian/cfg/system.config.in
- + hadrian/cfg/system.config.target.in
- hadrian/hadrian.cabal
- hadrian/src/Base.hs
- + hadrian/src/BindistConfig.hs
- hadrian/src/Builder.hs
- hadrian/src/Context.hs
- hadrian/src/Expression.hs
- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Hadrian/Builder.hs
- hadrian/src/Hadrian/Expression.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Hadrian/Haskell/Hash.hs
- hadrian/src/Hadrian/Oracles/TextFile.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Flavour.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Oracles/TestSettings.hs
- hadrian/src/Packages.hs
- hadrian/src/Rules.hs
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Rules/CabalReinstall.hs
- hadrian/src/Rules/Compile.hs
- hadrian/src/Rules/Documentation.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Gmp.hs
- hadrian/src/Rules/Libffi.hs
- hadrian/src/Rules/Library.hs
- hadrian/src/Rules/Program.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/Rts.hs
- hadrian/src/Rules/Test.hs
- hadrian/src/Settings.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/Common.hs
- hadrian/src/Settings/Builders/Configure.hs
- hadrian/src/Settings/Builders/DeriveConstants.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Builders/Hsc2Hs.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Builders/SplitSections.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Benchmark.hs
- hadrian/src/Settings/Flavours/Development.hs
- hadrian/src/Settings/Flavours/GhcInGhci.hs
- hadrian/src/Settings/Flavours/Performance.hs
- hadrian/src/Settings/Flavours/Quick.hs
- hadrian/src/Settings/Flavours/QuickCross.hs
- hadrian/src/Settings/Flavours/Quickest.hs
- hadrian/src/Settings/Flavours/Validate.hs
- hadrian/src/Settings/Packages.hs
- hadrian/src/Settings/Program.hs
- hadrian/src/Settings/Warnings.hs
- libraries/base/src/GHC/Base.hs
- libraries/base/src/GHC/Exts.hs
- libraries/ghc-experimental/CHANGELOG.md
- libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- + libraries/ghc-internal/cbits/RtsIface.c
- libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/include/RtsIfaceSymbols.h
- + libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- + libraries/ghc-internal/tests/backtraces/T26507.hs
- + libraries/ghc-internal/tests/backtraces/T26507.stderr
- libraries/ghc-internal/tests/backtraces/all.T
- libraries/ghc-internal/tests/stack-annotation/all.T
- libraries/ghc-prim/changelog.md
- + libraries/template-haskell-lift
- + libraries/template-haskell-quasiquoter
- m4/fp_check_pthreads.m4
- m4/fp_find_nm.m4
- m4/fptools_alex.m4
- m4/fptools_happy.m4
- m4/fptools_set_platform_vars.m4
- m4/prep_target_file.m4
- rts/BuiltinClosures.c
- rts/CloneStack.h
- rts/Compact.cmm
- rts/ContinuationOps.cmm
- rts/Exception.cmm
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/Printer.c
- rts/RtsAPI.c
- rts/RtsStartup.c
- rts/RtsSymbols.c
- + rts/RtsToHsIface.c
- rts/StgStdThunks.cmm
- rts/configure.ac
- − rts/external-symbols.list.in
- rts/include/Rts.h
- rts/include/RtsAPI.h
- rts/include/Stg.h
- + rts/include/rts/RtsToHsIface.h
- rts/include/rts/Types.h
- rts/include/stg/Prim.h
- rts/posix/OSMem.c
- rts/posix/Signals.c
- libraries/ghc-internal/cbits/atomic.c → rts/prim/atomic.c
- libraries/ghc-internal/cbits/bitrev.c → rts/prim/bitrev.c
- libraries/ghc-internal/cbits/bswap.c → rts/prim/bswap.c
- libraries/ghc-internal/cbits/clz.c → rts/prim/clz.c
- libraries/ghc-internal/cbits/ctz.c → rts/prim/ctz.c
- libraries/ghc-internal/cbits/int64x2minmax.c → rts/prim/int64x2minmax.c
- libraries/ghc-internal/cbits/longlong.c → rts/prim/longlong.c
- libraries/ghc-internal/cbits/mulIntMayOflo.c → rts/prim/mulIntMayOflo.c
- libraries/ghc-internal/cbits/pdep.c → rts/prim/pdep.c
- libraries/ghc-internal/cbits/pext.c → rts/prim/pext.c
- libraries/ghc-internal/cbits/popcnt.c → rts/prim/popcnt.c
- libraries/ghc-internal/cbits/vectorQuotRem.c → rts/prim/vectorQuotRem.c
- libraries/ghc-internal/cbits/word2float.c → rts/prim/word2float.c
- rts/rts.buildinfo.in
- rts/rts.cabal
- rts/wasm/JSFFI.c
- rts/wasm/scheduler.cmm
- rts/win32/libHSghc-internal.def
- testsuite/driver/cpu_features.py
- testsuite/ghc-config/ghc-config.hs
- testsuite/tests/codeGen/should_gen_asm/all.T
- + testsuite/tests/codeGen/should_gen_asm/mavx-should-enable-popcnt.asm
- + testsuite/tests/codeGen/should_gen_asm/mavx-should-enable-popcnt.hs
- + testsuite/tests/codeGen/should_gen_asm/msse-option-order.asm
- + testsuite/tests/codeGen/should_gen_asm/msse-option-order.hs
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/ghc-api/T26264.hs
- + testsuite/tests/ghc-api/T26264.stdout
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-e/should_fail/all.T
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/linters/all.T
- testsuite/tests/module/mod4.stderr
- testsuite/tests/overloadedrecflds/should_compile/BootFldReexport.stderr
- testsuite/tests/overloadedrecflds/should_fail/T16745.stderr
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
- + testsuite/tests/overloadedrecflds/should_fail/T26480.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480.stderr
- + testsuite/tests/overloadedrecflds/should_fail/T26480_aux1.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480_aux2.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480b.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480b.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
- testsuite/tests/overloadedrecflds/should_fail/hasfieldfail01.stderr
- testsuite/tests/overloadedrecflds/should_fail/hasfieldfail02.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.hs
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
- + testsuite/tests/parser/should_fail/T12488c.hs
- + testsuite/tests/parser/should_fail/T12488c.stderr
- + testsuite/tests/parser/should_fail/T12488d.hs
- + testsuite/tests/parser/should_fail/T12488d.stderr
- testsuite/tests/parser/should_fail/all.T
- + testsuite/tests/patsyn/should_compile/T26465b.hs
- + testsuite/tests/patsyn/should_compile/T26465c.hs
- + testsuite/tests/patsyn/should_compile/T26465d.hs
- + testsuite/tests/patsyn/should_compile/T26465d.stderr
- testsuite/tests/patsyn/should_compile/all.T
- + testsuite/tests/patsyn/should_fail/T26465.hs
- + testsuite/tests/patsyn/should_fail/T26465.stderr
- testsuite/tests/patsyn/should_fail/all.T
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/perf/should_run/T3586.hs
- testsuite/tests/perf/should_run/UniqLoop.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/regalloc/regalloc_unit_tests.hs
- + testsuite/tests/rename/should_compile/T12488b.hs
- + testsuite/tests/rename/should_compile/T12488f.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/rename/should_fail/T12488a.hs
- + testsuite/tests/rename/should_fail/T12488a.stderr
- + testsuite/tests/rename/should_fail/T12488a_foo.hs
- + testsuite/tests/rename/should_fail/T12488a_foo.stderr
- + testsuite/tests/rename/should_fail/T12488e.hs
- + testsuite/tests/rename/should_fail/T12488e.stderr
- + testsuite/tests/rename/should_fail/T12488g.hs
- + testsuite/tests/rename/should_fail/T12488g.stderr
- testsuite/tests/rename/should_fail/T19843h.stderr
- testsuite/tests/rename/should_fail/T25899e2.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rts/T22859.hs
- + testsuite/tests/rts/ipe/distinct-tables/Main.hs
- + testsuite/tests/rts/ipe/distinct-tables/Makefile
- + testsuite/tests/rts/ipe/distinct-tables/X.hs
- + testsuite/tests/rts/ipe/distinct-tables/all.T
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables01.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables02.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables03.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables04.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables05.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables06.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables07.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables08.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables09.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables10.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables11.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables12.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables13.stdout
- testsuite/tests/simd/should_run/all.T
- + testsuite/tests/simd/should_run/simd015.hs
- + testsuite/tests/simd/should_run/simd015.stdout
- + testsuite/tests/simd/should_run/simd016.hs
- + testsuite/tests/simd/should_run/simd016.stdout
- + testsuite/tests/simd/should_run/simd017.hs
- + testsuite/tests/simd/should_run/simd017.stdout
- testsuite/tests/simplCore/should_compile/rule2.stderr
- testsuite/tests/th/T8761.stderr
- + testsuite/tests/typecheck/should_compile/T17705.hs
- testsuite/tests/typecheck/should_compile/all.T
- utils/check-exact/ExactPrint.hs
- utils/deriveConstants/Main.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/jsffi/dyld.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fca890d0913f6b5e60d91fe34bd4f7…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fca890d0913f6b5e60d91fe34bd4f7…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: ghc-toolchain: detect PowerPC 64 bit ABI
by Marge Bot (@marge-bot) 01 Nov '25
by Marge Bot (@marge-bot) 01 Nov '25
01 Nov '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
f75ab223 by Peter Trommler at 2025-10-31T18:43:13-04:00
ghc-toolchain: detect PowerPC 64 bit ABI
Check preprocessor macro defined for ABI v2 and assume v1 otherwise.
Fixes #26521
- - - - -
d086c474 by Peter Trommler at 2025-10-31T18:43:13-04:00
ghc-toolchain: refactor, move lastLine to Utils
- - - - -
995dfe0d by Vladislav Zavialov at 2025-10-31T18:43:54-04:00
Tests for -Wduplicate-exports, -Wdodgy-exports
Add test cases for the previously untested diagnostics:
[GHC-51876] TcRnDupeModuleExport
[GHC-64649] TcRnNullExportedModule
This also revealed a typo (incorrect capitalization of "module") in the
warning text for TcRnDupeModuleExport, which is now fixed.
- - - - -
f6961b02 by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: reformat dyld source code
This commit reformats dyld source code with prettier, to avoid
introducing unnecessary diffs in subsequent patches when they're
formatted before committing.
- - - - -
0c9032a0 by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: simplify _initialize logic in dyld
This commit simplifies how we _initialize a wasm shared library in
dyld and removes special treatment for libc.so, see added comment for
detailed explanation.
- - - - -
ec1b40bd by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: support running dyld fully client side in the browser
This commit refactors the wasm dyld script so that it can be used to
load and run wasm shared libraries fully client-side in the browser
without needing a wasm32-wasi-ghci backend:
- A new `DyLDBrowserHost` class is exported, which runs in the browser
and uses the in-memory vfs without any RPC calls. This meant to be
used to create a `rpc` object for the fully client side use cases.
- The exported `main` function now can be used to load user-specified
shared libraries, and the user can use the returned `DyLD` instance
to run their own exported Haskell functions.
- The in-browser wasi implementation is switched to
https://github.com/haskell-wasm/browser_wasi_shim for bugfixes and
major performance improvements not landed upstream yet.
- When being run by deno, it now correctly switches to non-nodejs code
paths, so it's more convenient to test dyld logic with deno.
See added comments for details, as well as the added `playground001`
test case for an example of using it to build an in-browser Haskell
playground.
- - - - -
8f3e481f by Cheng Shao at 2025-11-01T00:08:01+01:00
testsuite: add playground001 to test haskell playground
This commit adds the playground001 test case to test the haskell
playground in browser, see comments for details.
- - - - -
af40606a by Cheng Shao at 2025-11-01T00:08:04+01:00
Revert "testsuite: add T26431 test case"
This reverts commit 695036686f8c6d78611edf3ed627608d94def6b7. T26431
is now retired, wasm ghc internal-interpreter logic is tested by
playground001.
- - - - -
21d446c5 by Vladislav Zavialov at 2025-11-01T01:23:22-04:00
Supplant TcRnExportHiddenComponents with TcRnDodgyExports (#26534)
Remove a bogus special case in lookup_ie_kids_all,
making TcRnExportHiddenComponents obsolete.
- - - - -
29 changed files:
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Types/Error/Codes.hs
- testsuite/tests/diagnostic-codes/codes.stdout
- + testsuite/tests/ghc-api-browser/README.md
- + testsuite/tests/ghc-api-browser/all.T
- + testsuite/tests/ghc-api-browser/index.html
- + testsuite/tests/ghc-api-browser/playground001.hs
- + testsuite/tests/ghc-api-browser/playground001.js
- + testsuite/tests/ghc-api-browser/playground001.sh
- testsuite/tests/ghci-wasm/T26431.stdout → testsuite/tests/ghc-api-browser/playground001.stdout
- − testsuite/tests/ghci-wasm/T26431.hs
- testsuite/tests/ghci-wasm/all.T
- + testsuite/tests/warnings/should_compile/DodgyExports02.hs
- + testsuite/tests/warnings/should_compile/DodgyExports02.stderr
- + testsuite/tests/warnings/should_compile/DodgyExports03.hs
- + testsuite/tests/warnings/should_compile/DodgyExports03.stderr
- + testsuite/tests/warnings/should_compile/DuplicateModExport.hs
- + testsuite/tests/warnings/should_compile/DuplicateModExport.stderr
- + testsuite/tests/warnings/should_compile/EmptyModExport.hs
- + testsuite/tests/warnings/should_compile/EmptyModExport.stderr
- testsuite/tests/warnings/should_compile/all.T
- utils/ghc-toolchain/ghc-toolchain.cabal
- utils/ghc-toolchain/src/GHC/Toolchain/CheckArm.hs
- + utils/ghc-toolchain/src/GHC/Toolchain/CheckPower.hs
- utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Utils.hs
- utils/jsffi/dyld.mjs
Changes:
=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -619,7 +619,7 @@ instance Diagnostic TcRnMessage where
TcRnDupeModuleExport mod
-> mkSimpleDecorated $
hsep [ text "Duplicate"
- , quotes (text "Module" <+> ppr mod)
+ , quotes (text "module" <+> ppr mod)
, text "in export list" ]
TcRnExportedModNotImported mod
-> mkSimpleDecorated
@@ -636,11 +636,6 @@ instance Diagnostic TcRnMessage where
$ formatExportItemError
(text "module" <+> ppr mod)
"is missing an export list"
- TcRnExportHiddenComponents export_item
- -> mkSimpleDecorated
- $ formatExportItemError
- (ppr export_item)
- "attempts to export constructors or class methods that are not visible here"
TcRnExportHiddenDefault export_item
-> mkSimpleDecorated
$ formatExportItemError
@@ -2231,8 +2226,6 @@ instance Diagnostic TcRnMessage where
-> WarningWithFlag Opt_WarnDodgyExports
TcRnMissingExportList{}
-> WarningWithFlag Opt_WarnMissingExportList
- TcRnExportHiddenComponents{}
- -> ErrorWithoutFlag
TcRnExportHiddenDefault{}
-> ErrorWithoutFlag
TcRnDuplicateExport{}
@@ -2904,8 +2897,6 @@ instance Diagnostic TcRnMessage where
-> noHints
TcRnMissingExportList{}
-> noHints
- TcRnExportHiddenComponents{}
- -> noHints
TcRnExportHiddenDefault{}
-> noHints
TcRnDuplicateExport{}
=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -1567,10 +1567,11 @@ data TcRnMessage where
occurs when a module appears more than once in an export list.
Example(s):
- module Foo (module Bar, module Bar)
- import Bar
+ module Foo (module Bar, module Bar) where
+ import Bar
- Text cases: None
+ Text cases:
+ DuplicateModExport
-}
TcRnDupeModuleExport :: ModuleName -> TcRnMessage
@@ -1590,10 +1591,11 @@ data TcRnMessage where
when an export list contains a module that has no exports.
Example(s):
- module Foo (module Bar) where
- import Bar ()
+ module Foo (module Bar) where
+ import Bar ()
- Test cases: None
+ Test cases:
+ EmptyModExport
-}
TcRnNullExportedModule :: ModuleName -> TcRnMessage
@@ -1606,15 +1608,6 @@ data TcRnMessage where
-}
TcRnMissingExportList :: ModuleName -> TcRnMessage
- {-| TcRnExportHiddenComponents is an error that occurs when an export contains
- constructor or class methods that are not visible.
-
- Example(s): None
-
- Test cases: None
- -}
- TcRnExportHiddenComponents :: IE GhcPs -> TcRnMessage
-
{-| TcRnExportHiddenDefault is an error that occurs when an export contains
a class default (with language extension NamedDefaults) that is not visible.
=====================================
compiler/GHC/Tc/Gen/Export.hs
=====================================
@@ -526,7 +526,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
} (L loc ie@(IEThingAll (warn_txt_ps, ann) l doc))
= do mb_gre <- lookupGreAvailRn (ieLWrappedNameWhatLooking l) $ lieWrappedName l
for mb_gre $ \ par -> do
- all_kids <- lookup_ie_kids_all ie l par
+ all_kids <- lookup_ie_kids_all l par
let name = greName par
all_gres = par : all_kids
all_names = map greName all_gres
@@ -562,7 +562,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
wc_kids <-
case wc of
NoIEWildcard -> return []
- IEWildcard _ -> lookup_ie_kids_all ie l par
+ IEWildcard _ -> lookup_ie_kids_all l par
let name = greName par
all_kids = with_kids ++ wc_kids
@@ -595,20 +595,15 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
; kids <- lookupChildrenExport gre child_gres sub_rdrs
; return (unzip kids) }
- lookup_ie_kids_all :: IE GhcPs -> LIEWrappedName GhcPs -> GlobalRdrElt
+ lookup_ie_kids_all :: LIEWrappedName GhcPs -> GlobalRdrElt
-> RnM [GlobalRdrElt]
- lookup_ie_kids_all ie (L _loc rdr) gre =
+ lookup_ie_kids_all (L _loc rdr) gre =
do { let name = greName gre
gres = findChildren kids_env name
-- We only choose level 0 exports when filling in part of an export list implicitly.
; let kids_0 = mapMaybe pickLevelZeroGRE gres
; addUsedKids (ieWrappedName rdr) kids_0
- ; when (null kids_0) $
- if isTyConName name
- then addTcRnDiagnostic (TcRnDodgyExports gre)
- else -- This occurs when you export T(..), but
- -- only import T abstractly, or T is a synonym.
- addErr (TcRnExportHiddenComponents ie)
+ ; when (null kids_0) $ addTcRnDiagnostic (TcRnDodgyExports gre)
; return kids_0 }
-------------
=====================================
compiler/GHC/Types/Error/Codes.hs
=====================================
@@ -505,7 +505,7 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "TcRnExportedModNotImported" = 90973
GhcDiagnosticCode "TcRnNullExportedModule" = 64649
GhcDiagnosticCode "TcRnMissingExportList" = 85401
- GhcDiagnosticCode "TcRnExportHiddenComponents" = 94558
+ GhcDiagnosticCode "TcRnExportHiddenComponents" = Outdated 94558
GhcDiagnosticCode "TcRnExportHiddenDefault" = 74775
GhcDiagnosticCode "TcRnDuplicateExport" = 47854
GhcDiagnosticCode "TcRnDuplicateNamedDefaultExport" = 31584
=====================================
testsuite/tests/diagnostic-codes/codes.stdout
=====================================
@@ -50,9 +50,6 @@
[GHC-17268] is untested (constructor = TcRnCharLiteralOutOfRange)
[GHC-36495] is untested (constructor = TcRnTagToEnumMissingValArg)
[GHC-55868] is untested (constructor = TcRnArrowIfThenElsePredDependsOnResultTy)
-[GHC-51876] is untested (constructor = TcRnDupeModuleExport)
-[GHC-64649] is untested (constructor = TcRnNullExportedModule)
-[GHC-94558] is untested (constructor = TcRnExportHiddenComponents)
[GHC-63055] is untested (constructor = TcRnFieldUpdateInvalidType)
[GHC-26133] is untested (constructor = TcRnForeignImportPrimSafeAnn)
[GHC-03355] is untested (constructor = TcRnIllegalForeignDeclBackend)
=====================================
testsuite/tests/ghc-api-browser/README.md
=====================================
@@ -0,0 +1,124 @@
+# The Haskell playground browser test
+
+This directory contains the `playground001` test, which builds a fully
+client side Haskell playground in the browser, then runs a
+puppeteer-based test to actually interpret a Haskell program in a
+headless browser.
+
+## Headless testing
+
+`playground001` is tested in GHC CI. To test it locally, first ensure
+you've set up the latest
+[`ghc-wasm-meta`](https://gitlab.haskell.org/haskell-wasm/ghc-wasm-meta)
+toolchain and sourced the `~/.ghc-wasm/env` script, so the right
+`node` with the right pre-installed libraries are used. Additionally,
+you need to install latest Firefox and:
+
+```sh
+export FIREFOX_LAUNCH_OPTS='{"browser":"firefox","executablePath":"/usr/bin/firefox"}'`
+```
+
+Or on macOS:
+
+```sh
+export FIREFOX_LAUNCH_OPTS='{"browser":"firefox","executablePath":"/Applications/Firefox.app/Contents/MacOS/firefox"}'
+```
+
+Without `FIREFOX_LAUNCH_OPTS`, `playground001` is skipped.
+
+It's possible to test against Chrome as well, the
+[`playground001.js`](./playground001.js) test driver doesn't assume
+anything Firefox-specific, it just takes the
+[`puppeteer.launch`](https://pptr.dev/api/puppeteer.puppeteernode.launch)
+options as JSON passed via command line.
+
+`playground001` works on latest versions of Firefox/Chrome/Safari.
+
+## Manual testing
+
+The simplest way to build the playground manually and run it in a
+browser tab is to test it once with `--only=playground001
+--keep-test-files` passed to Hadrian, then you can find the temporary
+directory containing [`index.html`](./index.html), `rootfs.tar.zst`
+etc, then fire up a dev web server and load it.
+
+Additionally, you can build the playground in tree without invoking
+the GHC testsuite. Just build GHC with the wasm target first, then
+copy `utils/jsffi/*.mjs` here and run
+[`./playground001.sh`](./playground001.sh) script. You need to set
+`TEST_CC` to the path of `wasm32-wasi-clang` and `TEST_HC` to the path
+of `wasm32-wasi-ghc`, that's it.
+
+## Customized Haskell playground
+
+You may want to build a customized Haskell playground that uses GHC
+API to interpret Haskell code with custom packages, here are some tips
+to get started:
+
+- Read the code in this directory and figure out how `playground001`
+ itself works.
+- [`./playground001.sh`](./playground001.sh) can be used as a basis to
+ write your own build/test script.
+
+You don't need to read the full `dyld.mjs` script. The user-facing
+things that are relevant to the playground use case are:
+
+- `export class DyLDBrowserHost`: it is the `rpc` object required when
+ calling `main`. You need to pass `stdout`/`stderr` callbacks to
+ write each line of stdout/stderr, as well as a `rootfs` object that
+ represents an in-memory vfs containing the shared libraries to load.
+- `export async function main`: it eventually returns a `DyLD` object
+ that can be used like `await
+ dyld.exportFuncs.myExportedHaskellFunc(js_foo, js_bar)` to invoke
+ your exported Haskell function.
+
+Check the source code of [`index.html`](./index.html) and cross
+reference [`playground001.hs`](./playground001.hs) for the example of
+how they are used.
+
+The `rootfs` object is a
+[`PreopenDirectory`](https://github.com/haskell-wasm/browser_wasi_shim/blob/master/src/fs_mem.ts)
+object in the
+[`browser_wasi_shim`](https://github.com/haskell-wasm/browser_wasi_shim)
+library. The Haskell playground needs a complex vfs containing many
+files (shared libraries, interface files, package databases, etc), so
+to speed things up, the whole vfs is compressed into a
+`rootfs.tar.zst` archive, then that archive is extracted using
+[`bsdtar-wasm`](https://github.com/haskell-wasm/bsdtar-wasm).
+
+You don't need to read the source code of `browser_wasi_shim`; you can
+simply paste and adapt the relevant code snippet in
+[`index.html`](./index.html) to create the right `rootfs` object from
+a tarball.
+
+The main concern is what do you need to pack into `rootfs.tar.zst`.
+For `playground001`, it contains:
+
+- `/tmp/clib`: the C/C++ shared libraries
+- `/tmp/hslib/lib`: the GHC libdir
+- `/tmp/libplayground001.so`: the main shared library to start loading
+ that exports `myMain`
+
+You can read [`./playground001.sh`](./playground001.sh) to figure out
+the details of how I prepare `rootfs.tar.zst` and trim unneeded files
+to minimize the tarball size.
+
+There are multiple possible ways to install third-party packages in
+the playground:
+
+- Start from a `wasm32-wasi-ghc` installation, use `wasm32-wasi-cabal
+ v1-install --global` to install everything to the global package
+ database. In theory this is the simplest way, though I haven't tried
+ it myself and it's unclear to what extent do `v1` commands work
+ these days.
+- Use default nix-style installation, then package the cabal store and
+ `dist-newstyle` directories into `rootfs.tar.zst`, and pass the
+ right package database flags when calling GHC API.
+
+Note that cabal built packages are not relocatable! So things will
+break if you build them at a host location and then package into a
+different absolute path into the rootfs, keep this in mind.
+
+If you have any difficulties, you're welcome to the [Haskell
+Wasm](https://matrix.to/#/#haskell.wasm:matrix.org) matrix room for
+community support.
=====================================
testsuite/tests/ghc-api-browser/all.T
=====================================
@@ -0,0 +1,52 @@
+# makefile_test/run_command is skipped when config.target_wrapper is
+# not None, see test_common_work in testsuite/driver/testlib.py. for
+# now just use this workaround to run custom test script here; ideally
+# we'd fix test failures elsewhere and enable
+# makefile_test/run_command for cross targets some day.
+async def stub_run_command(name, way, cmd):
+ return await run_command(name, way, cmd)
+
+
+# config.target_wrapper is prepended when running any command when
+# testing a cross target, see simple_run in
+# testsuite/driver/testlib.py. this is problematic when running a host
+# test script. for now do this override; ideally we'd have clear
+# host/target distinction for command invocations in the testsuite
+# driver instead of just a command string.
+def override_target_wrapper(name, opts):
+ opts.target_wrapper = ""
+
+
+setTestOpts(
+ [
+ unless(arch("wasm32"), skip),
+ override_target_wrapper,
+ high_memory_usage,
+ ignore_stderr,
+ only_ways(["dyn"]),
+ extra_ways(["dyn"]),
+ ]
+)
+
+
+test(
+ "playground001",
+ [
+ # pretty heavyweight, just test one browser for now.
+ unless("FIREFOX_LAUNCH_OPTS" in ghc_env, skip),
+ extra_files(
+ [
+ "../../../.gitlab/hello.hs",
+ "../../../utils/jsffi/dyld.mjs",
+ "../../../utils/jsffi/post-link.mjs",
+ "../../../utils/jsffi/prelude.mjs",
+ "index.html",
+ "playground001.hs",
+ "playground001.js",
+ "playground001.sh",
+ ]
+ ),
+ ],
+ stub_run_command,
+ ['./playground001.sh "$FIREFOX_LAUNCH_OPTS"'],
+)
=====================================
testsuite/tests/ghc-api-browser/index.html
=====================================
@@ -0,0 +1,234 @@
+<!DOCTYPE html>
+<html lang="en">
+ <head>
+ <meta charset="utf-8" />
+ <meta name="viewport" content="width=device-width, initial-scale=1" />
+ <title>ghc-in-browser</title>
+ <link
+ rel="stylesheet"
+ href="https://cdn.jsdelivr.net/npm/modern-normalize/modern-normalize.min.css"
+ />
+ <style>
+ html,
+ body {
+ height: 100%;
+ }
+ body {
+ margin: 0;
+ font-family: system-ui, -apple-system, Segoe UI, Roboto, sans-serif;
+ background: #0f172a;
+ color: #e5e7eb;
+ }
+ .app {
+ height: 100vh;
+ display: grid;
+ gap: 0.5rem;
+ padding: 0.5rem;
+ }
+ @media (min-width: 800px) {
+ .app {
+ grid-template-columns: 1fr 1fr;
+ }
+ }
+ @media (max-width: 799.98px) {
+ .app {
+ grid-template-rows: 1fr 1fr;
+ }
+ }
+ .pane {
+ background: #111827;
+ border: 1px solid #1f2937;
+ border-radius: 12px;
+ display: flex;
+ flex-direction: column;
+ min-height: 0;
+ }
+ header {
+ padding: 0.5rem 0.75rem;
+ border-bottom: 1px solid #1f2937;
+ font-weight: 600;
+ }
+ #editor {
+ flex: 1;
+ min-height: 0;
+ }
+ .right {
+ padding: 0.6rem;
+ gap: 0.6rem;
+ }
+ .controls {
+ display: flex;
+ gap: 0.5rem;
+ flex-wrap: wrap;
+ margin-bottom: 0.4rem;
+ }
+ .controls input[type="text"] {
+ flex: 1;
+ min-width: 200px;
+ background: #0b1020;
+ color: #e5e7eb;
+ border: 1px solid #223;
+ border-radius: 8px;
+ padding: 0.55rem;
+ }
+ .controls button {
+ background: #22c55e;
+ border: none;
+ border-radius: 8px;
+ padding: 0.55rem 0.85rem;
+ font-weight: 600;
+ cursor: pointer;
+ }
+ .outputs {
+ display: block;
+ }
+ .outputs .label {
+ font-size: 0.85rem;
+ opacity: 0.8;
+ margin: 0.35rem 0;
+ }
+ .outputs textarea {
+ display: block;
+ width: 100%;
+ min-height: 30vh;
+ background: #0b1020;
+ color: #d1fae5;
+ border: 1px solid #223;
+ border-radius: 8px;
+ padding: 0.6rem;
+ resize: vertical;
+ }
+ .stderr {
+ color: #fee2e2;
+ }
+ </style>
+
+ <script async type="module">
+ import * as monaco from "https://cdn.jsdelivr.net/npm/monaco-editor/+esm";
+ import {
+ ConsoleStdout,
+ File,
+ OpenFile,
+ PreopenDirectory,
+ WASI,
+ } from "https://esm.sh/gh/haskell-wasm/browser_wasi_shim";
+ import { DyLDBrowserHost, main } from "./dyld.mjs";
+
+ const rootfs = new PreopenDirectory("/", []);
+
+ const bsdtar_wasi = new WASI(
+ ["bsdtar.wasm", "-x"],
+ [],
+ [
+ new OpenFile(new File(new Uint8Array(), { readonly: true })),
+ ConsoleStdout.lineBuffered((msg) => console.info(msg)),
+ ConsoleStdout.lineBuffered((msg) => console.warn(msg)),
+ rootfs,
+ ],
+ { debug: false }
+ );
+
+ const [{ instance }, rootfs_bytes] = await Promise.all([
+ WebAssembly.instantiateStreaming(
+ fetch("https://haskell-wasm.github.io/bsdtar-wasm/bsdtar.wasm"),
+ { wasi_snapshot_preview1: bsdtar_wasi.wasiImport }
+ ),
+ fetch("./rootfs.tar.zst").then((r) => r.bytes()),
+ ]);
+
+ bsdtar_wasi.fds[0] = new OpenFile(
+ new File(rootfs_bytes, { readonly: true })
+ );
+ bsdtar_wasi.start(instance);
+
+ if (document.readyState === "loading") {
+ await new Promise((res) =>
+ document.addEventListener("DOMContentLoaded", res, { once: true })
+ );
+ }
+
+ window.editor = monaco.editor.create(document.getElementById("editor"), {
+ value: 'main :: IO ()\nmain = putStrLn "Hello, Haskell!"\n',
+ language: "haskell",
+ automaticLayout: true,
+ minimap: { enabled: false },
+ theme: "vs-dark",
+ fontSize: 14,
+ });
+
+ const dyld = await main({
+ rpc: new DyLDBrowserHost({
+ rootfs,
+ stdout: (msg) => {
+ document.getElementById("stdout").value += `${msg}\n`;
+ },
+ stderr: (msg) => {
+ document.getElementById("stderr").value += `${msg}\n`;
+ },
+ }),
+ searchDirs: [
+ "/tmp/clib",
+ "/tmp/hslib/lib/wasm32-wasi-ghc-9.15.20251024",
+ ],
+ mainSoPath: "/tmp/libplayground001.so",
+ args: ["libplayground001.so", "+RTS", "-c", "-RTS"],
+ isIserv: false,
+ });
+ const main_func = await dyld.exportFuncs.myMain("/tmp/hslib/lib");
+
+ document.getElementById("runBtn").addEventListener("click", async () => {
+ document.getElementById("runBtn").disabled = true;
+
+ try {
+ document.getElementById("stdout").value = "";
+ document.getElementById("stderr").value = "";
+
+ await main_func(
+ document.getElementById("ghcArgs").value,
+ editor.getValue()
+ );
+ } finally {
+ document.getElementById("runBtn").disabled = false;
+ }
+ });
+
+ document.getElementById("runBtn").disabled = false;
+ </script>
+ </head>
+ <body>
+ <div class="app">
+ <section class="pane">
+ <header>Haskell Source</header>
+ <div id="editor"></div>
+ </section>
+
+ <section class="pane right">
+ <header>Controls / Output</header>
+ <div class="controls">
+ <input
+ id="ghcArgs"
+ type="text"
+ placeholder="GHC args"
+ style="font-family: ui-monospace, Menlo, Consolas, monospace"
+ />
+ <button id="runBtn" disabled="true">Run</button>
+ </div>
+ <div class="outputs">
+ <div class="label">stdout</div>
+ <textarea
+ id="stdout"
+ readonly
+ style="font-family: ui-monospace, Menlo, Consolas, monospace"
+ ></textarea>
+ <div class="label">stderr</div>
+ <textarea
+ id="stderr"
+ class="stderr"
+ readonly
+ style="font-family: ui-monospace, Menlo, Consolas, monospace"
+ ></textarea>
+ </div>
+ </section>
+ </div>
+ </body>
+</html>
=====================================
testsuite/tests/ghc-api-browser/playground001.hs
=====================================
@@ -0,0 +1,95 @@
+module Playground
+ ( myMain,
+ )
+where
+
+import Control.Monad
+import Data.Coerce
+import Data.IORef
+import GHC
+import GHC.Driver.Config.Diagnostic
+import GHC.Driver.Errors
+import GHC.Driver.Errors.Types
+import GHC.Driver.Monad
+import GHC.Plugins
+import GHC.Runtime.Interpreter
+import GHC.Utils.Exception
+import GHC.Wasm.Prim
+
+newtype JSFunction t = JSFunction JSVal
+
+type ExportedMainFunction = JSString -> JSString -> IO ()
+
+-- main entry point of playground001, returns a js async function that
+-- takes ghc args and Main.hs content, interprets Main.hs and runs
+-- Main.main.
+myMain :: JSString -> IO (JSFunction ExportedMainFunction)
+myMain js_libdir =
+ defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
+ libdir <- evaluate $ fromJSString js_libdir
+ freeJSVal $ coerce js_libdir
+ -- we don't use runGhc since we want to share a session to be
+ -- reused.
+ session <- Session <$> newIORef undefined
+ -- save a fresh default dflags, otherwise user input ghc args are
+ -- not properly reset.
+ dflags0 <- flip reflectGhc session $ do
+ initGhcMonad (Just libdir)
+ dflags0 <- getSessionDynFlags
+ setSessionDynFlags $
+ dflags0
+ { ghcMode = CompManager,
+ backend = bytecodeBackend,
+ ghcLink = LinkInMemory,
+ verbosity = 1
+ }
+ getSessionDynFlags
+ -- this is always run in a forked thread. which is fine as long as
+ -- the sesssion is not reused concurrently, but it's up to the
+ -- caller in js to ensure that. we simply disable the run button
+ -- until each run completes in the playground ui logic.
+ toMainFunc $ \js_args js_src ->
+ defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
+ args <- evaluate $ words $ fromJSString js_args
+ freeJSVal $ coerce js_args
+ writeFile f $ fromJSString js_src
+ freeJSVal $ coerce js_src
+ -- it's fine to call withCleanupSession since it just cleans up
+ -- tmpfs for now. in the future if it does more cleanup that
+ -- makes the session state invalid for reuse, just remove it;
+ -- everything will be cleaned up anyway when the browser tab is
+ -- closed
+ flip reflectGhc session $ withCleanupSession $ do
+ setSessionDynFlags dflags0
+ logger0 <- getLogger
+ (dflags1, _, dynamicFlagWarnings) <-
+ parseDynamicFlags logger0 dflags0 $ map noLoc args
+ setSessionDynFlags dflags1
+ logger1 <- getLogger
+ liftIO
+ $ printOrThrowDiagnostics
+ logger1
+ (initPrintConfig dflags1)
+ (initDiagOpts dflags1)
+ $ GhcDriverMessage
+ <$> dynamicFlagWarnings
+ setTargets =<< (: []) <$> guessTarget f Nothing Nothing
+ r <- load LoadAllTargets
+ when (failed r) $ fail "load returned Failed"
+ setContext [IIDecl $ simpleImportDecl $ mkModuleName "Main"]
+ fhv <- compileExprRemote "Main.main"
+ hsc_env <- getSession
+ liftIO $ evalIO (hscInterp hsc_env) fhv
+ where
+ f = "/tmp/Main.hs"
+
+foreign import javascript "wrapper"
+ toMainFunc ::
+ ExportedMainFunction ->
+ IO (JSFunction ExportedMainFunction)
+
+foreign export javascript "myMain"
+ myMain ::
+ JSString ->
+ IO
+ (JSFunction ExportedMainFunction)
=====================================
testsuite/tests/ghc-api-browser/playground001.js
=====================================
@@ -0,0 +1,91 @@
+#!/usr/bin/env -S node
+
+const puppeteer = require("puppeteer-core");
+const fs = require("node:fs");
+const path = require("node:path");
+
+class Playground {
+ static #token = Symbol("Playground");
+ #browser;
+ #page;
+
+ static async create({ launchOpts, artifactDir }) {
+ const playground = new Playground(Playground.#token);
+ playground.#browser = await puppeteer.launch(launchOpts);
+
+ playground.#page = await playground.#browser.newPage();
+ await playground.#page.setRequestInterception(true);
+ playground.#page.on("request", async (req) => {
+ if (!req.url().startsWith("http://localhost")) {
+ return req.continue();
+ }
+
+ try {
+ const f = req.url().replace("http://localhost", artifactDir);
+ return req.respond({
+ status: 200,
+ contentType:
+ {
+ ".html": "text/html",
+ ".mjs": "application/javascript",
+ }[path.extname(f)] || "application/octet-stream",
+ body: await fs.promises.readFile(f),
+ });
+ } catch {
+ return req.abort();
+ }
+ });
+
+ await playground.#page.goto("http://localhost/index.html");
+ await playground.#page.locator("#runBtn:enabled").wait();
+ return playground;
+ }
+
+ async close() {
+ await this.#browser.close();
+ }
+
+ async runMain({ mainSrc, ghcArgs }) {
+ await Promise.all([
+ this.#page.evaluate((mainSrc) => editor.setValue(mainSrc), mainSrc),
+ this.#page.locator("#ghcArgs").fill(ghcArgs),
+ ]);
+ await this.#page.locator("#runBtn:enabled").click();
+ await this.#page.locator("#runBtn:enabled").wait();
+
+ const [stdout, stderr] = await Promise.all(
+ ["#stdout", "#stderr"].map((el) =>
+ this.#page
+ .locator(el)
+ .map((t) => t.value)
+ .wait()
+ )
+ );
+
+ return { stdout, stderr };
+ }
+
+ constructor(token) {
+ if (token !== Playground.#token) {
+ throw new Error("new Playground() is forbidden, use Playground.create()");
+ }
+ }
+}
+
+(async () => {
+ const playground = await Playground.create({
+ launchOpts: JSON.parse(process.argv[2]),
+ artifactDir: process.cwd(),
+ });
+
+ try {
+ const { stdout, stderr } = await playground.runMain({
+ mainSrc: await fs.promises.readFile("./hello.hs", { encoding: "utf-8" }),
+ ghcArgs: "-package ghc -v0",
+ });
+ process.stdout.write(stdout);
+ process.stderr.write(stderr);
+ } finally {
+ await playground.close();
+ }
+})();
=====================================
testsuite/tests/ghc-api-browser/playground001.sh
=====================================
@@ -0,0 +1,76 @@
+#!/usr/bin/env bash
+
+set -euo pipefail
+
+# also set this when building wasm32-wasi-ghc for production
+# deployment of haskell playground, so all the .so files are
+# optimized.
+export WASM_SO_OPT="--debuginfo --low-memory-unused --strip-dwarf -Oz"
+
+# we'll build a rootfs tarball that contains everything in tmp and
+# extracts to /tmp, mapped from here
+mkdir ./tmp
+
+$TEST_HC \
+ -v0 \
+ -package ghc \
+ -shared -dynamic \
+ -no-keep-hi-files -no-keep-o-files \
+ -O2 \
+ playground001.hs -o ./tmp/libplayground001.so
+rm -f ./*_stub.h ./playground001.hs
+
+# /tmp/clib contains libc/libc++ .so files
+cp -r "$(dirname "$TEST_CC")/../share/wasi-sysroot/lib/wasm32-wasi" ./tmp/clib
+# trim unneeded stuff in c libdir
+find ./tmp/clib -type f ! -name "*.so" -delete
+rm -f \
+ ./tmp/clib/libsetjmp.so \
+ ./tmp/clib/libwasi-emulated-*.so
+
+# /tmp/hslib/lib is the ghc libdir
+mkdir ./tmp/hslib
+cp -r "$($TEST_HC --print-libdir)" ./tmp/hslib/lib
+# unregister Cabal/Cabal-syntax, too big
+$GHC_PKG --no-user-package-db --global-package-db=./tmp/hslib/lib/package.conf.d unregister Cabal Cabal-syntax
+$GHC_PKG --no-user-package-db --global-package-db=./tmp/hslib/lib/package.conf.d recache
+# we only need non-profiling .dyn_hi/.so, trim as much as we can
+find ./tmp/hslib/lib "(" \
+ -name "*.hi" \
+ -o -name "*.a" \
+ -o -name "*.p_hi" \
+ -o -name "libHS*_p.a" \
+ -o -name "*.p_dyn_hi" \
+ -o -name "libHS*_p*.so" \
+ -o -name "libHSrts*_debug*.so" \
+ ")" -delete
+rm -rf \
+ ./tmp/hslib/lib/doc \
+ ./tmp/hslib/lib/html \
+ ./tmp/hslib/lib/latex \
+ ./tmp/hslib/lib/*.mjs \
+ ./tmp/hslib/lib/*.js \
+ ./tmp/hslib/lib/*.txt
+# HS_SEARCHDIR is something like
+# /tmp/hslib/lib/wasm32-wasi-ghc-9.15.20251024 which is the
+# dynamic-library-dirs that contains all libHS*.so in one place, and
+# also static libraries in per-unit directories
+HS_SEARCHDIR=$(find ./tmp/hslib/lib -type f -name "*.so" -print0 | xargs -0 -n1 dirname | sort -u | sed "s|^\./|/|")
+# hunt down the remaining bits of Cabal/Cabal-syntax. too bad there's
+# no ghc-pkg uninstall.
+rm -rf ."$HS_SEARCHDIR"/*Cabal*
+
+# fix the hard coded search dir in index.html
+SED_IS_GNU=$(sed --version &> /dev/null && echo 1 || echo 0)
+if [[ $SED_IS_GNU == "1" ]]; then
+ sed -i "s|/tmp/hslib/lib/wasm32-wasi-ghc-9.15.20251024|$HS_SEARCHDIR|" ./index.html
+else
+ sed -i "" "s|/tmp/hslib/lib/wasm32-wasi-ghc-9.15.20251024|$HS_SEARCHDIR|" ./index.html
+fi
+
+# also set ZSTD_NBTHREADS/ZSTD_CLEVEL when building for production
+tar -cf ./rootfs.tar.zst --zstd tmp
+rm -rf ./tmp
+
+# pass puppeteer.launch() opts as json
+exec ./playground001.js "$1"
=====================================
testsuite/tests/ghci-wasm/T26431.stdout → testsuite/tests/ghc-api-browser/playground001.stdout
=====================================
=====================================
testsuite/tests/ghci-wasm/T26431.hs deleted
=====================================
@@ -1,35 +0,0 @@
-import Control.Exception
-import Control.Monad.IO.Class
-import Data.Maybe
-import GHC
-import GHC.Plugins
-import GHC.Runtime.Interpreter
-import System.Environment.Blank
-
-main :: IO ()
-main = do
- [libdir] <- getArgs
- defaultErrorHandler defaultFatalMessager defaultFlushOut $
- runGhc (Just libdir) $
- do
- dflags0 <- getSessionDynFlags
- let dflags1 =
- dflags0
- { ghcMode = CompManager,
- backend = bytecodeBackend,
- ghcLink = LinkInMemory
- }
- logger <- getLogger
- (dflags2, _, _) <-
- parseDynamicFlags logger dflags1 $
- map noLoc ["-package", "ghc"]
- _ <- setSessionDynFlags dflags2
- addTarget =<< guessTarget "hello.hs" Nothing Nothing
- _ <- load LoadAllTargets
- setContext
- [ IIDecl $ simpleImportDecl $ mkModuleName "Prelude",
- IIDecl $ simpleImportDecl $ mkModuleName "Main"
- ]
- hsc_env <- getSession
- fhv <- compileExprRemote "main"
- liftIO $ evalIO (fromJust $ hsc_interp hsc_env) fhv
=====================================
testsuite/tests/ghci-wasm/all.T
=====================================
@@ -10,11 +10,3 @@ test('T26430', [
extra_hc_opts('-L. -lT26430B')]
, compile_and_run, ['']
)
-
-test('T26431', [
- extra_files(['../../../.gitlab/hello.hs']),
- extra_hc_opts('-package ghc'),
- extra_run_opts(f'"{config.libdir}"'),
- ignore_stderr]
-, compile_and_run, ['']
-)
=====================================
testsuite/tests/warnings/should_compile/DodgyExports02.hs
=====================================
@@ -0,0 +1,7 @@
+module DodgyExports02
+ ( Identity(..) -- type constructor has out-of-scope children
+ , Void(..) -- type constructor has no children
+ ) where
+
+import Data.Void (Void)
+import Data.Functor.Identity (Identity)
=====================================
testsuite/tests/warnings/should_compile/DodgyExports02.stderr
=====================================
@@ -0,0 +1,10 @@
+DodgyExports02.hs:2:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
+ The export item ‘Identity(..)’ suggests that
+ ‘Identity’ has (in-scope) constructors or record fields,
+ but it has none
+
+DodgyExports02.hs:3:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
+ The export item ‘Void(..)’ suggests that
+ ‘Void’ has (in-scope) constructors or record fields,
+ but it has none
+
=====================================
testsuite/tests/warnings/should_compile/DodgyExports03.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE ExplicitNamespaces #-}
+
+module DodgyExports03
+ ( data MkR(..) -- data constructors never have children ('fld' belongs to 'R')
+ ) where
+
+data R = MkR { fld :: Int }
=====================================
testsuite/tests/warnings/should_compile/DodgyExports03.stderr
=====================================
@@ -0,0 +1,4 @@
+DodgyExports03.hs:4:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
+ The export item ‘MkR(..)’ suggests that
+ ‘MkR’ has children, but it is not a type constructor or a class
+
=====================================
testsuite/tests/warnings/should_compile/DuplicateModExport.hs
=====================================
@@ -0,0 +1,3 @@
+module DuplicateModExport (module L, module L) where
+
+import Data.List as L
=====================================
testsuite/tests/warnings/should_compile/DuplicateModExport.stderr
=====================================
@@ -0,0 +1,3 @@
+DuplicateModExport.hs:1:38: warning: [GHC-51876] [-Wduplicate-exports (in -Wdefault)]
+ Duplicate ‘module L’ in export list
+
=====================================
testsuite/tests/warnings/should_compile/EmptyModExport.hs
=====================================
@@ -0,0 +1,3 @@
+module EmptyModExport (module L) where
+
+import Data.List as L ()
=====================================
testsuite/tests/warnings/should_compile/EmptyModExport.stderr
=====================================
@@ -0,0 +1,3 @@
+EmptyModExport.hs:1:24: warning: [GHC-64649] [-Wdodgy-exports (in -Wextra)]
+ The export item ‘module L’ exports nothing
+
=====================================
testsuite/tests/warnings/should_compile/all.T
=====================================
@@ -54,6 +54,8 @@ test('T19564d', normal, compile, [''])
# Also, suppress uniques as one of the warnings is unstable in CI, otherwise.
test('T19296', normal, compile, ['-fdiagnostics-show-caret -Wredundant-constraints -dsuppress-uniques'])
test('DodgyExports01', normal, compile, ['-Wdodgy-exports'])
+test('DodgyExports02', normal, compile, ['-Wdodgy-exports'])
+test('DodgyExports03', normal, compile, ['-Wdodgy-exports'])
test('DerivingTypeable', normal, compile, ['-Wderiving-typeable'])
test('T18862a', normal, compile, [''])
test('T18862b', normal, compile, [''])
@@ -72,3 +74,5 @@ test('T23465', normal, compile, ['-ddump-parsed'])
test('WarnNoncanonical', normal, compile, [''])
test('T24396', [extra_files(["T24396a.hs", "T24396b.hs"])], multimod_compile, ['T24396b', ''])
test('SpecMultipleTys', normal, compile, ['']) # compile_fail from GHC 9.18
+test('DuplicateModExport', normal, compile, ['-Wduplicate-exports'])
+test('EmptyModExport', normal, compile, ['-Wdodgy-exports'])
=====================================
utils/ghc-toolchain/ghc-toolchain.cabal
=====================================
@@ -21,6 +21,7 @@ library
GHC.Toolchain.NormaliseTriple,
GHC.Toolchain.CheckArm,
GHC.Toolchain.Target,
+ GHC.Toolchain.CheckPower
GHC.Toolchain.Tools.Ar,
GHC.Toolchain.Tools.Cc,
GHC.Toolchain.Tools.Cxx,
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/CheckArm.hs
=====================================
@@ -8,6 +8,7 @@ import System.Process
import GHC.Platform.ArchOS
import GHC.Toolchain.Prelude
+import GHC.Toolchain.Utils (lastLine)
import GHC.Toolchain.Tools.Cc
-- | Awkwardly, ARM triples sometimes contain insufficient information about
@@ -75,10 +76,6 @@ findArmIsa cc = do
"False" -> return False
_ -> throwE $ "unexpected output from test program: " ++ out
-lastLine :: String -> String
-lastLine "" = ""
-lastLine s = last $ lines s
-
-- | Raspbian unfortunately makes some extremely questionable packaging
-- decisions, configuring gcc to compile for ARMv6 despite the fact that the
-- Raspberry Pi 4 is ARMv8. As ARMv8 doesn't support all instructions supported
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/CheckPower.hs
=====================================
@@ -0,0 +1,29 @@
+module GHC.Toolchain.CheckPower ( checkPowerAbi ) where
+
+import GHC.Platform.ArchOS
+
+import GHC.Toolchain.Prelude
+import GHC.Toolchain.Utils (lastLine)
+import GHC.Toolchain.Tools.Cc
+
+-- 64-Bit ELF V2 ABI Specification, Power Architecture, Revision 1.5 says:
+-- A C preprocessor that conforms to this ABI shall predefine the macro
+-- _CALL_ELF to have a value of 2 (Section 5.1.4 Predifined Macros).
+-- The 64-bit PowerPC ELF Application Binary Interface Supplement 1.9
+-- does not define any macro to identify the ABI.
+-- So we check for ABI version 2 and default to ABI version 1.
+
+checkPowerAbi :: Cc -> M Arch
+checkPowerAbi cc = do
+ checking "POWER ELF ABI" $ do
+ out <- fmap lastLine $ preprocess cc $ unlines
+ [ "#if defined(_CALL_ELF) && _CALL_ELF == 2"
+ , "ELFv2"
+ , "#else"
+ , "ELFv1"
+ , "#endif"
+ ]
+ case out of
+ "ELFv1" -> pure $ ArchPPC_64 ELF_V1
+ "ELFv2" -> pure $ ArchPPC_64 ELF_V2
+ _ -> throwE $ "unexpected output from test program: " ++ out
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs
=====================================
@@ -6,6 +6,7 @@ import GHC.Platform.ArchOS
import GHC.Toolchain.Prelude
import GHC.Toolchain.CheckArm
+import GHC.Toolchain.CheckPower
import GHC.Toolchain.Tools.Cc
-- | Parse a triple `arch-vendor-os` into an 'ArchOS' and a vendor name 'String'
@@ -40,7 +41,7 @@ parseArch cc arch =
"x86_64" -> pure ArchX86_64
"amd64" -> pure ArchX86_64
"powerpc" -> pure ArchPPC
- "powerpc64" -> pure (ArchPPC_64 ELF_V1)
+ "powerpc64" -> checkPowerAbi cc
"powerpc64le" -> pure (ArchPPC_64 ELF_V2)
"s390x" -> pure ArchS390X
"arm" -> findArmIsa cc
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Utils.hs
=====================================
@@ -8,6 +8,7 @@ module GHC.Toolchain.Utils
, oneOf
, oneOf'
, isSuccess
+ , lastLine
) where
import Control.Exception
@@ -65,3 +66,6 @@ isSuccess = \case
ExitSuccess -> True
ExitFailure _ -> False
+lastLine :: String -> String
+lastLine "" = ""
+lastLine s = last $ lines s
=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -285,7 +285,7 @@ function originFromServerAddress({ address, family, port }) {
}
// Browser/node portable code stays above this watermark.
-const isNode = Boolean(globalThis?.process?.versions?.node);
+const isNode = Boolean(globalThis?.process?.versions?.node && !globalThis.Deno);
// Too cumbersome to only import at use sites. Too troublesome to
// factor out browser-only/node-only logic into different modules. For
@@ -307,27 +307,27 @@ if (isNode) {
ws = require("ws");
} catch {}
} else {
- wasi = await import(
- "https://cdn.jsdelivr.net/npm/@bjorn3/browser_wasi_shim@0.4.2/dist/index.js"
- );
+ wasi = await import("https://esm.sh/gh/haskell-wasm/browser_wasi_shim");
}
// A subset of dyld logic that can only be run in the host node
// process and has full access to local filesystem
-class DyLDHost {
+export class DyLDHost {
// Deduped absolute paths of directories where we lookup .so files
#rpaths = new Set();
- constructor() {
- // Inherited pipe file descriptors from GHC
- const out_fd = Number.parseInt(process.argv[4]),
- in_fd = Number.parseInt(process.argv[5]);
-
+ constructor({ outFd, inFd }) {
+ // When running a non-iserv shared library with node, the DyLDHost
+ // instance is created without a pair of fds, so skip creation of
+ // readStream/writeStream, they won't be used anyway
+ if (!(typeof outFd === "number" && typeof inFd === "number")) {
+ return;
+ }
this.readStream = stream.Readable.toWeb(
- fs.createReadStream(undefined, { fd: in_fd })
+ fs.createReadStream(undefined, { fd: inFd })
);
this.writeStream = stream.Writable.toWeb(
- fs.createWriteStream(undefined, { fd: out_fd })
+ fs.createWriteStream(undefined, { fd: outFd })
);
}
@@ -377,6 +377,72 @@ class DyLDHost {
}
}
+// Runs in the browser and uses the in-memory vfs, doesn't do any RPC
+// calls
+export class DyLDBrowserHost {
+ // Deduped absolute paths of directories where we lookup .so files
+ #rpaths = new Set();
+ // The PreopenDirectory object of the root filesystem
+ rootfs;
+ // Continuations to output a single line to stdout/stderr
+ stdout;
+ stderr;
+
+ // Given canonicalized absolute file path, returns the File object,
+ // or null if absent
+ #readFile(p) {
+ const { ret, entry } = this.rootfs.dir.get_entry_for_path({
+ parts: p.split("/").filter((tok) => tok !== ""),
+ is_dir: false,
+ });
+ return ret === 0 ? entry : null;
+ }
+
+ constructor({ rootfs, stdout, stderr }) {
+ this.rootfs = rootfs
+ ? rootfs
+ : new wasi.PreopenDirectory("/", [["tmp", new wasi.Directory([])]]);
+ this.stdout = stdout ? stdout : (msg) => console.info(msg);
+ this.stderr = stderr ? stderr : (msg) => console.warn(msg);
+ }
+
+ // p must be canonicalized absolute path
+ async addLibrarySearchPath(p) {
+ this.#rpaths.add(p);
+ return null;
+ }
+
+ async findSystemLibrary(f) {
+ if (f.startsWith("/")) {
+ if (this.#readFile(f)) {
+ return f;
+ }
+ throw new Error(`findSystemLibrary(${f}): not found in /`);
+ }
+
+ for (const rpath of this.#rpaths) {
+ const r = `${rpath}/${f}`;
+ if (this.#readFile(r)) {
+ return r;
+ }
+ }
+
+ throw new Error(
+ `findSystemLibrary(${f}): not found in ${[...this.#rpaths]}`
+ );
+ }
+
+ async fetchWasm(p) {
+ const entry = this.#readFile(p);
+ const r = new Response(entry.data, {
+ headers: { "Content-Type": "application/wasm" },
+ });
+ // It's only fetched once, take the chance to prune it in vfs to save memory
+ entry.data = new Uint8Array();
+ return r;
+ }
+}
+
// Fulfill the same functionality as DyLDHost by doing fetch() calls
// to respective RPC endpoints of a host http server. Also manages
// WebSocket connections back to host.
@@ -494,7 +560,7 @@ export class DyLDRPC {
// Actual implementation of endpoints used by DyLDRPC
class DyLDRPCServer {
- #dyldHost = new DyLDHost();
+ #dyldHost;
#server;
#wss;
@@ -502,11 +568,15 @@ class DyLDRPCServer {
host,
port,
dyldPath,
- libdir,
- ghciSoPath,
+ searchDirs,
+ mainSoPath,
+ outFd,
+ inFd,
args,
redirectWasiConsole,
}) {
+ this.#dyldHost = new DyLDHost({ outFd, inFd });
+
this.#server = http.createServer(async (req, res) => {
const origin = originFromServerAddress(await this.listening);
@@ -540,7 +610,7 @@ class DyLDRPCServer {
res.end(
`
import { DyLDRPC, main } from "./fs${dyldPath}";
-const args = ${JSON.stringify({ libdir, ghciSoPath, args })};
+const args = ${JSON.stringify({ searchDirs, mainSoPath, args, isIserv: true })};
args.rpc = new DyLDRPC({origin: "${origin}", redirectWasiConsole: ${redirectWasiConsole}});
args.rpc.opened.then(() => main(args));
`
@@ -829,11 +899,37 @@ class DyLD {
),
wasi.ConsoleStdout.lineBuffered((msg) => this.#rpc.stdout(msg)),
wasi.ConsoleStdout.lineBuffered((msg) => this.#rpc.stderr(msg)),
+ // for ghci browser mode, default to an empty rootfs with
+ // /tmp
+ this.#rpc instanceof DyLDBrowserHost
+ ? this.#rpc.rootfs
+ : new wasi.PreopenDirectory("/", [["tmp", new wasi.Directory([])]]),
],
{ debug: false }
);
}
+ // Both wasi implementations we use provide
+ // wasi.initialize(instance) to initialize a wasip1 reactor
+ // module. However, instance does not really need to be a
+ // WebAssembly.Instance object; the wasi implementations only need
+ // to access instance.exports.memory for the wasi syscalls to
+ // work.
+ //
+ // Given we'll reuse the same wasi object across different
+ // WebAssembly.Instance objects anyway and
+ // wasi.initialize(instance) can't be called more than once, we
+ // use this simple trick and pass a fake instance object that
+ // contains just enough info for the wasi implementation to
+ // initialize its internal state. Later when we load each wasm
+ // shared library, we can just manually invoke their
+ // initialization functions.
+ this.#wasi.initialize({
+ exports: {
+ memory: this.#memory,
+ },
+ });
+
// Keep this in sync with rts/wasm/Wasm.S!
for (let i = 1; i <= 10; ++i) {
this.#regs[`__R${i}`] = new WebAssembly.Global({
@@ -930,10 +1026,15 @@ class DyLD {
async loadDLLs(packed) {
// Normalize input to an array of strings. When called from Haskell
// we pass a single JSString containing NUL-separated paths.
- const paths = (typeof packed === "string"
- ? (packed.length === 0 ? [] : packed.split("\0"))
- : [packed] // tolerate an accidental single path object
- ).filter((s) => s.length > 0).reverse();
+ const paths = (
+ typeof packed === "string"
+ ? packed.length === 0
+ ? []
+ : packed.split("\0")
+ : [packed]
+ ) // tolerate an accidental single path object
+ .filter((s) => s.length > 0)
+ .reverse();
// Compute a single downsweep plan for the whole batch.
// Note: #downsweep mutates #loadedSos to break cycles and dedup.
@@ -1154,22 +1255,6 @@ class DyLD {
throw new Error(`cannot handle export ${k} ${v}`);
}
- // We call wasi.initialize when loading libc.so, then reuse the
- // wasi instance globally. When loading later .so files, just
- // manually invoke _initialize().
- if (soname === "libc.so") {
- instance.exports.__wasm_apply_data_relocs();
- // wasm-ld forbits --export-memory with --shared, I don't know
- // why but this is sufficient to make things work
- this.#wasi.initialize({
- exports: {
- memory: this.#memory,
- _initialize: instance.exports._initialize,
- },
- });
- continue;
- }
-
// See
// https://gitlab.haskell.org/haskell-wasm/llvm-project/-/blob/release/21.x/ll…,
// __wasm_apply_data_relocs is now optional so only call it if
@@ -1180,7 +1265,7 @@ class DyLD {
// been called upon instantiation, see
// Writer::createStartFunction().
if (instance.exports.__wasm_apply_data_relocs) {
- instance.exports.__wasm_apply_data_relocs();
+ instance.exports.__wasm_apply_data_relocs();
}
instance.exports._initialize();
@@ -1208,15 +1293,38 @@ class DyLD {
}
}
-export async function main({ rpc, libdir, ghciSoPath, args }) {
+// The main entry point of dyld that may be run on node/browser, and
+// may run either iserv defaultMain from the ghci library or an
+// alternative entry point from another shared library
+export async function main({
+ rpc, // Handle the side effects of DyLD
+ searchDirs, // Initial library search directories
+ mainSoPath, // Could also be another shared library that's actually not ghci
+ args, // WASI argv starting with the executable name. +RTS etc will be respected
+ isIserv, // set to true when running iserv defaultServer
+}) {
try {
const dyld = new DyLD({
- args: ["dyld.so", ...args],
+ args,
rpc,
});
- await dyld.addLibrarySearchPath(libdir);
- await dyld.loadDLLs(ghciSoPath);
+ for (const libdir of searchDirs) {
+ await dyld.addLibrarySearchPath(libdir);
+ }
+ await dyld.loadDLLs(mainSoPath);
+
+ // At this point, rts/ghc-internal are loaded, perform wasm shared
+ // library specific RTS startup logic, see Note [JSFFI initialization]
+ dyld.exportFuncs.__ghc_wasm_jsffi_init();
+
+ // We're not running iserv, just return the dyld instance so user
+ // could use it to invoke their exported functions, and don't
+ // perform cleanup (see finally block)
+ if (!isIserv) {
+ return dyld;
+ }
+ // iserv-specific logic follows
const reader = rpc.readStream.getReader();
const writer = rpc.writeStream.getWriter();
@@ -1235,31 +1343,25 @@ export async function main({ rpc, libdir, ghciSoPath, args }) {
writer.write(new Uint8Array(buf));
};
- dyld.exportFuncs.__ghc_wasm_jsffi_init();
- await dyld.exportFuncs.defaultServer(cb_sig, cb_recv, cb_send);
+ return await dyld.exportFuncs.defaultServer(cb_sig, cb_recv, cb_send);
} finally {
- rpc.close();
+ if (isIserv) {
+ rpc.close();
+ }
}
}
-(async () => {
- if (!isNode) {
- return;
- }
-
- const libdir = process.argv[2];
- const ghciSoPath = process.argv[3];
- const args = process.argv.slice(6);
-
+// node-specific iserv-specific logic
+async function nodeMain({ searchDirs, mainSoPath, outFd, inFd, args }) {
if (!process.env.GHCI_BROWSER) {
- const rpc = new DyLDHost();
- await main({
+ const rpc = new DyLDHost({ outFd, inFd });
+ return await main({
rpc,
- libdir,
- ghciSoPath,
+ searchDirs,
+ mainSoPath,
args,
+ isIserv: true,
});
- return;
}
if (!ws) {
@@ -1272,8 +1374,10 @@ export async function main({ rpc, libdir, ghciSoPath, args }) {
host: process.env.GHCI_BROWSER_HOST || "127.0.0.1",
port: process.env.GHCI_BROWSER_PORT || 0,
dyldPath: import.meta.filename,
- libdir,
- ghciSoPath,
+ searchDirs,
+ mainSoPath,
+ outFd,
+ inFd,
args,
redirectWasiConsole:
process.env.GHCI_BROWSER_PUPPETEER_LAUNCH_OPTS ||
@@ -1362,6 +1466,20 @@ export async function main({ rpc, libdir, ghciSoPath, args }) {
}
console.log(
- `Open ${origin}/main.html or import ${origin}/main.js to boot ghci`
+ `Open ${origin}/main.html or import("${origin}/main.js") to boot ghci`
);
-})();
+}
+
+const isNodeMain = isNode && import.meta.filename === process.argv[1];
+
+// node iserv as invoked by
+// GHC.Runtime.Interpreter.Wasm.spawnWasmInterp
+if (isNodeMain) {
+ const clibdir = process.argv[2];
+ const mainSoPath = process.argv[3];
+ const outFd = Number.parseInt(process.argv[4]),
+ inFd = Number.parseInt(process.argv[5]);
+ const args = ["dyld.so", ...process.argv.slice(6)];
+
+ await nodeMain({ searchDirs: [clibdir], mainSoPath, outFd, inFd, args });
+}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/da43e8776c3537fb8f6d45d2d58e61…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/da43e8776c3537fb8f6d45d2d58e61…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/int-index/imp-exp-whole-namespace] 9 commits: rts: remove unneccesary cabal flags
by Vladislav Zavialov (@int-index) 01 Nov '25
by Vladislav Zavialov (@int-index) 01 Nov '25
01 Nov '25
Vladislav Zavialov pushed to branch wip/int-index/imp-exp-whole-namespace at Glasgow Haskell Compiler / GHC
Commits:
643ce801 by Julian Ospald at 2025-10-28T18:18:55-04:00
rts: remove unneccesary cabal flags
We perform those checks via proper autoconf macros
instead that do the right thing and then add those
libs to the rts buildinfo.
- - - - -
d69ea8fe by Vladislav Zavialov at 2025-10-28T18:19:37-04:00
Test case for #17705
Starting with GHC 9.12 (the first release to include 5745dbd3),
all examples in this ticket are handled as expected.
- - - - -
4038a28b by Andreas Klebinger at 2025-10-30T12:38:52-04:00
Add a perf test for #26425
- - - - -
f997618e by Andreas Klebinger at 2025-10-30T12:38:52-04:00
OccAnal: Be stricter for better compiler perf.
In particular we are now stricter:
* When combining usageDetails.
* When computing binder info.
In combineUsageDetails when combining the underlying adds we compute a
new `LocalOcc` for each entry by combining the two existing ones.
Rather than wait for those entries to be forced down the road we now
force them immediately. Speeding up T26425 by about 10% with little
effect on the common case.
We also force binders we put into the Core AST everywhere now.
Failure to do so risks leaking the occ env used to set the binders
OccInfo.
For T26425 compiler residency went down by a factor of ~10x.
Compile time also improved by a factor of ~1.6.
-------------------------
Metric Decrease:
T18698a
T26425
T9233
-------------------------
- - - - -
5618645b by Vladislav Zavialov at 2025-10-30T12:39:33-04:00
Fix namespace specifiers in subordinate exports (#12488)
This patch fixes an oversight in the `lookupChildrenExport` function that
caused explicit namespace specifiers of subordinate export items to be
ignored:
module M (T (type A)) where -- should be rejected
data T = A
Based on the `IEWrappedName` data type, there are 5 cases to consider:
1. Unadorned name: P(X)
2. Named default: P(default X)
3. Pattern synonym: P(pattern X)
4. Type name: P(type X)
5. Data name: P(data X)
Case 1 is already handled correctly; cases 2 and 3 are parse errors; and
it is cases 4 and 5 that we are concerned with in this patch.
Following the precedent established in `LookupExactName`, we introduce
a boolean flag in `LookupChildren` to control whether to look up in all
namespaces or in a specific one. If an export item is accompanied by an
explicit namespace specifier `type` or `data`, we restrict the lookup in
`lookupGRE` to a specific namespace.
The newly introduced diagnostic `TcRnExportedSubordinateNotFound`
provides error messages and suggestions more tailored to this context
than the previously used `reportUnboundName`.
- - - - -
f75ab223 by Peter Trommler at 2025-10-31T18:43:13-04:00
ghc-toolchain: detect PowerPC 64 bit ABI
Check preprocessor macro defined for ABI v2 and assume v1 otherwise.
Fixes #26521
- - - - -
d086c474 by Peter Trommler at 2025-10-31T18:43:13-04:00
ghc-toolchain: refactor, move lastLine to Utils
- - - - -
995dfe0d by Vladislav Zavialov at 2025-10-31T18:43:54-04:00
Tests for -Wduplicate-exports, -Wdodgy-exports
Add test cases for the previously untested diagnostics:
[GHC-51876] TcRnDupeModuleExport
[GHC-64649] TcRnNullExportedModule
This also revealed a typo (incorrect capitalization of "module") in the
warning text for TcRnDupeModuleExport, which is now fixed.
- - - - -
862e9949 by Vladislav Zavialov at 2025-11-01T02:53:11+03:00
Namespace-specified wildcards in import/export lists
This change adds support for top-level namespace-specified wildcards
`type ..` and `data ..` to import and export lists.
Examples:
import M (type ..) -- imports all type and class constructors from M
import M (data ..) -- imports all data constructors and terms from M
module M (type .., f) where
-- exports all type and class constructors defined in M,
-- plus the function 'f'
The primary intended usage of this feature is in combination with module
aliases, allowing namespace disambiguation:
import Data.Proxy as T (type ..) -- T.Proxy is unambiguously the type constructor
import Data.Proxy as D (data ..) -- D.Proxy is unambiguously the data constructor
The patch accounts for the interactions of wildcards with:
* Imports with `hiding` clauses
* Import warnings -Wunused-imports, -Wdodgy-imports
* Export warnings -Wduplicate-exports, -Wdodgy-exports
Summary of the changes:
1. Move the NamespaceSpecifier type from GHC.Hs.Binds to GHC.Hs.Basic,
making it possible to use it in more places in the AST.
2. Extend the AST (type: IE) with a representation of `..`, `type ..`,
and `data ..` (constructor: IEWholeNamespace). Per the proposal, the
plain `..` is always rejected with a dedicated error message.
3. Extend the grammar in Parser.y with productions for `..`, `type ..`,
and `data ..` in both import and export lists.
4. Implement wildcard imports by updating the `filterImports` function
in GHC.Rename.Names; the logic for IEWholeNamespace is roughly
modeled after the Nothing (no explicit import list) case.
5. Implement wildcard exports by updating the `exports_from_avail`
function in GHC.Tc.Gen.Export; the logic for IEWholeNamespace is
closely modeled after the IEModuleContents case.
6. Refactor and extend diagnostics to report the new warnings and
errors. See PsErrPlainWildcardImport, DodgyImportsWildcard,
PsErrPlainWildcardExport, DodgyExportsWildcard,
TcRnDupeWildcardExport.
Note that this patch is specifically about top-level import/export
items. Subordinate import/export items are left unchanged.
- - - - -
111 changed files:
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Hs/Basic.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Var/Env.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/exts/explicit_namespaces.rst
- m4/fp_check_pthreads.m4
- rts/configure.ac
- + rts/rts.buildinfo.in
- rts/rts.cabal
- testsuite/tests/diagnostic-codes/codes.stdout
- + testsuite/tests/module/T25901_exp_plain_wc.hs
- + testsuite/tests/module/T25901_exp_plain_wc.stderr
- + testsuite/tests/module/T25901_imp_plain_wc.hs
- + testsuite/tests/module/T25901_imp_plain_wc.stderr
- testsuite/tests/module/all.T
- testsuite/tests/module/mod4.stderr
- + testsuite/tests/parser/should_fail/T12488c.hs
- + testsuite/tests/parser/should_fail/T12488c.stderr
- + testsuite/tests/parser/should_fail/T12488d.hs
- + testsuite/tests/parser/should_fail/T12488d.stderr
- testsuite/tests/parser/should_fail/all.T
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
- + testsuite/tests/rename/should_compile/T12488b.hs
- + testsuite/tests/rename/should_compile/T12488f.hs
- + testsuite/tests/rename/should_compile/T25901_exp_1.hs
- + testsuite/tests/rename/should_compile/T25901_exp_1_helper.hs
- + testsuite/tests/rename/should_compile/T25901_exp_2.hs
- + testsuite/tests/rename/should_compile/T25901_exp_2_helper.hs
- + testsuite/tests/rename/should_compile/T25901_imp_hq.hs
- + testsuite/tests/rename/should_compile/T25901_imp_hu.hs
- + testsuite/tests/rename/should_compile/T25901_imp_sq.hs
- + testsuite/tests/rename/should_compile/T25901_imp_su.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/rename/should_fail/T12488a.hs
- + testsuite/tests/rename/should_fail/T12488a.stderr
- + testsuite/tests/rename/should_fail/T12488a_foo.hs
- + testsuite/tests/rename/should_fail/T12488a_foo.stderr
- + testsuite/tests/rename/should_fail/T12488e.hs
- + testsuite/tests/rename/should_fail/T12488e.stderr
- + testsuite/tests/rename/should_fail/T12488g.hs
- + testsuite/tests/rename/should_fail/T12488g.stderr
- testsuite/tests/rename/should_fail/T25899e2.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1_helper.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2_helper.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_5.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_5.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_6.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_6.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_hu_fail_4.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hu_fail_4.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_2.hs
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_2.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_3.hs
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_3.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_su_fail_1.hs
- + testsuite/tests/rename/should_fail/T25901_imp_su_fail_1.stderr
- testsuite/tests/rename/should_fail/all.T
- + testsuite/tests/typecheck/should_compile/T17705.hs
- testsuite/tests/typecheck/should_compile/all.T
- + testsuite/tests/warnings/should_compile/DuplicateModExport.hs
- + testsuite/tests/warnings/should_compile/DuplicateModExport.stderr
- + testsuite/tests/warnings/should_compile/EmptyModExport.hs
- + testsuite/tests/warnings/should_compile/EmptyModExport.stderr
- + testsuite/tests/warnings/should_compile/T25901_dodgy_helper_1.hs
- + testsuite/tests/warnings/should_compile/T25901_dodgy_helper_2.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dodgy.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dodgy.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_1.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_2.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_2.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_1.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_2.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_2.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_1.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_2.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_2.stderr
- testsuite/tests/warnings/should_compile/all.T
- utils/check-exact/ExactPrint.hs
- utils/ghc-toolchain/ghc-toolchain.cabal
- utils/ghc-toolchain/src/GHC/Toolchain/CheckArm.hs
- + utils/ghc-toolchain/src/GHC/Toolchain/CheckPower.hs
- utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Utils.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6aabe75818dbcd05758e01e7f80626…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6aabe75818dbcd05758e01e7f80626…
You're receiving this email because of your account on gitlab.haskell.org.
1
0