[commit: ghc] wip/ermsb: ghc: add -march/-mcpu to DynFlags (41ddcd7)

git at git.haskell.org git at git.haskell.org
Mon Apr 28 09:18:14 UTC 2014


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

On branch  : wip/ermsb
Link       : http://ghc.haskell.org/trac/ghc/changeset/41ddcd7d7909224ac891c7b1ced8f2c59cb07dfc/ghc

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

commit 41ddcd7d7909224ac891c7b1ced8f2c59cb07dfc
Author: Austin Seipp <austin at well-typed.com>
Date:   Mon Apr 21 19:53:59 2014 -0500

    ghc: add -march/-mcpu to DynFlags
    
    Currently these are still unused, but now recognized by the command
    line.
    
    Signed-off-by: Austin Seipp <austin at well-typed.com>


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

41ddcd7d7909224ac891c7b1ced8f2c59cb07dfc
 compiler/main/DynFlags.hs |   22 ++++++++++++++++++++++
 1 file changed, 22 insertions(+)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 72ebb38..ee84bf5 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -794,6 +794,9 @@ data DynFlags = DynFlags {
   avx512f               :: Bool, -- Enable AVX-512 instructions.
   avx512pf              :: Bool, -- Enable AVX-512 PreFetch Instructions.
 
+  march                 :: CPUDesc,
+  mcpu                  :: CPUDesc,
+
   -- | Run-time linker information (what options we need, etc.)
   rtldInfo              :: IORef (Maybe LinkerInfo),
 
@@ -1459,6 +1462,8 @@ defaultDynFlags mySettings =
         avx512er = False,
         avx512f = False,
         avx512pf = False,
+        march = Generic,
+        mcpu  = Generic,
         rtldInfo = panic "defaultDynFlags: no rtldInfo",
         rtccInfo = panic "defaultDynFlags: no rtccInfo",
 
@@ -2388,6 +2393,9 @@ dynamic_flags = [
   , Flag "mavx512f"     (noArg (\d -> d{ avx512f = True }))
   , Flag "mavx512pf"    (noArg (\d -> d{ avx512pf = True }))
 
+  , Flag "march"        (HasArg hasMarch)
+  , Flag "mcpu"         (HasArg hasMcpu)
+
      ------ Warning opts -------------------------------------------------
   , Flag "W"      (NoArg (mapM_ setWarningFlag minusWOpts))
   , Flag "Werror" (NoArg (setGeneralFlag           Opt_WarnIsError))
@@ -3704,6 +3712,20 @@ setUnsafeGlobalDynFlags :: DynFlags -> IO ()
 setUnsafeGlobalDynFlags = writeIORef v_unsafeGlobalDynFlags
 
 -- -----------------------------------------------------------------------------
+-- march/mcpu handling
+
+hasMarch :: String -> DynP ()
+hasMarch s = case descToCPU s of
+  Nothing -> addWarn ("Invalid argument for -march, '"++s++"'")
+  Just x  -> do
+    upd (\d -> d { march = x })
+
+hasMcpu :: String -> DynP ()
+hasMcpu s = case descToCPU s of
+  Nothing -> addWarn ("Invalid argument for -mcpu, '"++s++"'")
+  Just x  -> upd (\d -> d { mcpu = x })
+
+-- -----------------------------------------------------------------------------
 -- SSE and AVX
 
 -- TODO: Instead of using a separate predicate (i.e. isSse2Enabled) to



More information about the ghc-commits mailing list