[commit: ghc] wip/simd: Add support for -mavx and -mavx2 flags. (0c6cf2a)
git at git.haskell.org
git at git.haskell.org
Mon Sep 23 06:12:19 CEST 2013
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/simd
Link : http://ghc.haskell.org/trac/ghc/changeset/0c6cf2a83b65bcb873e574d4940823e7f1c67c65/ghc
>---------------------------------------------------------------
commit 0c6cf2a83b65bcb873e574d4940823e7f1c67c65
Author: Geoffrey Mainland <gmainlan at microsoft.com>
Date: Wed Feb 13 16:33:01 2013 +0000
Add support for -mavx and -mavx2 flags.
>---------------------------------------------------------------
0c6cf2a83b65bcb873e574d4940823e7f1c67c65
compiler/main/DriverPipeline.hs | 12 +++++++++++-
compiler/main/DynFlags.hs | 18 ++++++++++++++++--
2 files changed, 27 insertions(+), 3 deletions(-)
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 035d577..a123564 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -1380,7 +1380,8 @@ runPhase (RealPhase LlvmLlc) input_fn dflags
++ [SysTools.Option tbaa]
++ map SysTools.Option fpOpts
++ map SysTools.Option abiOpts
- ++ map SysTools.Option sseOpts)
+ ++ map SysTools.Option sseOpts
+ ++ map SysTools.Option avxOpts)
return (RealPhase next_phase, output_fn)
where
@@ -1413,6 +1414,10 @@ runPhase (RealPhase LlvmLlc) input_fn dflags
| isSse2Enabled dflags = ["-mattr=+sse2"]
| otherwise = []
+ avxOpts | isAvx2Enabled dflags = ["-mattr=+avx2"]
+ | isAvxEnabled dflags = ["-mattr=+avx"]
+ | otherwise = []
+
-----------------------------------------------------------------------------
-- LlvmMangle phase
@@ -2022,6 +2027,10 @@ doCpp dflags raw input_fn output_fn = do
[ "-D__SSE2__=1" | sse2 || sse4_2 ] ++
[ "-D__SSE4_2__=1" | sse4_2 ]
+ let avx_defs =
+ [ "-D__AVX__=1" | isAvxEnabled dflags ] ++
+ [ "-D__AVX2__=1" | isAvx2Enabled dflags ]
+
backend_defs <- getBackendDefs dflags
cpp_prog ( map SysTools.Option verbFlags
@@ -2031,6 +2040,7 @@ doCpp dflags raw input_fn output_fn = do
++ map SysTools.Option backend_defs
++ map SysTools.Option hscpp_opts
++ map SysTools.Option sse_defs
+ ++ map SysTools.Option avx_defs
-- Set the language mode to assembler-with-cpp when preprocessing. This
-- alleviates some of the C99 macro rules relating to whitespace and the hash
-- operator, which we tend to abuse. Clang in particular is not very happy
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 63da5d6..cf6db24 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -128,9 +128,11 @@ module DynFlags (
unsafeGlobalDynFlags, setUnsafeGlobalDynFlags,
- -- * SSE
+ -- * SSE and AVX
isSse2Enabled,
isSse4_2Enabled,
+ isAvxEnabled,
+ isAvx2Enabled,
-- * Linker information
LinkerInfo(..),
@@ -770,6 +772,8 @@ data DynFlags = DynFlags {
-- | Machine dependant flags (-m<blah> stuff)
sseVersion :: Maybe (Int, Int), -- (major, minor)
+ avx :: Bool,
+ avx2 :: Bool,
-- | Run-time linker information (what options we need, etc.)
rtldFlags :: IORef (Maybe LinkerInfo)
@@ -1401,6 +1405,8 @@ defaultDynFlags mySettings =
interactivePrint = Nothing,
nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum",
sseVersion = Nothing,
+ avx = False,
+ avx2 = False,
rtldFlags = panic "defaultDynFlags: no rtldFlags"
}
@@ -2305,6 +2311,8 @@ dynamic_flags = [
, Flag "monly-3-regs" (NoArg (addWarn "The -monly-3-regs flag does nothing; it will be removed in a future GHC release"))
, Flag "monly-4-regs" (NoArg (addWarn "The -monly-4-regs flag does nothing; it will be removed in a future GHC release"))
, Flag "msse" (versionSuffix (\maj min d -> d{ sseVersion = Just (maj, min) }))
+ , Flag "mavx" (noArg (\d -> d{ avx = True }))
+ , Flag "mavx2" (noArg (\d -> d{ avx2 = True }))
------ Warning opts -------------------------------------------------
, Flag "W" (NoArg (mapM_ setWarningFlag minusWOpts))
@@ -3585,7 +3593,7 @@ setUnsafeGlobalDynFlags :: DynFlags -> IO ()
setUnsafeGlobalDynFlags = writeIORef v_unsafeGlobalDynFlags
-- -----------------------------------------------------------------------------
--- SSE
+-- SSE and AVX
-- TODO: Instead of using a separate predicate (i.e. isSse2Enabled) to
-- check if SSE is enabled, we might have x86-64 imply the -msse2
@@ -3605,6 +3613,12 @@ isSse2Enabled dflags = case platformArch (targetPlatform dflags) of
isSse4_2Enabled :: DynFlags -> Bool
isSse4_2Enabled dflags = sseVersion dflags >= Just (4,2)
+isAvxEnabled :: DynFlags -> Bool
+isAvxEnabled dflags = avx dflags || avx2 dflags
+
+isAvx2Enabled :: DynFlags -> Bool
+isAvx2Enabled dflags = avx2 dflags
+
-- -----------------------------------------------------------------------------
-- Linker information
More information about the ghc-commits
mailing list