[Git][ghc/ghc][master] AArch64/arm64 adjustments

Marge Bot gitlab at gitlab.haskell.org
Sun Nov 15 08:37:07 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00
AArch64/arm64 adjustments

This addes the necessary logic to support aarch64 on elf, as well
as aarch64 on mach-o, which Apple calls arm64.

We change architecture name to AArch64, which is the official arm
naming scheme.

- - - - -


30 changed files:

- .gitlab-ci.yml
- aclocal.m4
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
- compiler/GHC/CmmToAsm/Reg/Target.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Platform/ARM64.hs → compiler/GHC/Platform/AArch64.hs
- compiler/GHC/Platform/Regs.hs
- compiler/ghc.cabal.in
- config.sub
- includes/CodeGen.Platform.hs
- includes/rts/Flags.h
- includes/rts/storage/GC.h
- libraries/ghc-boot/GHC/Platform/ArchOS.hs
- libraries/ghci/GHCi/InfoTable.hsc
- llvm-targets
- rts/Adjustor.c
- rts/StgCRun.c
- rts/linker/elf_plt_aarch64.c
- rts/linker/elf_reloc.c
- rts/package.conf.in
- rts/rts.cabal.in
- rts/sm/Storage.c
- utils/llvm-targets/gen-data-layout.sh


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -528,6 +528,14 @@ validate-x86_64-darwin:
   tags:
     - aarch64-linux
 
+.build-aarch64-linux-deb10-llvm:
+  extends: .build-aarch64-linux-deb10
+  stage: full-build
+  variables:
+    BUILD_FLAVOUR: perf-llvm
+  tags:
+    - aarch64-linux
+
 validate-aarch64-linux-deb10:
   extends: .build-aarch64-linux-deb10
   artifacts:


=====================================
aclocal.m4
=====================================
@@ -118,7 +118,7 @@ AC_DEFUN([FPTOOLS_SET_PLATFORM_VARS],
         GHC_CONVERT_OS([$target_os], [$TargetArch], [TargetOS])
     fi
 
-    GHC_LLVM_TARGET([$target_cpu],[$target_vendor],[$target_os],[LlvmTarget])
+    GHC_LLVM_TARGET([$target],[$target_cpu],[$target_vendor],[$target_os],[LlvmTarget])
 
     GHC_SELECT_FILE_EXTENSIONS([$host], [exeext_host], [soext_host])
     GHC_SELECT_FILE_EXTENSIONS([$target], [exeext_target], [soext_target])
@@ -218,7 +218,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS],
             test -z "[$]2" || eval "[$]2=\"ArchARM \$ARM_ISA \$ARM_ISA_EXT \$ARM_ABI\""
             ;;
         aarch64)
-            test -z "[$]2" || eval "[$]2=ArchARM64"
+            test -z "[$]2" || eval "[$]2=ArchAArch64"
             ;;
         alpha)
             test -z "[$]2" || eval "[$]2=ArchAlpha"
@@ -327,9 +327,14 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS],
     AC_LINK_IFELSE(
         [AC_LANG_PROGRAM([], [__asm__ (".subsections_via_symbols");])],
         [AC_MSG_RESULT(yes)
-         TargetHasSubsectionsViaSymbols=YES
-         AC_DEFINE([HAVE_SUBSECTIONS_VIA_SYMBOLS],[1],
+         if test x"$TargetArch" = xaarch64; then
+            dnl subsections via symbols is busted on arm64
+            TargetHasSubsectionsViaSymbols=NO
+         else
+            TargetHasSubsectionsViaSymbols=YES
+            AC_DEFINE([HAVE_SUBSECTIONS_VIA_SYMBOLS],[1],
                    [Define to 1 if Apple-style dead-stripping is supported.])
+         fi
         ],
         [TargetHasSubsectionsViaSymbols=NO
          AC_MSG_RESULT(no)])
@@ -1976,7 +1981,7 @@ AC_MSG_CHECKING(for path to top of build tree)
 # `libraries/base/System/Info.hs`'s documentation.
 AC_DEFUN([GHC_CONVERT_CPU],[
 case "$1" in
-  aarch64*)
+  aarch64*|arm64*)
     $2="aarch64"
     ;;
   alpha*)
@@ -2058,18 +2063,19 @@ case "$1" in
   esac
 ])
 
-# GHC_LLVM_TARGET(target_cpu, target_vendor, target_os, llvm_target_var)
+# GHC_LLVM_TARGET(target, target_cpu, target_vendor, target_os, llvm_target_var)
 # --------------------------------
 # converts the canonicalized target into something llvm can understand
 AC_DEFUN([GHC_LLVM_TARGET], [
-  case "$2-$3" in
+  llvm_target_cpu=$2
+  case "$1" in
     *-freebsd*-gnueabihf)
       llvm_target_vendor="unknown"
       llvm_target_os="freebsd-gnueabihf"
       ;;
-    hardfloat-*eabi)
+    *-hardfloat-*eabi)
       llvm_target_vendor="unknown"
-      llvm_target_os="$3""hf"
+      llvm_target_os="$4""hf"
       ;;
     *-mingw32|*-mingw64|*-msys)
       llvm_target_vendor="unknown"
@@ -2080,15 +2086,25 @@ AC_DEFUN([GHC_LLVM_TARGET], [
     # turned into just `-linux` and fail to be found
     # in the `llvm-targets` file.
     *-android*|*-gnueabi*|*-musleabi*)
-      GHC_CONVERT_VENDOR([$2],[llvm_target_vendor])
-      llvm_target_os="$3"
+      GHC_CONVERT_VENDOR([$3],[llvm_target_vendor])
+      llvm_target_os="$4"
+      ;;
+    # apple is a bit about their naming scheme for
+    # aarch64; and clang on macOS doesn't know that
+    # aarch64 would be arm64. So for LLVM we'll need
+    # to call it arm64; while we'll refer to it internally
+    # as aarch64 for consistency and sanity.
+    aarch64-apple-*|arm64-apple-*)
+      llvm_target_cpu="arm64"
+      GHC_CONVERT_VENDOR([$3],[llvm_target_vendor])
+      GHC_CONVERT_OS([$4],[$2],[llvm_target_os])
       ;;
     *)
-      GHC_CONVERT_VENDOR([$2],[llvm_target_vendor])
-      GHC_CONVERT_OS([$3],[$1],[llvm_target_os])
+      GHC_CONVERT_VENDOR([$3],[llvm_target_vendor])
+      GHC_CONVERT_OS([$4],[$2],[llvm_target_os])
       ;;
   esac
-  $4="$1-$llvm_target_vendor-$llvm_target_os"
+  $5="$llvm_target_cpu-$llvm_target_vendor-$llvm_target_os"
 ])
 
 


=====================================
compiler/GHC/CmmToAsm.hs
=====================================
@@ -166,7 +166,7 @@ nativeCodeGen dflags this_mod modLoc h us cmms
       ArchSPARC64   -> panic "nativeCodeGen: No NCG for SPARC64"
       ArchS390X     -> panic "nativeCodeGen: No NCG for S390X"
       ArchARM {}    -> panic "nativeCodeGen: No NCG for ARM"
-      ArchARM64     -> panic "nativeCodeGen: No NCG for ARM64"
+      ArchAArch64   -> panic "nativeCodeGen: No NCG for AArch64"
       ArchAlpha     -> panic "nativeCodeGen: No NCG for Alpha"
       ArchMipseb    -> panic "nativeCodeGen: No NCG for mipseb"
       ArchMipsel    -> panic "nativeCodeGen: No NCG for mipsel"
@@ -1193,4 +1193,3 @@ initNCGConfig dflags this_mod = NCGConfig
    , ncgDwarfStripBlockInfo = debugLevel dflags <  2 -- We strip out block information when running with -g0 or -g1.
    , ncgDwarfSourceNotes    = debugLevel dflags >= 3 -- We produce GHC-specific source-note DIEs only with -g3
    }
-


=====================================
compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
=====================================
@@ -115,7 +115,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl
                             ArchSPARC64   -> panic "trivColorable ArchSPARC64"
                             ArchPPC_64 _  -> 15
                             ArchARM _ _ _ -> panic "trivColorable ArchARM"
-                            ArchARM64     -> panic "trivColorable ArchARM64"
+                            ArchAArch64   -> panic "trivColorable ArchAArch64"
                             ArchAlpha     -> panic "trivColorable ArchAlpha"
                             ArchMipseb    -> panic "trivColorable ArchMipseb"
                             ArchMipsel    -> panic "trivColorable ArchMipsel"
@@ -146,7 +146,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus
                             ArchSPARC64   -> panic "trivColorable ArchSPARC64"
                             ArchPPC_64 _  -> 0
                             ArchARM _ _ _ -> panic "trivColorable ArchARM"
-                            ArchARM64     -> panic "trivColorable ArchARM64"
+                            ArchAArch64   -> panic "trivColorable ArchAArch64"
                             ArchAlpha     -> panic "trivColorable ArchAlpha"
                             ArchMipseb    -> panic "trivColorable ArchMipseb"
                             ArchMipsel    -> panic "trivColorable ArchMipsel"
@@ -179,7 +179,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu
                             ArchSPARC64   -> panic "trivColorable ArchSPARC64"
                             ArchPPC_64 _  -> 20
                             ArchARM _ _ _ -> panic "trivColorable ArchARM"
-                            ArchARM64     -> panic "trivColorable ArchARM64"
+                            ArchAArch64   -> panic "trivColorable ArchAArch64"
                             ArchAlpha     -> panic "trivColorable ArchAlpha"
                             ArchMipseb    -> panic "trivColorable ArchMipseb"
                             ArchMipsel    -> panic "trivColorable ArchMipsel"


