[commit: ghc] wip/simd: Add support for -mavx and -mavx2 flags. (4485cac)

git at git.haskell.org git at git.haskell.org
Mon Sep 16 07:05:30 CEST 2013


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

On branch  : wip/simd
Link       : http://ghc.haskell.org/trac/ghc/changeset/4485cacfa776a920e8437e90c48a19f51a93cb43/ghc

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

commit 4485cacfa776a920e8437e90c48a19f51a93cb43
Author: Geoffrey Mainland <gmainlan at microsoft.com>
Date:   Wed Feb 13 16:33:01 2013 +0000

    Add support for -mavx and -mavx2 flags.


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

4485cacfa776a920e8437e90c48a19f51a93cb43
 compiler/main/DriverPipeline.hs |   12 +++++++++++-
 compiler/main/DynFlags.hs       |   18 ++++++++++++++++--
 libraries/primitive             |    2 +-
 libraries/vector                |    2 +-
 4 files changed, 29 insertions(+), 5 deletions(-)

diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index a6567c8..905608d 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -1452,7 +1452,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
@@ -1485,6 +1486,10 @@ runPhase (RealPhase LlvmLlc) input_fn dflags
                 | isSse2Enabled dflags   = ["-mattr=+sse2"]
                 | otherwise              = []
 
+        avxOpts | isAvx2Enabled dflags   = ["-mattr=+avx2"]
+                | isAvxEnabled dflags    = ["-mattr=+avx"]
+                | otherwise              = []
+
 -----------------------------------------------------------------------------
 -- LlvmMangle phase
 
@@ -2093,6 +2098,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__"  | isAvxEnabled  dflags ] ++
+          [ "-D__AVX2__" | isAvx2Enabled dflags ]
+
     backend_defs <- getBackendDefs dflags
 
     cpp_prog       (   map SysTools.Option verbFlags
@@ -2102,6 +2111,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 ada18b5..7743915 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(..),
@@ -765,6 +767,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)
@@ -1395,6 +1399,8 @@ defaultDynFlags mySettings =
         interactivePrint = Nothing,
         nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum",
         sseVersion = Nothing,
+        avx = False,
+        avx2 = False,
         rtldFlags = panic "defaultDynFlags: no rtldFlags"
       }
 
@@ -2299,6 +2305,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))
@@ -3578,7 +3586,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
@@ -3598,6 +3606,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
 
diff --git a/libraries/primitive b/libraries/primitive
index c6b1e20..fbb66b4 160000
--- a/libraries/primitive
+++ b/libraries/primitive
@@ -1 +1 @@
-Subproject commit c6b1e204f0f2a1a0d6cb1df35fa60762b2fe3cdc
+Subproject commit fbb66b473986b5f06a0d8302e9c55391215d8cad
diff --git a/libraries/vector b/libraries/vector
index f271569..502788e 160000
--- a/libraries/vector
+++ b/libraries/vector
@@ -1 +1 @@
-Subproject commit f27156970d9480806a5defcfea5367187c2a6997
+Subproject commit 502788ebda3d4e94d4d8e5ec4e46b49d5e598657




More information about the ghc-commits mailing list