[Git][ghc/ghc][wip/T25577-test] 2 commits: testsuite: Add testcase for #25577

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Fri Feb 21 00:13:24 UTC 2025



Ben Gamari pushed to branch wip/T25577-test at Glasgow Haskell Compiler / GHC


Commits:
3b037e97 by Ben Gamari at 2025-02-20T19:13:10-05:00
testsuite: Add testcase for #25577

- - - - -
cd5fffd0 by Ben Gamari at 2025-02-20T19:13:11-05:00
testsuite/ghc-api: Eliminate Makefile usage from  various GHC API tests

These tests can be expressed perfectly well using the testsuite driver
itself.

- - - - -


3 changed files:

- testsuite/tests/ghc-api/Makefile
- + testsuite/tests/ghc-api/T25577.hs
- testsuite/tests/ghc-api/all.T


Changes:

=====================================
testsuite/tests/ghc-api/Makefile
=====================================
@@ -2,29 +2,3 @@ TOP=../..
 include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
-clean:
-	rm -f *.o *.hi
-
-T6145:
-	rm -f T6145.o T6145.hi
-	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc T6145
-	./T6145 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
-
-T8639_api:
-	rm -f T8639_api.o T8639_api.hi
-	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc T8639_api
-	./T8639_api "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
-
-T8628:
-	rm -f T8628.o T8628.hi
-	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc -package exceptions T8628
-	./T8628 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
-
-T9015:
-	rm -f T9015.o T9015.hi
-	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc T9015
-	./T9015 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
-
-.PHONY: clean T6145 T8639_api T8628 T9015
-
-


=====================================
testsuite/tests/ghc-api/T25577.hs
=====================================
@@ -0,0 +1,42 @@
+module Main where
+
+import GHC
+import GHC.Paths
+import Unsafe.Coerce
+import Control.Monad.IO.Class
+import System.Environment (getArgs)
+
+main :: IO ()
+main = do
+    [libdir] <- getArgs
+    runGhc (Just libdir) run
+
+run :: Ghc ()
+run = do
+    dyn_flags <- getSessionDynFlags
+    _ <- setSessionDynFlags dyn_flags
+
+    setContext [ IIDecl . simpleImportDecl . mkModuleName $ "Prelude"
+               , IIDecl . simpleImportDecl . mkModuleName $ "Unsafe.Coerce" ]
+
+    wrong
+
+wrong :: Ghc ()
+wrong = do
+    let chck = "5.5626902089526504e-303 :: Double"
+    v <- compileExpr chck
+
+    liftIO $ do
+        putStr "Direct: "
+        print (5.5626902089526504e-303 :: Double)
+        putStr "API:    "
+        print (unsafeCoerce v :: Double)
+
+    let chck2 = "5.56269020895265e-303 :: Double"
+    v2 <- compileExpr chck2
+
+    liftIO $ do
+        putStr "Direct: "
+        print (5.56269020895265e-303 :: Double)
+        putStr "API:    "
+        print (unsafeCoerce v2 :: Double)


=====================================
testsuite/tests/ghc-api/all.T
=====================================
@@ -1,12 +1,28 @@
 setTestOpts(when(arch('wasm32'), run_timeout_multiplier(2)))
 
 test('ghcApi', normal, compile_and_run, ['-package ghc'])
-test('T6145', normal, makefile_test, ['T6145'])
-test('T8639_api', req_rts_linker,
-              makefile_test, ['T8639_api'])
-test('T8628', req_rts_linker,
-              makefile_test, ['T8628'])
-test('T9595', [extra_run_opts('"' + config.libdir + '"')],
+
+test('T6145',
+     [extra_run_opts(f'"{config.libdir}"')],
+     compile_and_run,
+     ['-package ghc'])
+
+test('T8639_api',
+     [extra_run_opts(f'"{config.libdir}"'), req_rts_linker],
+     compile_and_run,
+     ['-package ghc'])
+
+test('T8628',
+     [extra_run_opts(f'"{config.libdir}"'), req_rts_linker],
+     compile_and_run,
+     ['-package ghc -package exceptions'])
+
+test('T9015',
+     [extra_run_opts(f'"{config.libdir}"'), req_rts_linker],
+     compile_and_run,
+     ['-package ghc'])
+
+test('T9595', [extra_run_opts(f'"{config.libdir}"')],
               compile_and_run,
               ['-package ghc'])
 test('T10508_api', [ extra_run_opts('"' + config.libdir + '"'),
@@ -17,9 +33,6 @@ test('T10508_api', [ extra_run_opts('"' + config.libdir + '"'),
 test('T10942', [extra_run_opts('"' + config.libdir + '"')],
                    compile_and_run,
                    ['-package ghc'])
-test('T9015', [extra_run_opts('"' + config.libdir + '"')],
-              compile_and_run,
-              ['-package ghc'])
 test('T11579', [extra_run_opts('"' + config.libdir + '"'), js_skip], compile_and_run,
      ['-package ghc'])
 test('T12099', normal, compile_and_run, ['-package ghc'])
@@ -42,3 +55,4 @@ test('T20757', [unless(opsys('mingw32'), skip), exit_code(1), normalise_version(
                compile_and_run,
                ['-package ghc'])
 test('PrimOpEffect_Sanity', normal, compile_and_run, ['-Wall -Werror -package ghc'])
+test('T25577', extra_run_opts(f'"{config.libdir}"'), compile_and_run, ['-package ghc'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b353fcbbbf9c39b0e3eddcd85521bb634f6bf45...cd5fffd050aa4b3c6e64f41d6e45685c03c4fee0

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


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


More information about the ghc-commits mailing list