=====================================
compiler/GHC/CmmToAsm/Reg/Linear.hs
=====================================
@@ -223,7 +223,7 @@ linearRegAlloc config entry_ids block_live sccs
       ArchSPARC64    -> panic "linearRegAlloc ArchSPARC64"
       ArchPPC        -> go $ (frInitFreeRegs platform :: PPC.FreeRegs)
       ArchARM _ _ _  -> panic "linearRegAlloc ArchARM"
-      ArchARM64      -> panic "linearRegAlloc ArchARM64"
+      ArchAArch64    -> panic "linearRegAlloc ArchAArch64"
       ArchPPC_64 _   -> go $ (frInitFreeRegs platform :: PPC.FreeRegs)
       ArchAlpha      -> panic "linearRegAlloc ArchAlpha"
       ArchMipseb     -> panic "linearRegAlloc ArchMipseb"


=====================================
compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
=====================================
@@ -78,7 +78,7 @@ maxSpillSlots config = case platformArch (ncgPlatform config) of
    ArchSPARC     -> SPARC.Instr.maxSpillSlots config
    ArchSPARC64   -> panic "maxSpillSlots ArchSPARC64"
    ArchARM _ _ _ -> panic "maxSpillSlots ArchARM"
-   ArchARM64     -> panic "maxSpillSlots ArchARM64"
+   ArchAArch64   -> panic "maxSpillSlots ArchAArch64"
    ArchPPC_64 _  -> PPC.Instr.maxSpillSlots config
    ArchAlpha     -> panic "maxSpillSlots ArchAlpha"
    ArchMipseb    -> panic "maxSpillSlots ArchMipseb"


=====================================
compiler/GHC/CmmToAsm/Reg/Target.hs
=====================================
@@ -48,7 +48,7 @@ targetVirtualRegSqueeze platform
       ArchSPARC64   -> panic "targetVirtualRegSqueeze ArchSPARC64"
       ArchPPC_64 _  -> PPC.virtualRegSqueeze
       ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM"
-      ArchARM64     -> panic "targetVirtualRegSqueeze ArchARM64"
+      ArchAArch64   -> panic "targetVirtualRegSqueeze ArchAArch64"
       ArchAlpha     -> panic "targetVirtualRegSqueeze ArchAlpha"
       ArchMipseb    -> panic "targetVirtualRegSqueeze ArchMipseb"
       ArchMipsel    -> panic "targetVirtualRegSqueeze ArchMipsel"
@@ -67,7 +67,7 @@ targetRealRegSqueeze platform
       ArchSPARC64   -> panic "targetRealRegSqueeze ArchSPARC64"
       ArchPPC_64 _  -> PPC.realRegSqueeze
       ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM"
-      ArchARM64     -> panic "targetRealRegSqueeze ArchARM64"
+      ArchAArch64   -> panic "targetRealRegSqueeze ArchAArch64"
       ArchAlpha     -> panic "targetRealRegSqueeze ArchAlpha"
       ArchMipseb    -> panic "targetRealRegSqueeze ArchMipseb"
       ArchMipsel    -> panic "targetRealRegSqueeze ArchMipsel"
@@ -85,7 +85,7 @@ targetClassOfRealReg platform
       ArchSPARC64   -> panic "targetClassOfRealReg ArchSPARC64"
       ArchPPC_64 _  -> PPC.classOfRealReg
       ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM"
-      ArchARM64     -> panic "targetClassOfRealReg ArchARM64"
+      ArchAArch64   -> panic "targetClassOfRealReg ArchAArch64"
       ArchAlpha     -> panic "targetClassOfRealReg ArchAlpha"
       ArchMipseb    -> panic "targetClassOfRealReg ArchMipseb"
       ArchMipsel    -> panic "targetClassOfRealReg ArchMipsel"
@@ -103,7 +103,7 @@ targetMkVirtualReg platform
       ArchSPARC64   -> panic "targetMkVirtualReg ArchSPARC64"
       ArchPPC_64 _  -> PPC.mkVirtualReg
       ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM"
-      ArchARM64     -> panic "targetMkVirtualReg ArchARM64"
+      ArchAArch64   -> panic "targetMkVirtualReg ArchAArch64"
       ArchAlpha     -> panic "targetMkVirtualReg ArchAlpha"
       ArchMipseb    -> panic "targetMkVirtualReg ArchMipseb"
       ArchMipsel    -> panic "targetMkVirtualReg ArchMipsel"
@@ -121,7 +121,7 @@ targetRegDotColor platform
       ArchSPARC64   -> panic "targetRegDotColor ArchSPARC64"
       ArchPPC_64 _  -> PPC.regDotColor
       ArchARM _ _ _ -> panic "targetRegDotColor ArchARM"
-      ArchARM64     -> panic "targetRegDotColor ArchARM64"
+      ArchAArch64   -> panic "targetRegDotColor ArchAArch64"
       ArchAlpha     -> panic "targetRegDotColor ArchAlpha"
       ArchMipseb    -> panic "targetRegDotColor ArchMipseb"
       ArchMipsel    -> panic "targetRegDotColor ArchMipsel"


=====================================
compiler/GHC/CmmToC.hs
=====================================
@@ -1158,7 +1158,7 @@ cLoad platform expr rep
           bewareLoadStoreAlignment ArchMipseb   = True
           bewareLoadStoreAlignment ArchMipsel   = True
           bewareLoadStoreAlignment (ArchARM {}) = True
-          bewareLoadStoreAlignment ArchARM64    = True
+          bewareLoadStoreAlignment ArchAArch64  = True
           bewareLoadStoreAlignment ArchSPARC    = True
           bewareLoadStoreAlignment ArchSPARC64  = True
           -- Pessimistically assume that they will also cause problems


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -3842,8 +3842,8 @@ default_PIC platform =
     -- This requires PIC on AArch64, and ExternalDynamicRefs on Linux as on top
     -- of that.  Subsequently we expect all code on aarch64/linux (and macOS) to
     -- be built with -fPIC.
-    (OSDarwin,  ArchARM64)   -> [Opt_PIC]
-    (OSLinux,   ArchARM64)   -> [Opt_PIC, Opt_ExternalDynamicRefs]
+    (OSDarwin,  ArchAArch64) -> [Opt_PIC]
+    (OSLinux,   ArchAArch64) -> [Opt_PIC, Opt_ExternalDynamicRefs]
     (OSOpenBSD, ArchX86_64)  -> [Opt_PIC] -- Due to PIE support in
                                          -- OpenBSD since 5.3 release
                                          -- (1 May 2013) we need to


=====================================
compiler/GHC/Linker/Dynamic.hs
=====================================
@@ -179,7 +179,7 @@ linkDynLib dflags0 o_files dep_packages
                  ++ [ Option "-undefined",
                       Option "dynamic_lookup",
                       Option "-single_module" ]
-                 ++ (if platformArch platform == ArchX86_64
+                 ++ (if platformArch platform `elem` [ ArchX86_64, ArchAArch64 ]
                      then [ ]
                      else [ Option "-Wl,-read_only_relocs,suppress" ])
                  ++ [ Option "-install_name", Option instName ]


=====================================
compiler/GHC/Linker/Static.hs
=====================================
@@ -225,9 +225,9 @@ linkBinary' staticLink dflags o_files dep_units = do
                              (platformOS platform == OSDarwin) &&
                              case platformArch platform of
                                ArchX86 -> True
-                               ArchX86_64 -> True
-                               ArchARM {} -> True
-                               ArchARM64  -> True
+                               ArchX86_64  -> True
+                               ArchARM {}  -> True
+                               ArchAArch64 -> True
                                _ -> False
                           then ["-Wl,-no_compact_unwind"]
                           else [])
@@ -339,4 +339,3 @@ exeFileName platform staticLink output_fn
            else "a.out"
  where s <?.> ext | null (takeExtension s) = s <.> ext
                   | otherwise              = s
-


=====================================
compiler/GHC/Platform.hs
=====================================
@@ -109,7 +109,7 @@ platformOS platform = case platformArchOS platform of
 
 isARM :: Arch -> Bool
 isARM (ArchARM {}) = True
-isARM ArchARM64    = True
+isARM ArchAArch64  = True
 isARM _ = False
 
 -- | This predicate tells us whether the platform is 32-bit.
@@ -232,4 +232,3 @@ platformSOExt platform
       OSDarwin  -> "dylib"
       OSMinGW32 -> "dll"
       _         -> "so"
-


