[Git][ghc/ghc][wip/T24634-oneshot-bytecode] add test

Torsten Schmits (@torsten.schmits) gitlab at gitlab.haskell.org
Tue Jul 30 19:51:53 UTC 2024



Torsten Schmits pushed to branch wip/T24634-oneshot-bytecode at Glasgow Haskell Compiler / GHC


Commits:
b3a28c30 by Torsten Schmits at 2024-07-30T21:51:47+02:00
add test

- - - - -


8 changed files:

- + testsuite/tests/bytecode/T25090/A.hs
- + testsuite/tests/bytecode/T25090/B.hs
- + testsuite/tests/bytecode/T25090/C.hs
- + testsuite/tests/bytecode/T25090/C.hs-boot
- + testsuite/tests/bytecode/T25090/D.hs
- + testsuite/tests/bytecode/T25090/Makefile
- + testsuite/tests/bytecode/T25090/T25090.stdout
- + testsuite/tests/bytecode/T25090/all.T


Changes:

=====================================
testsuite/tests/bytecode/T25090/A.hs
=====================================
@@ -0,0 +1,7 @@
+{-# language TemplateHaskell #-}
+module Main where
+
+import D
+
+main :: IO ()
+main = putStrLn (show ($splc :: Int))


=====================================
testsuite/tests/bytecode/T25090/B.hs
=====================================
@@ -0,0 +1,5 @@
+module B where
+
+import {-# source #-} C (C)
+
+data B = B C


=====================================
testsuite/tests/bytecode/T25090/C.hs
=====================================
@@ -0,0 +1,8 @@
+module C where
+
+import B
+
+data C = C Int
+
+b :: B
+b = B (C 2024)


=====================================
testsuite/tests/bytecode/T25090/C.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module C where
+
+data C


=====================================
testsuite/tests/bytecode/T25090/D.hs
=====================================
@@ -0,0 +1,12 @@
+module D where
+
+import Language.Haskell.TH (ExpQ)
+import Language.Haskell.TH.Syntax (lift)
+import B
+import C
+
+splc :: ExpQ
+splc =
+  lift @_ @Int num
+  where
+    B (C num) = b


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -0,0 +1,12 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T25090:
+	$(TEST_HC) -c -fbyte-code-and-object-code -dynamic C.hs-boot
+	$(TEST_HC) -c -fbyte-code-and-object-code -dynamic B.hs
+	$(TEST_HC) -c -fbyte-code-and-object-code -dynamic C.hs
+	$(TEST_HC) -c -fbyte-code-and-object-code -dynamic D.hs
+	$(TEST_HC) -c -fbyte-code-and-object-code -fprefer-byte-code -dynamic A.hs
+	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code D.o A.o -o exe
+	./exe


=====================================
testsuite/tests/bytecode/T25090/T25090.stdout
=====================================
@@ -0,0 +1 @@
+2024


=====================================
testsuite/tests/bytecode/T25090/all.T
=====================================
@@ -0,0 +1,7 @@
+test('T25090',
+     [extra_files(['A.hs', 'B.hs', 'C.hs-boot', 'C.hs', 'D.hs']),
+      req_th,
+      ignore_stderr,
+      ],
+     makefile_test,
+     [])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3a28c30c4825c86eea7a5e37f2e227959c86d87

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3a28c30c4825c86eea7a5e37f2e227959c86d87
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/20240730/9c474f4a/attachment-0001.html>


More information about the ghc-commits mailing list