[Git][ghc/ghc][wip/fltused] LLVM: use -relocation-model=pic on Windows
sheaf (@sheaf)
gitlab at gitlab.haskell.org
Wed Sep 4 08:52:31 UTC 2024
sheaf pushed to branch wip/fltused at Glasgow Haskell Compiler / GHC
Commits:
7bda232a by sheaf at 2024-09-04T10:50:56+02:00
LLVM: use -relocation-model=pic on Windows
This is necessary to avoid the segfaults reported in #22487.
Fixes #22487
- - - - -
3 changed files:
- compiler/GHC/Driver/Pipeline/Execute.hs
- + testsuite/tests/llvm/should_run/T22487.hs
- + testsuite/tests/llvm/should_run/all.T
Changes:
=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -969,13 +969,18 @@ llvmOptions llvm_config dflags =
++ [("", "-target-abi=" ++ abi) | not (null abi) ]
where target = platformMisc_llvmTarget $ platformMisc dflags
+ target_os = platformOS (targetPlatform dflags)
Just (LlvmTarget _ mcpu mattr) = lookup target (llvmTargets llvm_config)
-- Relocation models
- rmodel | gopt Opt_PIC dflags = "pic"
- | positionIndependent dflags = "pic"
- | ways dflags `hasWay` WayDyn = "dynamic-no-pic"
- | otherwise = "static"
+ rmodel | gopt Opt_PIC dflags
+ || positionIndependent dflags
+ || target_os == OSMinGW32 -- #22487: use PIC on (64-bit) Windows
+ = "pic"
+ | ways dflags `hasWay` WayDyn
+ = "dynamic-no-pic"
+ | otherwise
+ = "static"
platform = targetPlatform dflags
arch = platformArch platform
=====================================
testsuite/tests/llvm/should_run/T22487.hs
=====================================
@@ -0,0 +1,8 @@
+
+module Main where
+
+add :: Double -> Double -> Double
+add x y = x + y
+{-# NOINLINE add #-}
+main = do putStrLn "Hello world!"
+ print (add 1.0 2.0)
=====================================
testsuite/tests/llvm/should_run/all.T
=====================================
@@ -0,0 +1,15 @@
+
+def f( name, opts ):
+ opts.only_ways = ['optllvm', 'llvm', 'debugllvm']
+
+setTestOpts(f)
+
+# Apples LLVM Toolchain knows about a `vortex` cpu (and possibly others), that
+# the stock LLVM toolchain doesn't know about and will warn about. Let's not
+# have test fail just because of processor name differences due to different
+# LLVM Toolchains. GHC tries to pass what apple expects (on darwin), but can
+# be used with the stock LLVM toolchain as well.
+def ignore_llvm_and_vortex( msg ):
+ return re.sub(r".* is not a recognized processor for this target.*\n",r"",msg)
+
+test('T22487', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7bda232ad966e93bb2f44594a0a04c92dd19758f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7bda232ad966e93bb2f44594a0a04c92dd19758f
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/20240904/433f686d/attachment-0001.html>
More information about the ghc-commits
mailing list