=====================================
compiler/GHC/Platform/ARM64.hs → compiler/GHC/Platform/AArch64.hs
=====================================
@@ -1,10 +1,9 @@
 {-# LANGUAGE CPP #-}
 
-module GHC.Platform.ARM64 where
+module GHC.Platform.AArch64 where
 
 import GHC.Prelude
 
 #define MACHREGS_NO_REGS 0
 #define MACHREGS_aarch64 1
 #include "../../../includes/CodeGen.Platform.hs"
-


=====================================
compiler/GHC/Platform/Regs.hs
=====================================
@@ -1,4 +1,3 @@
-
 module GHC.Platform.Regs
        (callerSaves, activeStgRegs, haveRegBase, globalRegMaybe, freeReg)
        where
@@ -10,7 +9,7 @@ import GHC.Platform
 import GHC.Platform.Reg
 
 import qualified GHC.Platform.ARM        as ARM
-import qualified GHC.Platform.ARM64      as ARM64
+import qualified GHC.Platform.AArch64    as AArch64
 import qualified GHC.Platform.PPC        as PPC
 import qualified GHC.Platform.S390X      as S390X
 import qualified GHC.Platform.SPARC      as SPARC
@@ -26,12 +25,12 @@ callerSaves platform
  | platformUnregisterised platform = NoRegs.callerSaves
  | otherwise
  = case platformArch platform of
-   ArchX86    -> X86.callerSaves
-   ArchX86_64 -> X86_64.callerSaves
-   ArchS390X  -> S390X.callerSaves
-   ArchSPARC  -> SPARC.callerSaves
-   ArchARM {} -> ARM.callerSaves
-   ArchARM64  -> ARM64.callerSaves
+   ArchX86     -> X86.callerSaves
+   ArchX86_64  -> X86_64.callerSaves
+   ArchS390X   -> S390X.callerSaves
+   ArchSPARC   -> SPARC.callerSaves
+   ArchARM {}  -> ARM.callerSaves
+   ArchAArch64 -> AArch64.callerSaves
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.callerSaves
@@ -48,12 +47,12 @@ activeStgRegs platform
  | platformUnregisterised platform = NoRegs.activeStgRegs
  | otherwise
  = case platformArch platform of
-   ArchX86    -> X86.activeStgRegs
-   ArchX86_64 -> X86_64.activeStgRegs
-   ArchS390X  -> S390X.activeStgRegs
-   ArchSPARC  -> SPARC.activeStgRegs
-   ArchARM {} -> ARM.activeStgRegs
-   ArchARM64  -> ARM64.activeStgRegs
+   ArchX86     -> X86.activeStgRegs
+   ArchX86_64  -> X86_64.activeStgRegs
+   ArchS390X   -> S390X.activeStgRegs
+   ArchSPARC   -> SPARC.activeStgRegs
+   ArchARM {}  -> ARM.activeStgRegs
+   ArchAArch64 -> AArch64.activeStgRegs
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.activeStgRegs
@@ -65,12 +64,12 @@ haveRegBase platform
  | platformUnregisterised platform = NoRegs.haveRegBase
  | otherwise
  = case platformArch platform of
-   ArchX86    -> X86.haveRegBase
-   ArchX86_64 -> X86_64.haveRegBase
-   ArchS390X  -> S390X.haveRegBase
-   ArchSPARC  -> SPARC.haveRegBase
-   ArchARM {} -> ARM.haveRegBase
-   ArchARM64  -> ARM64.haveRegBase
+   ArchX86     -> X86.haveRegBase
+   ArchX86_64  -> X86_64.haveRegBase
+   ArchS390X   -> S390X.haveRegBase
+   ArchSPARC   -> SPARC.haveRegBase
+   ArchARM {}  -> ARM.haveRegBase
+   ArchAArch64 -> AArch64.haveRegBase
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.haveRegBase
@@ -82,12 +81,12 @@ globalRegMaybe platform
  | platformUnregisterised platform = NoRegs.globalRegMaybe
  | otherwise
  = case platformArch platform of
-   ArchX86    -> X86.globalRegMaybe
-   ArchX86_64 -> X86_64.globalRegMaybe
-   ArchS390X  -> S390X.globalRegMaybe
-   ArchSPARC  -> SPARC.globalRegMaybe
-   ArchARM {} -> ARM.globalRegMaybe
-   ArchARM64  -> ARM64.globalRegMaybe
+   ArchX86     -> X86.globalRegMaybe
+   ArchX86_64  -> X86_64.globalRegMaybe
+   ArchS390X   -> S390X.globalRegMaybe
+   ArchSPARC   -> SPARC.globalRegMaybe
+   ArchARM {}  -> ARM.globalRegMaybe
+   ArchAArch64 -> AArch64.globalRegMaybe
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.globalRegMaybe
@@ -99,15 +98,14 @@ freeReg platform
  | platformUnregisterised platform = NoRegs.freeReg
  | otherwise
  = case platformArch platform of
-   ArchX86    -> X86.freeReg
-   ArchX86_64 -> X86_64.freeReg
-   ArchS390X  -> S390X.freeReg
-   ArchSPARC  -> SPARC.freeReg
-   ArchARM {} -> ARM.freeReg
-   ArchARM64  -> ARM64.freeReg
+   ArchX86     -> X86.freeReg
+   ArchX86_64  -> X86_64.freeReg
+   ArchS390X   -> S390X.freeReg
+   ArchSPARC   -> SPARC.freeReg
+   ArchARM {}  -> ARM.freeReg
+   ArchAArch64 -> AArch64.freeReg
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.freeReg
 
     | otherwise -> NoRegs.freeReg
-


=====================================
compiler/ghc.cabal.in
=====================================
@@ -478,7 +478,7 @@ Library
         GHC.Parser.Types
         GHC.Platform
         GHC.Platform.ARM
-        GHC.Platform.ARM64
+        GHC.Platform.AArch64
         GHC.Platform.Constants
         GHC.Platform.NoRegs
         GHC.Platform.PPC


=====================================
config.sub
=====================================
@@ -1,8 +1,8 @@
 #! /bin/sh
 # Configuration validation subroutine script.
-#   Copyright 1992-2019 Free Software Foundation, Inc.
+#   Copyright 1992-2020 Free Software Foundation, Inc.
 
-timestamp='2019-01-05'
+timestamp='2020-09-08'
 
 # This file is free software; you can redistribute it and/or modify it
 # under the terms of the GNU General Public License as published by
@@ -67,7 +67,7 @@ Report bugs and patches to <config-patches at gnu.org>."
 version="\
 GNU config.sub ($timestamp)
 
-Copyright 1992-2019 Free Software Foundation, Inc.
+Copyright 1992-2020 Free Software Foundation, Inc.
 
 This is free software; see the source for copying conditions.  There is NO
 warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE."
@@ -124,28 +124,27 @@ case $1 in
 		;;
 	*-*-*-*)
 		basic_machine=$field1-$field2
-		os=$field3-$field4
+		basic_os=$field3-$field4
 		;;
 	*-*-*)
 		# Ambiguous whether COMPANY is present, or skipped and KERNEL-OS is two
 		# parts
 		maybe_os=$field2-$field3
 		case $maybe_os in
-			nto-qnx* | linux-gnu* | linux-android* | linux-dietlibc \
-			| linux-newlib* | linux-musl* | linux-uclibc* | uclinux-uclibc* \
+			nto-qnx* | linux-* | uclinux-uclibc* \
 			| uclinux-gnu* | kfreebsd*-gnu* | knetbsd*-gnu* | netbsd*-gnu* \
 			| netbsd*-eabi* | kopensolaris*-gnu* | cloudabi*-eabi* \
 			| storm-chaos* | os2-emx* | rtmk-nova*)
 				basic_machine=$field1
-				os=$maybe_os
+				basic_os=$maybe_os
 				;;
 			android-linux)
 				basic_machine=$field1-unknown
-				os=linux-android
+				basic_os=linux-android
 				;;
 			*)
 				basic_machine=$field1-$field2
-				os=$field3
+				basic_os=$field3
 				;;
 		esac
 		;;
@@ -154,7 +153,7 @@ case $1 in
 		case $field1-$field2 in
 			decstation-3100)
 				basic_machine=mips-dec
-				os=
+				basic_os=
 				;;
 			*-*)
 				# Second component is usually, but not always the OS
@@ -162,7 +161,7 @@ case $1 in
 					# Prevent following clause from handling this valid os
 					sun*os*)
 						basic_machine=$field1
-						os=$field2
+						basic_os=$field2
 						;;
 					# Manufacturers
 					dec* | mips* | sequent* | encore* | pc533* | sgi* | sony* \
@@ -175,11 +174,11 @@ case $1 in
 					| microblaze* | sim | cisco \
 					| oki | wec | wrs | winbond)
 						basic_machine=$field1-$field2
-						os=
+						basic_os=
 						;;
 					*)
 						basic_machine=$field1
-						os=$field2
+						basic_os=$field2
 						;;
 				esac
 			;;
@@ -191,450 +190,451 @@ case $1 in
 		case $field1 in
 			386bsd)
 				basic_machine=i386-pc
-				os=bsd
+				basic_os=bsd
 				;;
 			a29khif)
 				basic_machine=a29k-amd
-				os=udi
+				basic_os=udi
 				;;
 			adobe68k)
 				basic_machine=m68010-adobe
-				os=scout
+				basic_os=scout
 				;;
 			alliant)
 				basic_machine=fx80-alliant
-				os=
+				basic_os=
 				;;
 			altos | altos3068)
 				basic_machine=m68k-altos
-				os=
+				basic_os=
 				;;
 			am29k)
 				basic_machine=a29k-none
-				os=bsd
+				basic_os=bsd
 				;;
 			amdahl)
 				basic_machine=580-amdahl
-				os=sysv
+				basic_os=sysv
 				;;
 			amiga)
 				basic_machine=m68k-unknown
-				os=
+				basic_os=
 				;;
 			amigaos | amigados)
 				basic_machine=m68k-unknown
-				os=amigaos
+				basic_os=amigaos
 				;;
 			amigaunix | amix)
 				basic_machine=m68k-unknown
-				os=sysv4
+				basic_os=sysv4
 				;;
 			apollo68)
 				basic_machine=m68k-apollo
-				os=sysv
+				basic_os=sysv
 				;;
 			apollo68bsd)
 				basic_machine=m68k-apollo
-				os=bsd
+				basic_os=bsd
 				;;
 			aros)
 				basic_machine=i386-pc
-				os=aros
+				basic_os=aros
 				;;
 			aux)
 				basic_machine=m68k-apple
-				os=aux
+				basic_os=aux
 				;;
 			balance)
 				basic_machine=ns32k-sequent
