[commit: ghc] wip/T15449, wip/T16188, wip/llvm-configure-opts: Fix test for T16180 on Darwin (fix #16128) (d97f0db)

git at git.haskell.org git at git.haskell.org
Sun Feb 10 21:30:12 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branches: wip/T15449,wip/T16188,wip/llvm-configure-opts
Link       : http://ghc.haskell.org/trac/ghc/changeset/d97f0db8fa6c5d9a4c90c6096b01a76da07cfb2b/ghc

>---------------------------------------------------------------

commit d97f0db8fa6c5d9a4c90c6096b01a76da07cfb2b
Author: Sylvain Henry <sylvain at haskus.fr>
Date:   Tue Jan 29 02:14:12 2019 +0100

    Fix test for T16180 on Darwin (fix #16128)


>---------------------------------------------------------------

d97f0db8fa6c5d9a4c90c6096b01a76da07cfb2b
 testsuite/tests/th/T16180.hs | 21 ++++++++++-----------
 testsuite/tests/th/all.T     |  2 +-
 2 files changed, 11 insertions(+), 12 deletions(-)

diff --git a/testsuite/tests/th/T16180.hs b/testsuite/tests/th/T16180.hs
index 2a4b80c..073ad7a 100644
--- a/testsuite/tests/th/T16180.hs
+++ b/testsuite/tests/th/T16180.hs
@@ -4,19 +4,18 @@ module Main where
 
 import Language.Haskell.TH.Syntax
 import Foreign.C.String
+import Config -- from "ghc" package
 
 $(do
-   -- some architectures require a "_" symbol prefix...
-   -- GHC defines a LEADING_UNDERSCORE CPP constant to indicate this.
-   addForeignSource LangAsm
-      "#if defined(LEADING_UNDERSCORE)\n\
-      \.global \"_mydata\"\n\
-      \_mydata:\n\
-      \#else\n\
-      \.global \"mydata\"\n\
-      \mydata:\n\
-      \#endif\n\
-      \.ascii \"Hello world\\0\"\n"
+   -- some targets (e.g. Darwin) require a "_" symbol prefix...
+   addForeignSource LangAsm (if cLeadingUnderscore == "YES"
+      then ".global \"_mydata\"\n\
+           \_mydata:\n\
+           \.ascii \"Hello world\\0\"\n"
+      else ".global \"mydata\"\n\
+           \mydata:\n\
+           \.ascii \"Hello world\\0\"\n"
+      )
    return [])
 
 foreign import ccall "&mydata" mystring :: CString
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 59123fa..0d34c69 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -461,5 +461,5 @@ test('T15437', expect_broken(15437), multimod_compile,
 test('T15985', normal, compile, [''])
 test('T16133', normal, compile_fail, [''])
 test('T15471', normal, multimod_compile, ['T15471.hs', '-v0'])
-test('T16180', when(opsys('darwin'), expect_broken(16218)), compile_and_run, [''])
+test('T16180', normal, compile_and_run, ['-package ghc'])
 test('T16183', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])



More information about the ghc-commits mailing list