[commit: ghc] master: Allow aligning of cmm procs at specific boundry (f68c2cb)

git at git.haskell.org git at git.haskell.org
Sun Jun 3 05:40:30 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/f68c2cb60f881a0a41ae2e8cafc5de193ef9c3fb/ghc

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

commit f68c2cb60f881a0a41ae2e8cafc5de193ef9c3fb
Author: klebinger.andreas at gmx.at <klebinger.andreas at gmx.at>
Date:   Sun Jun 3 00:37:59 2018 -0400

    Allow aligning of cmm procs at specific boundry
    
    Allows to align CmmProcs at the given boundries.
    
    It makes performance usually worse but can be helpful
    to limit the effect of a unrelated function B becoming
    faster/slower after changing function A.
    
    Test Plan: ci, using it.
    
    Reviewers: bgamari
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie, carter
    
    GHC Trac Issues: #15148
    
    Differential Revision: https://phabricator.haskell.org/D4706


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

f68c2cb60f881a0a41ae2e8cafc5de193ef9c3fb
 compiler/main/DynFlags.hs      |  7 +++++++
 compiler/nativeGen/X86/Ppr.hs  |  7 +++++++
 docs/users_guide/debugging.rst | 11 +++++++++++
 3 files changed, 25 insertions(+)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index b9141f9..b2c82fa 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -876,6 +876,8 @@ data DynFlags = DynFlags {
   floatLamArgs          :: Maybe Int,   -- ^ Arg count for lambda floating
                                         --   See CoreMonad.FloatOutSwitches
 
+  cmmProcAlignment      :: Maybe Int,   -- ^ Align Cmm functions at this boundry or use default.
+
   historySize           :: Int,         -- ^ Simplification history size
 
   importPaths           :: [FilePath],
@@ -1758,6 +1760,7 @@ defaultDynFlags mySettings (myLlvmTargets, myLlvmPasses) =
         specConstrRecursive     = 3,
         liberateCaseThreshold   = Just 2000,
         floatLamArgs            = Just 0, -- Default: float only if no fvs
+        cmmProcAlignment        = Nothing,
 
         historySize             = 20,
         strictnessBefore        = [],
@@ -3397,6 +3400,10 @@ dynamic_flags_deps = [
       (intSuffix (\n d -> d { floatLamArgs = Just n }))
   , make_ord_flag defFlag "ffloat-all-lams"
       (noArg (\d -> d { floatLamArgs = Nothing }))
+  , make_ord_flag defFlag "fproc-alignment"
+      (intSuffix (\n d -> d { cmmProcAlignment = Just n }))
+
+
   , make_ord_flag defFlag "fhistory-size"
       (intSuffix (\n d -> d { historySize = n }))
   , make_ord_flag defFlag "funfolding-creation-threshold"
diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs
index c03bf4f..c5fbeb5 100644
--- a/compiler/nativeGen/X86/Ppr.hs
+++ b/compiler/nativeGen/X86/Ppr.hs
@@ -73,12 +73,17 @@ import Data.Bits
 -- .subsections_via_symbols and -dead_strip can be found at
 -- <https://developer.apple.com/library/mac/documentation/DeveloperTools/Reference/Assembler/040-Assembler_Directives/asm_directives.html#//apple_ref/doc/uid/TP30000823-TPXREF101>
 
+pprProcAlignment :: SDoc
+pprProcAlignment = sdocWithDynFlags $ \dflags ->
+  (maybe empty pprAlign . cmmProcAlignment $ dflags)
+
 pprNatCmmDecl :: NatCmmDecl (Alignment, CmmStatics) Instr -> SDoc
 pprNatCmmDecl (CmmData section dats) =
   pprSectionAlign section $$ pprDatas dats
 
 pprNatCmmDecl proc@(CmmProc top_info lbl _ (ListGraph blocks)) =
   sdocWithDynFlags $ \dflags ->
+  pprProcAlignment $$
   case topInfoTable proc of
     Nothing ->
        case blocks of
@@ -86,6 +91,7 @@ pprNatCmmDecl proc@(CmmProc top_info lbl _ (ListGraph blocks)) =
            pprLabel lbl
          blocks -> -- special case for code without info table:
            pprSectionAlign (Section Text lbl) $$
+           pprProcAlignment $$
            pprLabel lbl $$ -- blocks guaranteed not null, so label needed
            vcat (map (pprBasicBlock top_info) blocks) $$
            (if debugLevel dflags > 0
@@ -95,6 +101,7 @@ pprNatCmmDecl proc@(CmmProc top_info lbl _ (ListGraph blocks)) =
     Just (Statics info_lbl _) ->
       sdocWithPlatform $ \platform ->
       pprSectionAlign (Section Text info_lbl) $$
+      pprProcAlignment $$
       (if platformHasSubsectionsViaSymbols platform
           then ppr (mkDeadStripPreventer info_lbl) <> char ':'
           else empty) $$
diff --git a/docs/users_guide/debugging.rst b/docs/users_guide/debugging.rst
index 4e0be93..7adcc84 100644
--- a/docs/users_guide/debugging.rst
+++ b/docs/users_guide/debugging.rst
@@ -758,6 +758,17 @@ Checking for consistency
     Compile with alignment checks for all info table dereferences. This can be
     useful when finding pointer tagging issues.
 
+.. ghc-flag:: -fproc-alignment
+    :shortdesc: Align functions at given boundry.
+    :type: dynamic
+
+    Align functions to multiples of the given value. Only valid values are powers
+    of two.
+
+    ``-fproc-alignment=64`` can be used to limit alignment impact on performance
+    as each function will start at a cache line.
+    However forcing larger alignments in general reduces performance.
+
 .. ghc-flag:: -fcatch-bottoms
     :shortdesc: Insert ``error`` expressions after bottoming expressions; useful
         when debugging the compiler.



More information about the ghc-commits mailing list