-				os=dynix
+				basic_os=dynix
 				;;
 			blackfin)
 				basic_machine=bfin-unknown
-				os=linux
+				basic_os=linux
 				;;
 			cegcc)
 				basic_machine=arm-unknown
-				os=cegcc
+				basic_os=cegcc
 				;;
 			convex-c1)
 				basic_machine=c1-convex
-				os=bsd
+				basic_os=bsd
 				;;
 			convex-c2)
 				basic_machine=c2-convex
-				os=bsd
+				basic_os=bsd
 				;;
 			convex-c32)
 				basic_machine=c32-convex
-				os=bsd
+				basic_os=bsd
 				;;
 			convex-c34)
 				basic_machine=c34-convex
-				os=bsd
+				basic_os=bsd
 				;;
 			convex-c38)
 				basic_machine=c38-convex
-				os=bsd
+				basic_os=bsd
 				;;
 			cray)
 				basic_machine=j90-cray
-				os=unicos
+				basic_os=unicos
 				;;
 			crds | unos)
 				basic_machine=m68k-crds
-				os=
+				basic_os=
 				;;
 			da30)
 				basic_machine=m68k-da30
-				os=
+				basic_os=
 				;;
 			decstation | pmax | pmin | dec3100 | decstatn)
 				basic_machine=mips-dec
-				os=
+				basic_os=
 				;;
 			delta88)
 				basic_machine=m88k-motorola
-				os=sysv3
+				basic_os=sysv3
 				;;
 			dicos)
 				basic_machine=i686-pc
-				os=dicos
+				basic_os=dicos
 				;;
 			djgpp)
 				basic_machine=i586-pc
-				os=msdosdjgpp
+				basic_os=msdosdjgpp
 				;;
 			ebmon29k)
 				basic_machine=a29k-amd
-				os=ebmon
+				basic_os=ebmon
 				;;
 			es1800 | OSE68k | ose68k | ose | OSE)
 				basic_machine=m68k-ericsson
-				os=ose
+				basic_os=ose
 				;;
 			gmicro)
 				basic_machine=tron-gmicro
-				os=sysv
+				basic_os=sysv
 				;;
 			go32)
 				basic_machine=i386-pc
-				os=go32
+				basic_os=go32
 				;;
 			h8300hms)
 				basic_machine=h8300-hitachi
-				os=hms
+				basic_os=hms
 				;;
 			h8300xray)
 				basic_machine=h8300-hitachi
-				os=xray
+				basic_os=xray
 				;;
 			h8500hms)
 				basic_machine=h8500-hitachi
-				os=hms
+				basic_os=hms
 				;;
 			harris)
 				basic_machine=m88k-harris
-				os=sysv3
+				basic_os=sysv3
 				;;
-			hp300)
+			hp300 | hp300hpux)
 				basic_machine=m68k-hp
+				basic_os=hpux
 				;;
 			hp300bsd)
 				basic_machine=m68k-hp
-				os=bsd
-				;;
-			hp300hpux)
-				basic_machine=m68k-hp
-				os=hpux
+				basic_os=bsd
 				;;
 			hppaosf)
 				basic_machine=hppa1.1-hp
-				os=osf
+				basic_os=osf
 				;;
 			hppro)
 				basic_machine=hppa1.1-hp
-				os=proelf
+				basic_os=proelf
 				;;
 			i386mach)
 				basic_machine=i386-mach
-				os=mach
-				;;
-			vsta)
-				basic_machine=i386-pc
-				os=vsta
+				basic_os=mach
 				;;
 			isi68 | isi)
 				basic_machine=m68k-isi
-				os=sysv
+				basic_os=sysv
 				;;
 			m68knommu)
 				basic_machine=m68k-unknown
-				os=linux
+				basic_os=linux
 				;;
 			magnum | m3230)
 				basic_machine=mips-mips
-				os=sysv
+				basic_os=sysv
 				;;
 			merlin)
 				basic_machine=ns32k-utek
-				os=sysv
+				basic_os=sysv
 				;;
 			mingw64)
 				basic_machine=x86_64-pc
-				os=mingw64
+				basic_os=mingw64
 				;;
 			mingw32)
 				basic_machine=i686-pc
-				os=mingw32
+				basic_os=mingw32
 				;;
 			mingw32ce)
 				basic_machine=arm-unknown
-				os=mingw32ce
+				basic_os=mingw32ce
 				;;
 			monitor)
 				basic_machine=m68k-rom68k
-				os=coff
+				basic_os=coff
 				;;
 			morphos)
 				basic_machine=powerpc-unknown
-				os=morphos
+				basic_os=morphos
 				;;
 			moxiebox)
 				basic_machine=moxie-unknown
-				os=moxiebox
+				basic_os=moxiebox
 				;;
 			msdos)
 				basic_machine=i386-pc
-				os=msdos
+				basic_os=msdos
 				;;
 			msys)
 				basic_machine=i686-pc
-				os=msys
+				basic_os=msys
 				;;
 			mvs)
 				basic_machine=i370-ibm
-				os=mvs
+				basic_os=mvs
 				;;
 			nacl)
 				basic_machine=le32-unknown
-				os=nacl
+				basic_os=nacl
 				;;
 			ncr3000)
 				basic_machine=i486-ncr
-				os=sysv4
+				basic_os=sysv4
 				;;
 			netbsd386)
 				basic_machine=i386-pc
-				os=netbsd
+				basic_os=netbsd
 				;;
 			netwinder)
 				basic_machine=armv4l-rebel
-				os=linux
+				basic_os=linux
 				;;
 			news | news700 | news800 | news900)
 				basic_machine=m68k-sony
-				os=newsos
+				basic_os=newsos
 				;;
 			news1000)
 				basic_machine=m68030-sony
-				os=newsos
+				basic_os=newsos
 				;;
 			necv70)
 				basic_machine=v70-nec
-				os=sysv
+				basic_os=sysv
 				;;
 			nh3000)
 				basic_machine=m68k-harris
-				os=cxux
+				basic_os=cxux
 				;;
 			nh[45]000)
 				basic_machine=m88k-harris
-				os=cxux
+				basic_os=cxux
 				;;
 			nindy960)
 				basic_machine=i960-intel
-				os=nindy
+				basic_os=nindy
 				;;
 			mon960)
 				basic_machine=i960-intel
-				os=mon960
+				basic_os=mon960
 				;;
 			nonstopux)
 				basic_machine=mips-compaq
-				os=nonstopux
+				basic_os=nonstopux
 				;;
 			os400)
 				basic_machine=powerpc-ibm
-				os=os400
+				basic_os=os400
 				;;
 			OSE68000 | ose68000)
 				basic_machine=m68000-ericsson
-				os=ose
+				basic_os=ose
 				;;
 			os68k)
 				basic_machine=m68k-none
-				os=os68k
+				basic_os=os68k
 				;;
 			paragon)
 				basic_machine=i860-intel
-				os=osf
+				basic_os=osf
 				;;
 			parisc)
 				basic_machine=hppa-unknown
-				os=linux
+				basic_os=linux
+				;;
+			psp)
+				basic_machine=mipsallegrexel-sony
+				basic_os=psp
 				;;
 			pw32)
 				basic_machine=i586-unknown
-				os=pw32
+				basic_os=pw32
 				;;
 			rdos | rdos64)
 				basic_machine=x86_64-pc
-				os=rdos
+				basic_os=rdos
 				;;
 			rdos32)
 				basic_machine=i386-pc
-				os=rdos
+				basic_os=rdos
 				;;
 			rom68k)
 				basic_machine=m68k-rom68k
-				os=coff
+				basic_os=coff
 				;;
 			sa29200)
 				basic_machine=a29k-amd
-				os=udi
+				basic_os=udi
 				;;
 			sei)
 				basic_machine=mips-sei
-				os=seiux
+				basic_os=seiux
 				;;
 			sequent)
 				basic_machine=i386-sequent
-				os=
+				basic_os=
 				;;
 			sps7)
 				basic_machine=m68k-bull
-				os=sysv2
+				basic_os=sysv2
 				;;
 			st2000)
 				basic_machine=m68k-tandem
-				os=
+				basic_os=
 				;;
 			stratus)
 				basic_machine=i860-stratus
-				os=sysv4
+				basic_os=sysv4
 				;;
 			sun2)
 				basic_machine=m68000-sun
-				os=
+				basic_os=
 				;;
 			sun2os3)
 				basic_machine=m68000-sun
-				os=sunos3
+				basic_os=sunos3
 				;;
 			sun2os4)
 				basic_machine=m68000-sun
-				os=sunos4
+				basic_os=sunos4
 				;;
 			sun3)
 				basic_machine=m68k-sun
-				os=
+				basic_os=
 				;;
 			sun3os3)
 				basic_machine=m68k-sun
-				os=sunos3
+				basic_os=sunos3
 				;;
 			sun3os4)
 				basic_machine=m68k-sun
-				os=sunos4
+				basic_os=sunos4
 				;;
 			sun4)
 				basic_machine=sparc-sun
-				os=
+				basic_os=
 				;;
 			sun4os3)
 				basic_machine=sparc-sun
-				os=sunos3
+				basic_os=sunos3
 				;;
 			sun4os4)
 				basic_machine=sparc-sun
-				os=sunos4
+				basic_os=sunos4
 				;;
 			sun4sol2)
 				basic_machine=sparc-sun
-				os=solaris2
+				basic_os=solaris2
 				;;
 			sun386 | sun386i | roadrunner)
 				basic_machine=i386-sun
-				os=
+				basic_os=
 				;;
 			sv1)
 				basic_machine=sv1-cray
