Skip to content
Snippets Groups Projects
Commit ea25088d authored by lrzlin's avatar lrzlin Committed by Marge Bot
Browse files

Add initial support for LoongArch Architecture.

parent d122e022
No related branches found
No related tags found
No related merge requests found
Showing
with 121 additions and 6 deletions
...@@ -377,6 +377,74 @@ import GHC.Platform.Reg ...@@ -377,6 +377,74 @@ import GHC.Platform.Reg
# define ft10 62 # define ft10 62
# define ft11 63 # define ft11 63
#elif defined(MACHREGS_loongarch64)
# define zero 0
# define ra 1
# define tp 2
# define sp 3
# define a0 4
# define a1 5
# define a2 6
# define a3 7
# define a4 8
# define a5 9
# define a6 10
# define a7 11
# define t0 12
# define t1 13
# define t2 14
# define t3 15
# define t4 16
# define t5 17
# define t6 18
# define t7 19
# define t8 20
# define u0 21
# define fp 22
# define s0 23
# define s1 24
# define s2 25
# define s3 26
# define s4 27
# define s5 28
# define s6 29
# define s7 30
# define s8 31
# define fa0 32
# define fa1 33
# define fa2 34
# define fa3 35
# define fa4 36
# define fa5 37
# define fa6 38
# define fa7 39
# define ft0 40
# define ft1 41
# define ft2 42
# define ft3 43
# define ft4 44
# define ft5 45
# define ft6 46
# define ft7 47
# define ft8 48
# define ft9 49
# define ft10 50
# define ft11 51
# define ft12 52
# define ft13 53
# define ft14 54
# define ft15 55
# define fs0 56
# define fs1 57
# define fs2 58
# define fs3 59
# define fs4 60
# define fs5 61
# define fs6 62
# define fs7 63
#endif #endif
callerSaves :: GlobalReg -> Bool callerSaves :: GlobalReg -> Bool
...@@ -665,7 +733,9 @@ globalRegMaybe :: GlobalReg -> Maybe RealReg ...@@ -665,7 +733,9 @@ globalRegMaybe :: GlobalReg -> Maybe RealReg
|| defined(MACHREGS_powerpc) \ || defined(MACHREGS_powerpc) \
|| defined(MACHREGS_arm) || defined(MACHREGS_aarch64) \ || defined(MACHREGS_arm) || defined(MACHREGS_aarch64) \
|| defined(MACHREGS_s390x) || defined(MACHREGS_riscv64) \ || defined(MACHREGS_s390x) || defined(MACHREGS_riscv64) \
|| defined(MACHREGS_wasm32) || defined(MACHREGS_wasm32) \
|| defined(MACHREGS_loongarch64)
# if defined(REG_Base) # if defined(REG_Base)
globalRegMaybe BaseReg = Just (RealRegSingle REG_Base) globalRegMaybe BaseReg = Just (RealRegSingle REG_Base)
# endif # endif
......
...@@ -166,6 +166,7 @@ nativeCodeGen logger config modLoc h us cmms ...@@ -166,6 +166,7 @@ nativeCodeGen logger config modLoc h us cmms
ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb" ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb"
ArchMipsel -> panic "nativeCodeGen: No NCG for mipsel" ArchMipsel -> panic "nativeCodeGen: No NCG for mipsel"
ArchRISCV64 -> panic "nativeCodeGen: No NCG for RISCV64" ArchRISCV64 -> panic "nativeCodeGen: No NCG for RISCV64"
ArchLoongArch64->panic "nativeCodeGen: No NCG for LoongArch64"
ArchUnknown -> panic "nativeCodeGen: No NCG for unknown arch" ArchUnknown -> panic "nativeCodeGen: No NCG for unknown arch"
ArchJavaScript-> panic "nativeCodeGen: No NCG for JavaScript" ArchJavaScript-> panic "nativeCodeGen: No NCG for JavaScript"
ArchWasm32 -> Wasm32.ncgWasm platform us modLoc h cmms ArchWasm32 -> Wasm32.ncgWasm platform us modLoc h cmms
......
...@@ -118,6 +118,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl ...@@ -118,6 +118,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl
ArchMipsel -> panic "trivColorable ArchMipsel" ArchMipsel -> panic "trivColorable ArchMipsel"
ArchS390X -> panic "trivColorable ArchS390X" ArchS390X -> panic "trivColorable ArchS390X"
ArchRISCV64 -> panic "trivColorable ArchRISCV64" ArchRISCV64 -> panic "trivColorable ArchRISCV64"
ArchLoongArch64->panic "trivColorable ArchLoongArch64"
ArchJavaScript-> panic "trivColorable ArchJavaScript" ArchJavaScript-> panic "trivColorable ArchJavaScript"
ArchWasm32 -> panic "trivColorable ArchWasm32" ArchWasm32 -> panic "trivColorable ArchWasm32"
ArchUnknown -> panic "trivColorable ArchUnknown") ArchUnknown -> panic "trivColorable ArchUnknown")
...@@ -152,6 +153,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus ...@@ -152,6 +153,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus
ArchMipsel -> panic "trivColorable ArchMipsel" ArchMipsel -> panic "trivColorable ArchMipsel"
ArchS390X -> panic "trivColorable ArchS390X" ArchS390X -> panic "trivColorable ArchS390X"
ArchRISCV64 -> panic "trivColorable ArchRISCV64" ArchRISCV64 -> panic "trivColorable ArchRISCV64"
ArchLoongArch64->panic "trivColorable ArchLoongArch64"
ArchJavaScript-> panic "trivColorable ArchJavaScript" ArchJavaScript-> panic "trivColorable ArchJavaScript"
ArchWasm32 -> panic "trivColorable ArchWasm32" ArchWasm32 -> panic "trivColorable ArchWasm32"
ArchUnknown -> panic "trivColorable ArchUnknown") ArchUnknown -> panic "trivColorable ArchUnknown")
...@@ -185,6 +187,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu ...@@ -185,6 +187,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu
ArchMipsel -> panic "trivColorable ArchMipsel" ArchMipsel -> panic "trivColorable ArchMipsel"
ArchS390X -> panic "trivColorable ArchS390X" ArchS390X -> panic "trivColorable ArchS390X"
ArchRISCV64 -> panic "trivColorable ArchRISCV64" ArchRISCV64 -> panic "trivColorable ArchRISCV64"
ArchLoongArch64->panic "trivColorable ArchLoongArch64"
ArchJavaScript-> panic "trivColorable ArchJavaScript" ArchJavaScript-> panic "trivColorable ArchJavaScript"
ArchWasm32 -> panic "trivColorable ArchWasm32" ArchWasm32 -> panic "trivColorable ArchWasm32"
ArchUnknown -> panic "trivColorable ArchUnknown") ArchUnknown -> panic "trivColorable ArchUnknown")
......
...@@ -224,6 +224,7 @@ linearRegAlloc config entry_ids block_live sccs ...@@ -224,6 +224,7 @@ linearRegAlloc config entry_ids block_live sccs
ArchMipseb -> panic "linearRegAlloc ArchMipseb" ArchMipseb -> panic "linearRegAlloc ArchMipseb"
ArchMipsel -> panic "linearRegAlloc ArchMipsel" ArchMipsel -> panic "linearRegAlloc ArchMipsel"
ArchRISCV64 -> panic "linearRegAlloc ArchRISCV64" ArchRISCV64 -> panic "linearRegAlloc ArchRISCV64"
ArchLoongArch64-> panic "linearRegAlloc ArchLoongArch64"
ArchJavaScript -> panic "linearRegAlloc ArchJavaScript" ArchJavaScript -> panic "linearRegAlloc ArchJavaScript"
ArchWasm32 -> panic "linearRegAlloc ArchWasm32" ArchWasm32 -> panic "linearRegAlloc ArchWasm32"
ArchUnknown -> panic "linearRegAlloc ArchUnknown" ArchUnknown -> panic "linearRegAlloc ArchUnknown"
......
...@@ -77,6 +77,7 @@ maxSpillSlots config = case platformArch (ncgPlatform config) of ...@@ -77,6 +77,7 @@ maxSpillSlots config = case platformArch (ncgPlatform config) of
ArchMipseb -> panic "maxSpillSlots ArchMipseb" ArchMipseb -> panic "maxSpillSlots ArchMipseb"
ArchMipsel -> panic "maxSpillSlots ArchMipsel" ArchMipsel -> panic "maxSpillSlots ArchMipsel"
ArchRISCV64 -> panic "maxSpillSlots ArchRISCV64" ArchRISCV64 -> panic "maxSpillSlots ArchRISCV64"
ArchLoongArch64->panic "maxSpillSlots ArchLoongArch64"
ArchJavaScript-> panic "maxSpillSlots ArchJavaScript" ArchJavaScript-> panic "maxSpillSlots ArchJavaScript"
ArchWasm32 -> panic "maxSpillSlots ArchWasm32" ArchWasm32 -> panic "maxSpillSlots ArchWasm32"
ArchUnknown -> panic "maxSpillSlots ArchUnknown" ArchUnknown -> panic "maxSpillSlots ArchUnknown"
...@@ -50,6 +50,7 @@ targetVirtualRegSqueeze platform ...@@ -50,6 +50,7 @@ targetVirtualRegSqueeze platform
ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb" ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb"
ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel" ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel"
ArchRISCV64 -> panic "targetVirtualRegSqueeze ArchRISCV64" ArchRISCV64 -> panic "targetVirtualRegSqueeze ArchRISCV64"
ArchLoongArch64->panic "targetVirtualRegSqueeze ArchLoongArch64"
ArchJavaScript-> panic "targetVirtualRegSqueeze ArchJavaScript" ArchJavaScript-> panic "targetVirtualRegSqueeze ArchJavaScript"
ArchWasm32 -> panic "targetVirtualRegSqueeze ArchWasm32" ArchWasm32 -> panic "targetVirtualRegSqueeze ArchWasm32"
ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown" ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown"
...@@ -69,6 +70,7 @@ targetRealRegSqueeze platform ...@@ -69,6 +70,7 @@ targetRealRegSqueeze platform
ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb" ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb"
ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel" ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel"
ArchRISCV64 -> panic "targetRealRegSqueeze ArchRISCV64" ArchRISCV64 -> panic "targetRealRegSqueeze ArchRISCV64"
ArchLoongArch64->panic "targetRealRegSqueeze ArchLoongArch64"
ArchJavaScript-> panic "targetRealRegSqueeze ArchJavaScript" ArchJavaScript-> panic "targetRealRegSqueeze ArchJavaScript"
ArchWasm32 -> panic "targetRealRegSqueeze ArchWasm32" ArchWasm32 -> panic "targetRealRegSqueeze ArchWasm32"
ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown" ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown"
...@@ -87,6 +89,7 @@ targetClassOfRealReg platform ...@@ -87,6 +89,7 @@ targetClassOfRealReg platform
ArchMipseb -> panic "targetClassOfRealReg ArchMipseb" ArchMipseb -> panic "targetClassOfRealReg ArchMipseb"
ArchMipsel -> panic "targetClassOfRealReg ArchMipsel" ArchMipsel -> panic "targetClassOfRealReg ArchMipsel"
ArchRISCV64 -> panic "targetClassOfRealReg ArchRISCV64" ArchRISCV64 -> panic "targetClassOfRealReg ArchRISCV64"
ArchLoongArch64->panic "targetClassOfRealReg ArchLoongArch64"
ArchJavaScript-> panic "targetClassOfRealReg ArchJavaScript" ArchJavaScript-> panic "targetClassOfRealReg ArchJavaScript"
ArchWasm32 -> panic "targetClassOfRealReg ArchWasm32" ArchWasm32 -> panic "targetClassOfRealReg ArchWasm32"
ArchUnknown -> panic "targetClassOfRealReg ArchUnknown" ArchUnknown -> panic "targetClassOfRealReg ArchUnknown"
...@@ -105,6 +108,7 @@ targetMkVirtualReg platform ...@@ -105,6 +108,7 @@ targetMkVirtualReg platform
ArchMipseb -> panic "targetMkVirtualReg ArchMipseb" ArchMipseb -> panic "targetMkVirtualReg ArchMipseb"
ArchMipsel -> panic "targetMkVirtualReg ArchMipsel" ArchMipsel -> panic "targetMkVirtualReg ArchMipsel"
ArchRISCV64 -> panic "targetMkVirtualReg ArchRISCV64" ArchRISCV64 -> panic "targetMkVirtualReg ArchRISCV64"
ArchLoongArch64->panic "targetMkVirtualReg ArchLoongArch64"
ArchJavaScript-> panic "targetMkVirtualReg ArchJavaScript" ArchJavaScript-> panic "targetMkVirtualReg ArchJavaScript"
ArchWasm32 -> panic "targetMkVirtualReg ArchWasm32" ArchWasm32 -> panic "targetMkVirtualReg ArchWasm32"
ArchUnknown -> panic "targetMkVirtualReg ArchUnknown" ArchUnknown -> panic "targetMkVirtualReg ArchUnknown"
...@@ -123,6 +127,7 @@ targetRegDotColor platform ...@@ -123,6 +127,7 @@ targetRegDotColor platform
ArchMipseb -> panic "targetRegDotColor ArchMipseb" ArchMipseb -> panic "targetRegDotColor ArchMipseb"
ArchMipsel -> panic "targetRegDotColor ArchMipsel" ArchMipsel -> panic "targetRegDotColor ArchMipsel"
ArchRISCV64 -> panic "targetRegDotColor ArchRISCV64" ArchRISCV64 -> panic "targetRegDotColor ArchRISCV64"
ArchLoongArch64->panic "targetRegDotColor ArchLoongArch64"
ArchJavaScript-> panic "targetRegDotColor ArchJavaScript" ArchJavaScript-> panic "targetRegDotColor ArchJavaScript"
ArchWasm32 -> panic "targetRegDotColor ArchWasm32" ArchWasm32 -> panic "targetRegDotColor ArchWasm32"
ArchUnknown -> panic "targetRegDotColor ArchUnknown" ArchUnknown -> panic "targetRegDotColor ArchUnknown"
......
...@@ -1015,6 +1015,7 @@ llvmOptions llvm_config dflags = ...@@ -1015,6 +1015,7 @@ llvmOptions llvm_config dflags =
abi :: String abi :: String
abi = case platformArch (targetPlatform dflags) of abi = case platformArch (targetPlatform dflags) of
ArchRISCV64 -> "lp64d" ArchRISCV64 -> "lp64d"
ArchLoongArch64 -> "lp64d"
_ -> "" _ -> ""
-- | What phase to run after one of the backend code generators has run -- | What phase to run after one of the backend code generators has run
......
...@@ -263,6 +263,7 @@ platformCConvNeedsExtension platform = case platformArch platform of ...@@ -263,6 +263,7 @@ platformCConvNeedsExtension platform = case platformArch platform of
ArchPPC_64 _ -> True ArchPPC_64 _ -> True
ArchS390X -> True ArchS390X -> True
ArchRISCV64 -> True ArchRISCV64 -> True
ArchLoongArch64 -> True
ArchAArch64 ArchAArch64
-- Apple's AArch64 ABI requires that the caller sign-extend -- Apple's AArch64 ABI requires that the caller sign-extend
-- small integer arguments. See -- small integer arguments. See
......
{-# LANGUAGE CPP #-}
module GHC.Platform.LoongArch64 where
import GHC.Prelude
#define MACHREGS_NO_REGS 0
#define MACHREGS_loongarch64 1
#include "CodeGen.Platform.h"
\ No newline at end of file
...@@ -16,6 +16,7 @@ import qualified GHC.Platform.X86 as X86 ...@@ -16,6 +16,7 @@ import qualified GHC.Platform.X86 as X86
import qualified GHC.Platform.X86_64 as X86_64 import qualified GHC.Platform.X86_64 as X86_64
import qualified GHC.Platform.RISCV64 as RISCV64 import qualified GHC.Platform.RISCV64 as RISCV64
import qualified GHC.Platform.Wasm32 as Wasm32 import qualified GHC.Platform.Wasm32 as Wasm32
import qualified GHC.Platform.LoongArch64 as LoongArch64
import qualified GHC.Platform.NoRegs as NoRegs import qualified GHC.Platform.NoRegs as NoRegs
-- | Returns 'True' if this global register is stored in a caller-saves -- | Returns 'True' if this global register is stored in a caller-saves
...@@ -33,6 +34,7 @@ callerSaves platform ...@@ -33,6 +34,7 @@ callerSaves platform
ArchAArch64 -> AArch64.callerSaves ArchAArch64 -> AArch64.callerSaves
ArchRISCV64 -> RISCV64.callerSaves ArchRISCV64 -> RISCV64.callerSaves
ArchWasm32 -> Wasm32.callerSaves ArchWasm32 -> Wasm32.callerSaves
ArchLoongArch64 -> LoongArch64.callerSaves
arch arch
| arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
PPC.callerSaves PPC.callerSaves
...@@ -56,6 +58,7 @@ activeStgRegs platform ...@@ -56,6 +58,7 @@ activeStgRegs platform
ArchAArch64 -> AArch64.activeStgRegs ArchAArch64 -> AArch64.activeStgRegs
ArchRISCV64 -> RISCV64.activeStgRegs ArchRISCV64 -> RISCV64.activeStgRegs
ArchWasm32 -> Wasm32.activeStgRegs ArchWasm32 -> Wasm32.activeStgRegs
ArchLoongArch64 -> LoongArch64.activeStgRegs
arch arch
| arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
PPC.activeStgRegs PPC.activeStgRegs
...@@ -74,6 +77,7 @@ haveRegBase platform ...@@ -74,6 +77,7 @@ haveRegBase platform
ArchAArch64 -> AArch64.haveRegBase ArchAArch64 -> AArch64.haveRegBase
ArchRISCV64 -> RISCV64.haveRegBase ArchRISCV64 -> RISCV64.haveRegBase
ArchWasm32 -> Wasm32.haveRegBase ArchWasm32 -> Wasm32.haveRegBase
ArchLoongArch64 -> LoongArch64.haveRegBase
arch arch
| arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
PPC.haveRegBase PPC.haveRegBase
...@@ -92,6 +96,7 @@ globalRegMaybe platform ...@@ -92,6 +96,7 @@ globalRegMaybe platform
ArchAArch64 -> AArch64.globalRegMaybe ArchAArch64 -> AArch64.globalRegMaybe
ArchRISCV64 -> RISCV64.globalRegMaybe ArchRISCV64 -> RISCV64.globalRegMaybe
ArchWasm32 -> Wasm32.globalRegMaybe ArchWasm32 -> Wasm32.globalRegMaybe
ArchLoongArch64 -> LoongArch64.globalRegMaybe
arch arch
| arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
PPC.globalRegMaybe PPC.globalRegMaybe
...@@ -110,6 +115,7 @@ freeReg platform ...@@ -110,6 +115,7 @@ freeReg platform
ArchAArch64 -> AArch64.freeReg ArchAArch64 -> AArch64.freeReg
ArchRISCV64 -> RISCV64.freeReg ArchRISCV64 -> RISCV64.freeReg
ArchWasm32 -> Wasm32.freeReg ArchWasm32 -> Wasm32.freeReg
ArchLoongArch64 -> LoongArch64.freeReg
arch arch
| arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
PPC.freeReg PPC.freeReg
......
...@@ -569,6 +569,7 @@ Library ...@@ -569,6 +569,7 @@ Library
GHC.Platform.Reg.Class GHC.Platform.Reg.Class
GHC.Platform.Regs GHC.Platform.Regs
GHC.Platform.RISCV64 GHC.Platform.RISCV64
GHC.Platform.LoongArch64
GHC.Platform.S390X GHC.Platform.S390X
GHC.Platform.Wasm32 GHC.Platform.Wasm32
GHC.Platform.Ways GHC.Platform.Ways
......
...@@ -333,7 +333,7 @@ AC_SUBST(TablesNextToCode) ...@@ -333,7 +333,7 @@ AC_SUBST(TablesNextToCode)
dnl ** Does target have runtime linker support? dnl ** Does target have runtime linker support?
dnl -------------------------------------------------------------- dnl --------------------------------------------------------------
case "$target" in case "$target" in
powerpc64-*|powerpc64le-*|powerpc-ibm-aix*|s390x-ibm-linux|riscv64-*|wasm*|js-*) powerpc64-*|powerpc64le-*|powerpc-ibm-aix*|s390x-ibm-linux|riscv64-*|wasm*|js-*|loongarch64-*)
TargetHasRTSLinker=NO TargetHasRTSLinker=NO
;; ;;
*) *)
......
...@@ -118,7 +118,8 @@ targetSupportsSMP = do ...@@ -118,7 +118,8 @@ targetSupportsSMP = do
, "arm" , "arm"
, "aarch64" , "aarch64"
, "s390x" , "s390x"
, "riscv64"] , "riscv64"
, "loongarch64"]
if -- The THREADED_RTS requires `BaseReg` to be in a register and the if -- The THREADED_RTS requires `BaseReg` to be in a register and the
-- Unregisterised mode doesn't allow that. -- Unregisterised mode doesn't allow that.
| unreg -> return False | unreg -> return False
......
...@@ -89,6 +89,8 @@ os = HOST_OS ...@@ -89,6 +89,8 @@ os = HOST_OS
-- * "powerpc64le" -- * "powerpc64le"
-- * "riscv32" -- * "riscv32"
-- * "riscv64" -- * "riscv64"
-- * "loongarch32"
-- * "loongarch64"
-- * "rs6000" -- * "rs6000"
-- * "s390" -- * "s390"
-- * "s390x" -- * "s390x"
......
...@@ -44,6 +44,7 @@ data Arch ...@@ -44,6 +44,7 @@ data Arch
| ArchMipseb | ArchMipseb
| ArchMipsel | ArchMipsel
| ArchRISCV64 | ArchRISCV64
| ArchLoongArch64
| ArchJavaScript | ArchJavaScript
| ArchWasm32 | ArchWasm32
deriving (Read, Show, Eq, Ord) deriving (Read, Show, Eq, Ord)
...@@ -134,6 +135,7 @@ stringEncodeArch = \case ...@@ -134,6 +135,7 @@ stringEncodeArch = \case
ArchMipseb -> "mipseb" ArchMipseb -> "mipseb"
ArchMipsel -> "mipsel" ArchMipsel -> "mipsel"
ArchRISCV64 -> "riscv64" ArchRISCV64 -> "riscv64"
ArchLoongArch64 -> "loongarch64"
ArchJavaScript -> "js" ArchJavaScript -> "js"
ArchWasm32 -> "wasm32" ArchWasm32 -> "wasm32"
......
...@@ -43,6 +43,8 @@ ...@@ -43,6 +43,8 @@
,("s390x-ibm-linux", ("E-m:e-i1:8:16-i8:8:16-i64:64-f128:64-a:8:16-n32:64", "z10", "")) ,("s390x-ibm-linux", ("E-m:e-i1:8:16-i8:8:16-i64:64-f128:64-a:8:16-n32:64", "z10", ""))
,("riscv64-unknown-linux-gnu", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+m +a +f +d +c +relax")) ,("riscv64-unknown-linux-gnu", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+m +a +f +d +c +relax"))
,("riscv64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+m +a +f +d +c +relax")) ,("riscv64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+m +a +f +d +c +relax"))
,("loongarch64-unknown-linux-gnu", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+f +d"))
,("loongarch64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+f +d"))
,("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", "")) ,("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", "")) ,("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", "generic", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes")) ,("arm64-apple-darwin", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes"))
......
...@@ -45,7 +45,10 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS_SHELL_FUNCTIONS], ...@@ -45,7 +45,10 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS_SHELL_FUNCTIONS],
wasm32) wasm32)
test -z "[$]2" || eval "[$]2=ArchWasm32" test -z "[$]2" || eval "[$]2=ArchWasm32"
;; ;;
hppa|hppa1_1|ia64|m68k|nios2|riscv32|rs6000|s390|sh4|vax) loongarch64)
test -z "[$]2" || eval "[$]2=ArchLoongArch64"
;;
hppa|hppa1_1|ia64|m68k|nios2|riscv32|loongarch32|rs6000|s390|sh4|vax)
test -z "[$]2" || eval "[$]2=ArchUnknown" test -z "[$]2" || eval "[$]2=ArchUnknown"
;; ;;
js) js)
......
...@@ -56,6 +56,12 @@ case "$1" in ...@@ -56,6 +56,12 @@ case "$1" in
riscv|riscv32*) riscv|riscv32*)
$2="riscv32" $2="riscv32"
;; ;;
loongarch64*)
$2="loongarch64"
;;
loongarch32*)
$2="loongarch32"
;;
rs6000) rs6000)
$2="rs6000" $2="rs6000"
;; ;;
......
...@@ -17,7 +17,7 @@ AC_DEFUN([GHC_TABLES_NEXT_TO_CODE], ...@@ -17,7 +17,7 @@ AC_DEFUN([GHC_TABLES_NEXT_TO_CODE],
case "$Unregisterised" in case "$Unregisterised" in
NO) NO)
case "$TargetArch" in case "$TargetArch" in
ia64|powerpc64|powerpc64le|s390x|wasm32) ia64|powerpc64|powerpc64le|s390x|wasm32|loongarch64)
TablesNextToCodeDefault=NO TablesNextToCodeDefault=NO
AC_MSG_RESULT([no]) AC_MSG_RESULT([no])
;; ;;
......
...@@ -5,7 +5,7 @@ AC_DEFUN([GHC_UNREGISTERISED], ...@@ -5,7 +5,7 @@ AC_DEFUN([GHC_UNREGISTERISED],
[ [
AC_MSG_CHECKING(whether target supports a registerised ABI) AC_MSG_CHECKING(whether target supports a registerised ABI)
case "$TargetArch" in case "$TargetArch" in
i386|x86_64|powerpc|powerpc64|powerpc64le|s390x|arm|aarch64|riscv64|wasm32|js) i386|x86_64|powerpc|powerpc64|powerpc64le|s390x|arm|aarch64|riscv64|wasm32|js|loongarch64)
UnregisterisedDefault=NO UnregisterisedDefault=NO
AC_MSG_RESULT([yes]) AC_MSG_RESULT([yes])
;; ;;
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment