[Git][ghc/ghc][wip/andreask/arm_mem_model] NCG: AArch64 - Add -finter-module-far-jumps.

Andreas Klebinger (@AndreasK) gitlab at gitlab.haskell.org
Fri Mar 7 16:14:52 UTC 2025



Andreas Klebinger pushed to branch wip/andreask/arm_mem_model at Glasgow Haskell Compiler / GHC


Commits:
5757fbcf by Andreas Klebinger at 2025-03-07T16:52:07+01:00
NCG: AArch64 - Add -finter-module-far-jumps.

When enabled the arm backend will assume jumps to targets outside of the
current module are further than 128MB away.

This will allow for code to work if:
* The current module results in less than 128MB of code.
* The whole program is loaded within a 4GB memory region.

We enable this by default on mac where the lack of split sections can
sometimes cause us to go over this limit - see #24648.

This works around #24648 for now.

-------------------------
Metric Increase:
    T783
-------------------------

- - - - -


7 changed files:

- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/using-optimisation.rst


Changes:

=====================================
compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
=====================================
@@ -24,7 +24,7 @@ import GHC.Cmm.DebugBlock
 import GHC.CmmToAsm.Monad
    ( NatM, getNewRegNat
    , getPicBaseMaybeNat, getPlatform, getConfig
-   , getDebugBlock, getFileId, getNewLabelNat
+   , getDebugBlock, getFileId, getNewLabelNat, getThisModuleNat
    )
 -- import GHC.CmmToAsm.Instr
 import GHC.CmmToAsm.PIC
@@ -1505,8 +1505,19 @@ assignReg_FltCode = assignReg_IntCode
 -- Jumps
 
 genJump :: CmmExpr{-the branch target-} -> NatM InstrBlock
-genJump expr@(CmmLit (CmmLabel lbl))
-  = return $ unitOL (annExpr expr (J (TLabel lbl)))
+genJump expr@(CmmLit (CmmLabel lbl)) = do
+  cur_mod <- getThisModuleNat
+  !useFarJumps <- ncgEnableInterModuleFarJumps <$> getConfig
+  let is_local = isLocalCLabel cur_mod lbl
+
+  -- We prefer to generate a near jump using a simble `B` instruction
+  -- with a range (+/-128MB). But if the target is outside the current module
+  -- we might have to account for large code offsets. (#24648)
+  if not useFarJumps || is_local
+    then return $ unitOL (annExpr expr (J (TLabel lbl)))
+    else do
+      (target, _format, code) <- getSomeReg expr
+      return (code `appOL` unitOL (annExpr expr (J (TReg target))))
 
 genJump expr = do
     (target, _format, code) <- getSomeReg expr


=====================================
compiler/GHC/CmmToAsm/Config.hs
=====================================
@@ -47,6 +47,7 @@ data NCGConfig = NCGConfig
    , ncgDwarfSourceNotes      :: !Bool            -- ^ Enable GHC-specific source note DIEs
    , ncgCmmStaticPred         :: !Bool            -- ^ Enable static control-flow prediction
    , ncgEnableShortcutting    :: !Bool            -- ^ Enable shortcutting (don't jump to blocks only containing a jump)
+   , ncgEnableInterModuleFarJumps:: !Bool            -- ^ Use far-jumps for cross-module jumps.
    , ncgComputeUnwinding      :: !Bool            -- ^ Compute block unwinding tables
    , ncgEnableDeadCodeElimination :: !Bool        -- ^ Whether to enable the dead-code elimination
    }


=====================================
compiler/GHC/Driver/Config/CmmToAsm.hs
=====================================
@@ -70,6 +70,7 @@ initNCGConfig dflags this_mod = NCGConfig
    , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags
    , ncgCmmStaticPred       = gopt Opt_CmmStaticPred dflags
    , ncgEnableShortcutting  = gopt Opt_AsmShortcutting dflags
+   , ncgEnableInterModuleFarJumps = gopt Opt_InterModuleFarJumps dflags
    , ncgComputeUnwinding    = debugLevel dflags > 0
    , ncgEnableDeadCodeElimination = not (gopt Opt_InfoTableMap dflags)
                                      -- Disable when -finfo-table-map is on (#20428)


=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -1191,6 +1191,17 @@ defaultFlags settings
 
     ++ validHoleFitDefaults
 
+    -- Platform/OS specific stuff
+    ++ case platformOS platform of
+        -- On mac naturally the linker is broken for jumps with very large
+        -- offsets. (#24648) So we enable HugeTextSections by default to generate
+        -- far jumps when crossing module boundries instead. As these don't rely
+        -- on linker fixups.
+        OSDarwin
+          | platformArch platform == ArchAArch64
+          -> [Opt_InterModuleFarJumps]
+        _ -> []
+
 
     where platform = sTargetPlatform settings
 


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -657,6 +657,7 @@ data GeneralFlag
    | Opt_CmmElimCommonBlocks
    | Opt_CmmControlFlow
    | Opt_AsmShortcutting
+   | Opt_InterModuleFarJumps
    | Opt_OmitYields
    | Opt_FunToThunk               -- deprecated
    | Opt_DictsStrict                     -- be strict in argument dictionaries
@@ -906,6 +907,7 @@ optimisationFlags = EnumSet.fromList
    , Opt_CmmSink
    , Opt_CmmElimCommonBlocks
    , Opt_AsmShortcutting
+   , Opt_InterModuleFarJumps
    , Opt_FunToThunk
    , Opt_DmdTxDictSel
    , Opt_Loopification


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2462,6 +2462,7 @@ fFlagsDeps = [
   flagSpec "gen-manifest"                     Opt_GenManifest,
   flagSpec "ghci-history"                     Opt_GhciHistory,
   flagSpec "ghci-leak-check"                  Opt_GhciLeakCheck,
+  flagSpec "inter-module-far-jumps"               Opt_InterModuleFarJumps,
   flagSpec "validate-ide-info"                Opt_ValidateHie,
   flagGhciSpec "local-ghci-history"           Opt_LocalGhciHistory,
   flagGhciSpec "no-it"                        Opt_NoIt,


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -687,6 +687,22 @@ as such you shouldn't need to set any of them explicitly. A flag
     ``-fno-full-laziness``. If that is inconvenient for you, please leave a
     comment `on the issue tracker (#21204) <https://gitlab.haskell.org/ghc/ghc/-/issues/21204>`__.
 
+.. ghc-flag:: -finter-module-far-jumps
+    :shortdesc: Assume code sections can be very large.
+    :type: dynamic
+    :reverse: -fno-inter-module-far-jumps
+    :category:
+
+    :default: On for AArch64 MacOS
+
+    This flag forces GHC to use far jumps instead of near jumps for all jumps
+    which cross module boundries. This removes the need for jump islands/linker
+    jump fixups which some linkers struggle to deal with. (:ghc-ticket:`24648`)
+
+    This comes at a very modest code size/runtime overhead. Note that this flag
+    currently only affects the NCG AArch64 backend.
+
+
 .. ghc-flag:: -fignore-asserts
     :shortdesc: Ignore assertions in the source. Implied by :ghc-flag:`-O`.
     :type: dynamic



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5757fbcf88911bf4249eef0633528c3258a36d49

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5757fbcf88911bf4249eef0633528c3258a36d49
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/20250307/9f82e373/attachment-0001.html>


More information about the ghc-commits mailing list