-				os=unicos
+				basic_os=unicos
 				;;
 			symmetry)
 				basic_machine=i386-sequent
-				os=dynix
+				basic_os=dynix
 				;;
 			t3e)
 				basic_machine=alphaev5-cray
-				os=unicos
+				basic_os=unicos
 				;;
 			t90)
 				basic_machine=t90-cray
-				os=unicos
+				basic_os=unicos
 				;;
 			toad1)
 				basic_machine=pdp10-xkl
-				os=tops20
+				basic_os=tops20
 				;;
 			tpf)
 				basic_machine=s390x-ibm
-				os=tpf
+				basic_os=tpf
 				;;
 			udi29k)
 				basic_machine=a29k-amd
-				os=udi
+				basic_os=udi
 				;;
 			ultra3)
 				basic_machine=a29k-nyu
-				os=sym1
+				basic_os=sym1
 				;;
 			v810 | necv810)
 				basic_machine=v810-nec
-				os=none
+				basic_os=none
 				;;
 			vaxv)
 				basic_machine=vax-dec
-				os=sysv
+				basic_os=sysv
 				;;
 			vms)
 				basic_machine=vax-dec
-				os=vms
+				basic_os=vms
+				;;
+			vsta)
+				basic_machine=i386-pc
+				basic_os=vsta
 				;;
 			vxworks960)
 				basic_machine=i960-wrs
-				os=vxworks
+				basic_os=vxworks
 				;;
 			vxworks68)
 				basic_machine=m68k-wrs
-				os=vxworks
+				basic_os=vxworks
 				;;
 			vxworks29k)
 				basic_machine=a29k-wrs
-				os=vxworks
+				basic_os=vxworks
 				;;
 			xbox)
 				basic_machine=i686-pc
-				os=mingw32
+				basic_os=mingw32
 				;;
 			ymp)
 				basic_machine=ymp-cray
-				os=unicos
+				basic_os=unicos
 				;;
 			*)
 				basic_machine=$1
-				os=
+				basic_os=
 				;;
 		esac
 		;;
@@ -686,17 +686,17 @@ case $basic_machine in
 	bluegene*)
 		cpu=powerpc
 		vendor=ibm
-		os=cnk
+		basic_os=cnk
 		;;
 	decsystem10* | dec10*)
 		cpu=pdp10
 		vendor=dec
-		os=tops10
+		basic_os=tops10
 		;;
 	decsystem20* | dec20*)
 		cpu=pdp10
 		vendor=dec
-		os=tops20
+		basic_os=tops20
 		;;
 	delta | 3300 | motorola-3300 | motorola-delta \
 	      | 3300-motorola | delta-motorola)
@@ -706,7 +706,7 @@ case $basic_machine in
 	dpx2*)
 		cpu=m68k
 		vendor=bull
-		os=sysv3
+		basic_os=sysv3
 		;;
 	encore | umax | mmax)
 		cpu=ns32k
@@ -715,7 +715,7 @@ case $basic_machine in
 	elxsi)
 		cpu=elxsi
 		vendor=elxsi
-		os=${os:-bsd}
+		basic_os=${basic_os:-bsd}
 		;;
 	fx2800)
 		cpu=i860
@@ -728,7 +728,7 @@ case $basic_machine in
 	h3050r* | hiux*)
 		cpu=hppa1.1
 		vendor=hitachi
-		os=hiuxwe2
+		basic_os=hiuxwe2
 		;;
 	hp3k9[0-9][0-9] | hp9[0-9][0-9])
 		cpu=hppa1.0
@@ -771,36 +771,36 @@ case $basic_machine in
 	i*86v32)
 		cpu=`echo "$1" | sed -e 's/86.*/86/'`
 		vendor=pc
-		os=sysv32
+		basic_os=sysv32
 		;;
 	i*86v4*)
 		cpu=`echo "$1" | sed -e 's/86.*/86/'`
 		vendor=pc
-		os=sysv4
+		basic_os=sysv4
 		;;
 	i*86v)
 		cpu=`echo "$1" | sed -e 's/86.*/86/'`
 		vendor=pc
-		os=sysv
+		basic_os=sysv
 		;;
 	i*86sol2)
 		cpu=`echo "$1" | sed -e 's/86.*/86/'`
 		vendor=pc
-		os=solaris2
+		basic_os=solaris2
 		;;
 	j90 | j90-cray)
 		cpu=j90
 		vendor=cray
-		os=${os:-unicos}
+		basic_os=${basic_os:-unicos}
 		;;
 	iris | iris4d)
 		cpu=mips
 		vendor=sgi
-		case $os in
+		case $basic_os in
 		    irix*)
 			;;
 		    *)
-			os=irix4
+			basic_os=irix4
 			;;
 		esac
 		;;
@@ -811,26 +811,26 @@ case $basic_machine in
 	*mint | mint[0-9]* | *MiNT | *MiNT[0-9]*)
 		cpu=m68k
 		vendor=atari
-		os=mint
+		basic_os=mint
 		;;
 	news-3600 | risc-news)
 		cpu=mips
 		vendor=sony
-		os=newsos
+		basic_os=newsos
 		;;
 	next | m*-next)
 		cpu=m68k
 		vendor=next
-		case $os in
+		case $basic_os in
 		    openstep*)
 		        ;;
 		    nextstep*)
 			;;
 		    ns2*)
-		      os=nextstep2
+		      basic_os=nextstep2
 			;;
 		    *)
-		      os=nextstep3
+		      basic_os=nextstep3
 			;;
 		esac
 		;;
@@ -841,12 +841,12 @@ case $basic_machine in
 	op50n-* | op60c-*)
 		cpu=hppa1.1
 		vendor=oki
-		os=proelf
+		basic_os=proelf
 		;;
 	pa-hitachi)
 		cpu=hppa1.1
 		vendor=hitachi
-		os=hiuxwe2
+		basic_os=hiuxwe2
 		;;
 	pbd)
 		cpu=sparc
@@ -883,12 +883,12 @@ case $basic_machine in
 	sde)
 		cpu=mipsisa32
 		vendor=sde
-		os=${os:-elf}
+		basic_os=${basic_os:-elf}
 		;;
 	simso-wrs)
 		cpu=sparclite
 		vendor=wrs
-		os=vxworks
+		basic_os=vxworks
 		;;
 	tower | tower-32)
 		cpu=m68k
@@ -905,7 +905,7 @@ case $basic_machine in
 	w89k-*)
 		cpu=hppa1.1
 		vendor=winbond
-		os=proelf
+		basic_os=proelf
 		;;
 	none)
 		cpu=none
@@ -958,11 +958,11 @@ case $cpu-$vendor in
 	# some cases the only manufacturer, in others, it is the most popular.
 	craynv-unknown)
 		vendor=cray
-		os=${os:-unicosmp}
+		basic_os=${basic_os:-unicosmp}
 		;;
 	c90-unknown | c90-cray)
 		vendor=cray
-		os=${os:-unicos}
+		basic_os=${Basic_os:-unicos}
 		;;
 	fx80-unknown)
 		vendor=alliant
@@ -1006,7 +1006,7 @@ case $cpu-$vendor in
 	dpx20-unknown | dpx20-bull)
 		cpu=rs6000
 		vendor=bull
-		os=${os:-bosx}
+		basic_os=${basic_os:-bosx}
 		;;
 
 	# Here we normalize CPU types irrespective of the vendor
@@ -1015,7 +1015,7 @@ case $cpu-$vendor in
 		;;
 	blackfin-*)
 		cpu=bfin
-		os=linux
+		basic_os=linux
 		;;
 	c54x-*)
 		cpu=tic54x
@@ -1028,7 +1028,7 @@ case $cpu-$vendor in
 		;;
 	e500v[12]-*)
 		cpu=powerpc
-		os=$os"spe"
+		basic_os=${basic_os}"spe"
 		;;
 	mips3*-*)
 		cpu=mips64
@@ -1038,7 +1038,7 @@ case $cpu-$vendor in
 		;;
 	m68knommu-*)
 		cpu=m68k
-		os=linux
+		basic_os=linux
 		;;
 	m9s12z-* | m68hcs12z-* | hcs12z-* | s12z-*)
 		cpu=s12z
@@ -1048,7 +1048,7 @@ case $cpu-$vendor in
 		;;
 	parisc-*)
 		cpu=hppa
-		os=linux
+		basic_os=linux
 		;;
 	pentium-* | p5-* | k5-* | k6-* | nexgen-* | viac3-*)
 		cpu=i586
@@ -1104,11 +1104,14 @@ case $cpu-$vendor in
 	xscale-* | xscalee[bl]-*)
 		cpu=`echo "$cpu" | sed 's/^xscale/arm/'`
 		;;
+	arm64-*)
+		cpu=aarch64
+		;;
 
 	# Recognize the canonical CPU Types that limit and/or modify the
 	# company names they are paired with.
 	cr16-*)
-		os=${os:-elf}
+		basic_os=${basic_os:-elf}
 		;;
 	crisv32-* | etraxfs*-*)
 		cpu=crisv32
@@ -1119,7 +1122,7 @@ case $cpu-$vendor in
 		vendor=axis
 		;;
 	crx-*)
-		os=${os:-elf}
+		basic_os=${basic_os:-elf}
 		;;
 	neo-tandem)
 		cpu=neo
@@ -1141,16 +1144,12 @@ case $cpu-$vendor in
 		cpu=nsx
 		vendor=tandem
 		;;
-	s390-*)
-		cpu=s390
-		vendor=ibm
-		;;
-	s390x-*)
-		cpu=s390x
-		vendor=ibm
+	mipsallegrexel-sony)
+		cpu=mipsallegrexel
+		vendor=sony
 		;;
 	tile*-*)
-		os=${os:-linux-gnu}
+		basic_os=${basic_os:-linux-gnu}
 		;;
 
 	*)
@@ -1167,12 +1166,12 @@ case $cpu-$vendor in
 			| am33_2.0 \
 			| amdgcn \
 			| arc | arceb \
-			| arm  | arm[lb]e | arme[lb] | armv* \
+			| arm | arm[lb]e | arme[lb] | armv* \
 			| avr | avr32 \
 			| asmjs \
 			| ba \
 			| be32 | be64 \
-			| bfin | bs2000 \
+			| bfin | bpf | bs2000 \
 			| c[123]* | c30 | [cjt]90 | c4x \
 			| c8051 | clipper | craynv | csky | cydra \
 			| d10v | d30v | dlx | dsp16xx \
@@ -1232,6 +1231,7 @@ case $cpu-$vendor in
 			| pyramid \
 			| riscv | riscv32 | riscv64 \
 			| rl78 | romp | rs6000 | rx \
+			| s390 | s390x \
 			| score \
 			| sh | shl \
 			| sh[1234] | sh[24]a | sh[24]ae[lb] | sh[23]e | she[lb] | sh[lb]e \
@@ -1278,8 +1278,43 @@ esac
 
 # Decode manufacturer-specific aliases for certain operating systems.
 
-if [ x$os != x ]
+if test x$basic_os != x
 then
+
+# First recognize some ad-hoc caes, or perhaps split kernel-os, or else just
+# set os.
+case $basic_os in
+	gnu/linux*)
+		kernel=linux
+		os=`echo $basic_os | sed -e 's|gnu/linux|gnu|'`
+		;;
+	nto-qnx*)
+		kernel=nto
+		os=`echo $basic_os | sed -e 's|nto-qnx|qnx|'`
+		;;
+	*-*)
+		# shellcheck disable=SC2162
+		IFS="-" read kernel os <<EOF
+$basic_os
+EOF
+		;;
+	# Default OS when just kernel was specified
+	nto*)
+		kernel=nto
+		os=`echo $basic_os | sed -e 's|nto|qnx|'`
+		;;
+	linux*)
+		kernel=linux
+		os=`echo $basic_os | sed -e 's|linux|gnu|'`
+		;;
+	*)
+		kernel=
+		os=$basic_os
+		;;
+esac
+
+# Now, normalize the OS (knowing we just have one component, it's not a kernel,
+# etc.)
 case $os in
 	# First match some system type aliases that might get confused
 	# with valid system types.
@@ -1299,9 +1334,6 @@ case $os in
 	unixware*)
 		os=sysv4.2uw
 		;;
-	gnu/linux*)
-		os=`echo $os | sed -e 's|gnu/linux|linux-gnu|'`
-		;;
 	# es1800 is here to avoid being matched by es* (a different OS)
 	es1800*)
 		os=ose
@@ -1325,10 +1357,7 @@ case $os in
 	sco3.2.[4-9]*)
 		os=`echo $os | sed -e 's/sco3.2./sco3.2v/'`
 		;;
-	sco3.2v[4-9]* | sco5v6*)
-		# Don't forget version if it is 3.2v4 or newer.
-		;;
-	scout)
+	sco*v* | scout)
 		# Don't match below
 		;;
 	sco*)
@@ -1337,77 +1366,25 @@ case $os in
 	psos*)
 		os=psos
 		;;
-	# Now accept the basic system types.
-	# The portable systems comes first.
-	# Each alternative MUST end in a * to match a version number.
-	# sysv* is not here because it comes later, after sysvr4.
-	gnu* | bsd* | mach* | minix* | genix* | ultrix* | irix* \
-	     | *vms* | esix* | aix* | cnk* | sunos | sunos[34]*\
-	     | hpux* | unos* | osf* | luna* | dgux* | auroraux* | solaris* \
-	     | sym* | kopensolaris* | plan9* \
-	     | amigaos* | amigados* | msdos* | newsos* | unicos* | aof* \
-	     | aos* | aros* | cloudabi* | sortix* \
-	     | nindy* | vxsim* | vxworks* | ebmon* | hms* | mvs* \
-	     | clix* | riscos* | uniplus* | iris* | isc* | rtu* | xenix* \
-	     | knetbsd* | mirbsd* | netbsd* \
-	     | bitrig* | openbsd* | solidbsd* | libertybsd* \
-	     | ekkobsd* | kfreebsd* | freebsd* | riscix* | lynxos* \
-	     | bosx* | nextstep* | cxux* | aout* | elf* | oabi* \
-	     | ptx* | coff* | ecoff* | winnt* | domain* | vsta* \
-	     | udi* | eabi* | lites* | ieee* | go32* | aux* | hcos* \
-	     | chorusrdb* | cegcc* | glidix* \
-	     | cygwin* | msys* | pe* | moss* | proelf* | rtems* \
-	     | midipix* | mingw32* | mingw64* | linux-gnu* | linux-android* \
-	     | linux-newlib* | linux-musl* | linux-uclibc* \
-	     | uxpv* | beos* | mpeix* | udk* | moxiebox* \
-	     | interix* | uwin* | mks* | rhapsody* | darwin* \
-	     | openstep* | oskit* | conix* | pw32* | nonstopux* \
-	     | storm-chaos* | tops10* | tenex* | tops20* | its* \
-	     | os2* | vos* | palmos* | uclinux* | nucleus* \
-	     | morphos* | superux* | rtmk* | windiss* \
-	     | powermax* | dnix* | nx6 | nx7 | sei* | dragonfly* \
-	     | skyos* | haiku* | rdos* | toppers* | drops* | es* \
-	     | onefs* | tirtos* | phoenix* | fuchsia* | redox* | bme* \
-	     | midnightbsd* | amdhsa* | unleashed* | emscripten* | wasi*)
-	# Remember, each alternative MUST END IN *, to match a version number.
-		;;
 	qnx*)
-		case $cpu in
-		    x86 | i*86)
-			;;
-		    *)
-			os=nto-$os
-			;;
-		esac
+		os=qnx
 		;;
 	hiux*)
 		os=hiuxwe2
 		;;
-	nto-qnx*)
-		;;
-	nto*)
-		os=`echo $os | sed -e 's|nto|nto-qnx|'`
-		;;
-	sim | xray | os68k* | v88r* \
-	    | windows* | osx | abug | netware* | os9* \
-	    | macos* | mpw* | magic* | mmixware* | mon960* | lnews*)
-		;;
-	linux-dietlibc)
-		os=linux-dietlibc
-		;;
-	linux*)
-		os=`echo $os | sed -e 's|linux|linux-gnu|'`
-		;;
 	lynx*178)
 		os=lynxos178
 		;;
 	lynx*5)
 		os=lynxos5
 		;;
+	lynxos*)
+		# don't get caught up in next wildcard
+		;;
 	lynx*)
 		os=lynxos
 		;;
-	mac*)
+	mac[0-9]*)
 		os=`echo "$os" | sed -e 's|mac|macos|'`
 		;;
 	opened*)
@@ -1452,9 +1429,6 @@ case $os in
 	ns2)
 		os=nextstep2
 		;;
-	nsk*)
-		os=nsk
-		;;
 	# Preserve the version number of sinix5.
 	sinix5.*)
 		os=`echo $os | sed -e 's|sinix|sysv|'`
@@ -1480,18 +1454,12 @@ case $os in
 	sysvr4)
 		os=sysv4
 		;;
-	# This must come after sysvr4.
-	sysv*)
-		;;
 	ose*)
 		os=ose
 		;;
 	*mint | mint[0-9]* | *MiNT | MiNT[0-9]*)
 		os=mint
 		;;
-	zvmoe)
-		os=zvmoe
-		;;
 	dicos*)
 		os=dicos
 		;;
@@ -1508,19 +1476,11 @@ case $os in
 			;;
 		esac
 		;;
-	nacl*)
-		;;
-	ios)
-		;;
-	none)
-		;;
-	*-eabi)
-		;;
 	*)
-		echo Invalid configuration \`"$1"\': system \`"$os"\' not recognized 1>&2
-		exit 1
+		# No normalization, but not necessarily accepted, that comes below.
 		;;
 esac
+
 else
 
 # Here we handle the default operating systems that come with various machines.
@@ -1533,6 +1493,7 @@ else
 # will signal an error saying that MANUFACTURER isn't an operating
 # system, and we'll never get to this point.
 
+kernel=
 case $cpu-$vendor in
 	score-*)
 		os=elf
@@ -1544,7 +1505,8 @@ case $cpu-$vendor in
 		os=riscix1.2
 		;;
 	arm*-rebel)
-		os=linux
+		kernel=linux
+		os=gnu
 		;;
 	arm*-semi)
 		os=aout
@@ -1710,84 +1672,169 @@ case $cpu-$vendor in
 		os=none
 		;;
 esac
+
 fi
 
+# Now, validate our (potentially fixed-up) OS.
+case $os in
+	# Sometimes we do "kernel-abi", so those need to count as OSes.
+	musl* | newlib* | uclibc*)
+		;;
+	# Likewise for "kernel-libc"
+	eabi | eabihf | gnueabi | gnueabihf)
+		;;
+	# Now accept the basic system types.
+	# The portable systems comes first.
+	# Each alternative MUST end in a * to match a version number.
+	gnu* | android* | bsd* | mach* | minix* | genix* | ultrix* | irix* \
+	     | *vms* | esix* | aix* | cnk* | sunos | sunos[34]* \
+	     | hpux* | unos* | osf* | luna* | dgux* | auroraux* | solaris* \
+	     | sym* |  plan9* | psp* | sim* | xray* | os68k* | v88r* \
+	     | hiux* | abug | nacl* | netware* | windows* \
+	     | os9* | macos* | osx* | ios* \
+	     | mpw* | magic* | mmixware* | mon960* | lnews* \
+	     | amigaos* | amigados* | msdos* | newsos* | unicos* | aof* \
+	     | aos* | aros* | cloudabi* | sortix* | twizzler* \
+	     | nindy* | vxsim* | vxworks* | ebmon* | hms* | mvs* \
+	     | clix* | riscos* | uniplus* | iris* | isc* | rtu* | xenix* \
+	     | mirbsd* | netbsd* | dicos* | openedition* | ose* \
+	     | bitrig* | openbsd* | solidbsd* | libertybsd* | os108* \
+	     | ekkobsd* | freebsd* | riscix* | lynxos* | os400* \
+	     | bosx* | nextstep* | cxux* | aout* | elf* | oabi* \
+	     | ptx* | coff* | ecoff* | winnt* | domain* | vsta* \
+	     | udi* | lites* | ieee* | go32* | aux* | hcos* \
+	     | chorusrdb* | cegcc* | glidix* \
+	     | cygwin* | msys* | pe* | moss* | proelf* | rtems* \
+	     | midipix* | mingw32* | mingw64* | mint* \
+	     | uxpv* | beos* | mpeix* | udk* | moxiebox* \
+	     | interix* | uwin* | mks* | rhapsody* | darwin* \
+	     | openstep* | oskit* | conix* | pw32* | nonstopux* \
+	     | storm-chaos* | tops10* | tenex* | tops20* | its* \
+	     | os2* | vos* | palmos* | uclinux* | nucleus* | morphos* \
+	     | scout* | superux* | sysv* | rtmk* | tpf* | windiss* \
+	     | powermax* | dnix* | nx6 | nx7 | sei* | dragonfly* \
+	     | skyos* | haiku* | rdos* | toppers* | drops* | es* \
+	     | onefs* | tirtos* | phoenix* | fuchsia* | redox* | bme* \
+	     | midnightbsd* | amdhsa* | unleashed* | emscripten* | wasi* \
+	     | nsk* | powerunix* | genode* | zvmoe* | qnx* )
+		;;
+	# This one is extra strict with allowed versions
+	sco3.2v2 | sco3.2v[4-9]* | sco5v6*)
+		# Don't forget version if it is 3.2v4 or newer.
+		;;
+	none)
+		;;
+	*)
+		echo Invalid configuration \`"$1"\': OS \`"$os"\' not recognized 1>&2
+		exit 1
+		;;
+esac
+
+# As a final step for OS-related things, validate the OS-kernel combination
+# (given a valid OS), if there is a kernel.
+case $kernel-$os in
+	linux-gnu* | linux-dietlibc* | linux-android* | linux-newlib* | linux-musl* | linux-uclibc* )
+		;;
+	-dietlibc* | -newlib* | -musl* | -uclibc* )
+		# These are just libc implementations, not actual OSes, and thus
+		# require a kernel.
+		echo "Invalid configuration \`$1': libc \`$os' needs explicit kernel." 1>&2
+		exit 1
+		;;
+	kfreebsd*-gnu* | kopensolaris*-gnu*)
+		;;
+	nto-qnx*)
+		;;
+	*-eabi* | *-gnueabi*)
+		;;
+	-*)
+		# Blank kernel with real OS is always fine.
+		;;
+	*-*)
+		echo "Invalid configuration \`$1': Kernel \`$kernel' not known to work with OS \`$os'." 1>&2
+		exit 1
+		;;
+esac
+
 # Here we handle the case where we know the os, and the CPU type, but not the
 # manufacturer.  We pick the logical manufacturer.
 case $vendor in
 	unknown)
-		case $os in
-			riscix*)
+		case $cpu-$os in
+			*-riscix*)
 				vendor=acorn
 				;;
-			sunos*)
+			*-sunos*)
 				vendor=sun
 				;;
-			cnk*|-aix*)
+			*-cnk* | *-aix*)
 				vendor=ibm
 				;;
-			beos*)
+			*-beos*)
 				vendor=be
 				;;
-			hpux*)
+			*-hpux*)
 				vendor=hp
 				;;
-			mpeix*)
+			*-mpeix*)
 				vendor=hp
 				;;
-			hiux*)
+			*-hiux*)
 				vendor=hitachi
 				;;
-			unos*)
+			*-unos*)
 				vendor=crds
 				;;
-			dgux*)
+			*-dgux*)
 				vendor=dg
 				;;
-			luna*)
+			*-luna*)
 				vendor=omron
 				;;
-			genix*)
+			*-genix*)
 				vendor=ns
 				;;
-			clix*)
+			*-clix*)
 				vendor=intergraph
 				;;
-			mvs* | opened*)
+			*-mvs* | *-opened*)
+				vendor=ibm
+				;;
+			*-os400*)
 				vendor=ibm
 				;;
-			os400*)
+			s390-* | s390x-*)
 				vendor=ibm
 				;;
-			ptx*)
+			*-ptx*)
 				vendor=sequent
 				;;
-			tpf*)
+			*-tpf*)
 				vendor=ibm
 				;;
-			vxsim* | vxworks* | windiss*)
+			*-vxsim* | *-vxworks* | *-windiss*)
 				vendor=wrs
 				;;
-			aux*)
+			*-aux*)
 				vendor=apple
 				;;
-			hms*)
+			*-hms*)
 				vendor=hitachi
 				;;
-			mpw* | macos*)
+			*-mpw* | *-macos*)
 				vendor=apple
 				;;
-			*mint | mint[0-9]* | *MiNT | MiNT[0-9]*)
+			*-*mint | *-mint[0-9]* | *-*MiNT | *-MiNT[0-9]*)
 				vendor=atari
 				;;
-			vos*)
+			*-vos*)
 				vendor=stratus
 				;;
 		esac
 		;;
 esac
 
-echo "$cpu-$vendor-$os"
+echo "$cpu-$vendor-${kernel:+$kernel-}$os"
 exit
 
 # Local variables:


=====================================
includes/CodeGen.Platform.hs
=====================================
@@ -94,7 +94,7 @@ import GHC.Platform.Reg
 # define zmm14 30
 # define zmm15 31
 
--- Note: these are only needed for ARM/ARM64 because globalRegMaybe is now used in CmmSink.hs.
+-- Note: these are only needed for ARM/AArch64 because globalRegMaybe is now used in CmmSink.hs.
 -- Since it's only used to check 'isJust', the actual values don't matter, thus
 -- I'm not sure if these are the correct numberings.
 -- Normally, the register names are just stringified as part of the REG() macro
@@ -1096,4 +1096,3 @@ freeReg _ = True
 freeReg = panic "freeReg not defined for this platform"
 
 #endif
-


=====================================
includes/rts/Flags.h
=====================================
@@ -199,6 +199,8 @@ typedef struct _CONCURRENT_FLAGS {
  * When linkerAlwaysPic is true, the runtime linker assume that all object
  * files were compiled with -fPIC -fexternal-dynamic-refs and load them
  * anywhere in the address space.
+ * Note that there is no 32bit darwin system we can realistically expect to
+ * run on or compile for.
  */
 #if defined(darwin_HOST_OS) || defined(aarch64_HOST_ARCH)
 #define DEFAULT_LINKER_ALWAYS_PIC true


=====================================
includes/rts/storage/GC.h
=====================================
@@ -202,7 +202,7 @@ typedef void* AdjustorExecutable;
 
 AdjustorWritable allocateExec(W_ len, AdjustorExecutable *exec_addr);
 void flushExec(W_ len, AdjustorExecutable exec_addr);
-#if defined(ios_HOST_OS)
+#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS))
 AdjustorWritable execToWritable(AdjustorExecutable exec);
 #endif
 void             freeExec (AdjustorExecutable p);


=====================================
libraries/ghc-boot/GHC/Platform/ArchOS.hs
=====================================
@@ -41,7 +41,7 @@ data Arch
    | ArchSPARC
    | ArchSPARC64
    | ArchARM ArmISA [ArmISAExt] ArmABI
-   | ArchARM64
+   | ArchAArch64
    | ArchAlpha
    | ArchMipseb
    | ArchMipsel
@@ -130,7 +130,7 @@ stringEncodeArch = \case
   ArchARM ARMv5 _ _ -> "armv5"
   ArchARM ARMv6 _ _ -> "armv6"
   ArchARM ARMv7 _ _ -> "armv7"
-  ArchARM64         -> "aarch64"
+  ArchAArch64       -> "aarch64"
   ArchAlpha         -> "alpha"
   ArchMipseb        -> "mipseb"
   ArchMipsel        -> "mipsel"


=====================================
libraries/ghci/GHCi/InfoTable.hsc
=====================================
@@ -69,7 +69,7 @@ data Arch = ArchSPARC
           | ArchX86_64
           | ArchAlpha
           | ArchARM
-          | ArchARM64
+          | ArchAArch64
           | ArchPPC64
           | ArchPPC64LE
           | ArchS390X
@@ -102,7 +102,7 @@ mArch =
 #elif defined(arm_HOST_ARCH)
        Just ArchARM
 #elif defined(aarch64_HOST_ARCH)
-       Just ArchARM64
+       Just ArchAArch64
 #elif defined(powerpc64_HOST_ARCH)
        Just ArchPPC64
 #elif defined(powerpc64le_HOST_ARCH)
@@ -214,7 +214,7 @@ mkJumpToAddr' platform a = case platform of
                 , 0x11, 0xff, 0x2f, 0xe1
                 , byte0 w32, byte1 w32, byte2 w32, byte3 w32]
 
-    ArchARM64 { } ->
+    ArchAArch64 { } ->
         -- Generates:
         --
         --      ldr     x1, label


=====================================
llvm-targets
=====================================
@@ -1,7 +1,7 @@
-[("i386-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", ""))
-,("i686-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", ""))
-,("x86_64-unknown-windows", ("e-m:w-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
-,("arm-unknown-linux-gnueabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+soft-float -fp16 -vfp2 -vfp2sp -vfp2d16 -vfp2d16sp -vfp3 -vfp3sp -vfp3d16 -vfp3d16sp -vfp4 -vfp4sp -vfp4d16 -vfp4d16sp -fp-armv8 -fp-armv8sp -fp-armv8d16 -fp-armv8d16sp -fullfp16 -neon -crypto -dotprod -fp16fml -fp64 -d32 -fpregs +strict-align"))
+[("i386-unknown-windows", ("e-m:x-p:32:32-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", ""))
+,("i686-unknown-windows", ("e-m:x-p:32:32-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", ""))
+,("x86_64-unknown-windows", ("e-m:w-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
+,("arm-unknown-linux-gnueabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+strict-align"))
 ,("arm-unknown-linux-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align"))
 ,("arm-unknown-linux-musleabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align"))
 ,("armv6-unknown-linux-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1136jf-s", "+strict-align"))
@@ -21,31 +21,32 @@
 ,("aarch64-unknown-linux-gnu", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon"))
 ,("aarch64-unknown-linux-musl", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon"))
 ,("aarch64-unknown-linux", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon"))
-,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
-,("i386-unknown-linux-musl", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
-,("i386-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
-,("i686-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
-,("i686-unknown-linux-musl", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
-,("i686-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
-,("x86_64-unknown-linux-gnu", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
-,("x86_64-unknown-linux-musl", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
-,("x86_64-unknown-linux", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
-,("x86_64-unknown-linux-android", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt +cx16"))
-,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2d16 +vfp2d16sp +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml"))
+,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
+,("i386-unknown-linux-musl", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
+,("i386-unknown-linux", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
+,("i686-unknown-linux-gnu", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
+,("i686-unknown-linux-musl", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
+,("i686-unknown-linux", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
+,("x86_64-unknown-linux-gnu", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
+,("x86_64-unknown-linux-musl", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
+,("x86_64-unknown-linux", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
+,("x86_64-unknown-linux-android", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt +cx16"))
+,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml"))
 ,("aarch64-unknown-linux-android", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon"))
-,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2d16 +vfp2d16sp +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml"))
+,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml"))
 ,("powerpc64le-unknown-linux-gnu", ("e-m:e-i64:64-n32:64", "ppc64le", ""))
 ,("powerpc64le-unknown-linux-musl", ("e-m:e-i64:64-n32:64", "ppc64le", "+secure-plt"))
 ,("powerpc64le-unknown-linux", ("e-m:e-i64:64-n32:64", "ppc64le", ""))
 ,("s390x-ibm-linux", ("E-m:e-i1:8:16-i8:8:16-i64:64-f128:64-a:8:16-n32:64", "z10", ""))
-,("i386-apple-darwin", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", ""))
-,("x86_64-apple-darwin", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", ""))
-,("armv7-apple-ios", ("e-m:o-p:32:32-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", ""))
-,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+neon"))
-,("i386-apple-ios", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", ""))
-,("x86_64-apple-ios", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", ""))
-,("amd64-portbld-freebsd", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
-,("x86_64-unknown-freebsd", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
+,("i386-apple-darwin", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "penryn", ""))
+,("x86_64-apple-darwin", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "penryn", ""))
+,("arm64-apple-darwin", ("e-m:o-i64:64-i128:128-n32:64-S128", "vortex", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes"))
+,("armv7-apple-ios", ("e-m:o-p:32:32-Fi8-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", ""))
+,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "apple-a7", "+fp-armv8 +neon +crypto +zcm +zcz +sha2 +aes"))
+,("i386-apple-ios", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "yonah", ""))
+,("x86_64-apple-ios", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "core2", ""))
+,("amd64-portbld-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
+,("x86_64-unknown-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
 ,("aarch64-unknown-freebsd", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon"))
 ,("armv6-unknown-freebsd-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align"))
 ,("armv7-unknown-freebsd-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+strict-align"))


=====================================
rts/Adjustor.c
=====================================
@@ -99,7 +99,7 @@ freeHaskellFunctionPtr(void* ptr)
 {
     ffi_closure *cl;
 
-#if defined(ios_HOST_OS)
+#if defined(ios_HOST_OS) || defined(darwin_HOST_OS)
     cl = execToWritable(ptr);
 #else
     cl = (ffi_closure*)ptr;


=====================================
rts/StgCRun.c
=====================================
@@ -932,7 +932,7 @@ StgRun(StgFunPtr f, StgRegTable *basereg) {
         "br %1\n\t"
 
         ".globl " STG_RETURN "\n\t"
-#if !defined(ios_HOST_OS)
+#if !defined(ios_HOST_OS) && !defined(darwin_HOST_OS)
         ".type " STG_RETURN ", %%function\n"
 #endif
         STG_RETURN ":\n\t"
@@ -941,7 +941,7 @@ StgRun(StgFunPtr f, StgRegTable *basereg) {
          */
         "add sp, sp, %3\n\t"
         /*
-         * Return the new register table, taking it from Stg's R1 (ARM64's R22).
+         * Return the new register table, taking it from Stg's R1 (AArch64's R22).
          */
         "mov %0, x22\n\t"
         /*


=====================================
rts/linker/elf_plt_aarch64.c
=====================================
@@ -46,8 +46,8 @@ bool needStubForRelaAarch64(Elf_Rela * rela) {
 bool
 makeStubAarch64(Stub * s) {
     // We (the linker) may corrupt registers x16 (IP0) and x17 (IP1) [AAPCS64]
-    // and the condition flags, according to the "ELF for the ARM64
-    // Architecture".
+    // and the condition flags, according to the "ELF for the ARM 64-bit
+    // Architecture (AArch64)".
     //
     // [Special purpose regs]
     // X16 and X17 are IP0 and IP1, intra-procedure-call temporary registers.


=====================================
rts/linker/elf_reloc.c
=====================================
@@ -4,7 +4,7 @@
 
 #if defined(OBJFORMAT_ELF)
 
-/* we currently only use this abstraction for elf/arm64 */
+/* we currently only use this abstraction for elf/aarch64 */
 #if defined(aarch64_HOST_ARCH)
 
 bool


=====================================
rts/package.conf.in
=====================================
@@ -318,7 +318,7 @@ ld-options:
          , "-Wl,-search_paths_first"
 #endif
 
-#if defined(darwin_HOST_OS) && !defined(x86_64_HOST_ARCH)
+#if defined(darwin_HOST_OS) && !defined(x86_64_HOST_ARCH) && !defined(aarch64_HOST_ARCH)
          , "-read_only_relocs", "warning"
 #endif
 


=====================================
rts/rts.cabal.in
=====================================
@@ -398,7 +398,7 @@ library
 
     if os(osx)
       ld-options: "-Wl,-search_paths_first"
-      if !arch(x86_64)
+      if !arch(x86_64) && !arch(aarch64)
          ld-options: -read_only_relocs warning
 
     cmm-sources: Apply.cmm


=====================================
rts/sm/Storage.c
=====================================
@@ -30,7 +30,7 @@
 #include "GC.h"
 #include "Evac.h"
 #include "NonMoving.h"
-#if defined(ios_HOST_OS)
+#if defined(ios_HOST_OS) || defined(darwin_HOST_OS)
 #include "Hash.h"
 #endif
 
@@ -1648,7 +1648,7 @@ StgWord calcTotalCompactW (void)
          should be modified to use allocateExec instead of VirtualAlloc.
    ------------------------------------------------------------------------- */
 
-#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS)
+#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS))
 #include <libkern/OSCacheControl.h>
 #endif
 
@@ -1679,7 +1679,7 @@ void flushExec (W_ len, AdjustorExecutable exec_addr)
   /* x86 doesn't need to do anything, so just suppress some warnings. */
   (void)len;
   (void)exec_addr;
-#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS)
+#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS))
   /* On iOS we need to use the special 'sys_icache_invalidate' call. */
   sys_icache_invalidate(exec_addr, len);
 #elif defined(__clang__)
@@ -1734,7 +1734,7 @@ void freeExec (AdjustorExecutable addr)
     RELEASE_SM_LOCK
 }
 
-#elif defined(ios_HOST_OS)
+#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS))
 
 static HashTable* allocatedExecs;
 


=====================================
utils/llvm-targets/gen-data-layout.sh
=====================================
@@ -84,9 +84,12 @@ TARGETS=(
     # macOS
     "i386-apple-darwin"
     "x86_64-apple-darwin"
+    "arm64-apple-darwin"
     # iOS
-    "armv7-apple-ios arm64-apple-ios"
-    "i386-apple-ios x86_64-apple-ios"
+    "armv7-apple-ios"
+    "arm64-apple-ios"
+    "i386-apple-ios"
+    "x86_64-apple-ios"
 
     #########################
     # FreeBSD



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8887102fc4ed8ed1089c1aafd19bab424ad706f3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8887102fc4ed8ed1089c1aafd19bab424ad706f3
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/20201115/01d93cf3/attachment-0001.html>


More information about the ghc-commits mailing list