diff --git a/compiler/CodeGen.Platform.h b/compiler/CodeGen.Platform.h
index 42274b2f8dc521ea71ce10e0f2953197560625b4..01ea529fa0fc6cb978bcf9e978bfd50583df5d0f 100644
--- a/compiler/CodeGen.Platform.h
+++ b/compiler/CodeGen.Platform.h
@@ -377,6 +377,74 @@ import GHC.Platform.Reg
 # define ft10 62
 # 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
 
 callerSaves :: GlobalReg -> Bool
@@ -665,7 +733,9 @@ globalRegMaybe :: GlobalReg -> Maybe RealReg
     || defined(MACHREGS_powerpc) \
     || defined(MACHREGS_arm) || defined(MACHREGS_aarch64) \
     || defined(MACHREGS_s390x) || defined(MACHREGS_riscv64) \
-    || defined(MACHREGS_wasm32)
+    || defined(MACHREGS_wasm32) \
+    || defined(MACHREGS_loongarch64)
+
 # if defined(REG_Base)
 globalRegMaybe BaseReg                  = Just (RealRegSingle REG_Base)
 # endif
diff --git a/compiler/GHC/CmmToAsm.hs b/compiler/GHC/CmmToAsm.hs
index adb71e11a87edb10dff41d48f2b873c8cfa17da1..f4eb61c449eaaa9c9a95250f6fbff5fa8d80db64 100644
--- a/compiler/GHC/CmmToAsm.hs
+++ b/compiler/GHC/CmmToAsm.hs
@@ -166,6 +166,7 @@ nativeCodeGen logger config modLoc h us cmms
       ArchMipseb    -> panic "nativeCodeGen: No NCG for mipseb"
       ArchMipsel    -> panic "nativeCodeGen: No NCG for mipsel"
       ArchRISCV64   -> panic "nativeCodeGen: No NCG for RISCV64"
+      ArchLoongArch64->panic "nativeCodeGen: No NCG for LoongArch64"
       ArchUnknown   -> panic "nativeCodeGen: No NCG for unknown arch"
       ArchJavaScript-> panic "nativeCodeGen: No NCG for JavaScript"
       ArchWasm32    -> Wasm32.ncgWasm platform us modLoc h cmms
diff --git a/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs b/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
index 7e0c5703876b430d573650eba3da817b71c97b6c..26ce377ab10168000954806c8dcf1189be21fe65 100644
--- a/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
@@ -118,6 +118,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl
                             ArchMipsel    -> panic "trivColorable ArchMipsel"
                             ArchS390X     -> panic "trivColorable ArchS390X"
                             ArchRISCV64   -> panic "trivColorable ArchRISCV64"
+                            ArchLoongArch64->panic "trivColorable ArchLoongArch64"
                             ArchJavaScript-> panic "trivColorable ArchJavaScript"
                             ArchWasm32    -> panic "trivColorable ArchWasm32"
                             ArchUnknown   -> panic "trivColorable ArchUnknown")
@@ -152,6 +153,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus
                             ArchMipsel    -> panic "trivColorable ArchMipsel"
                             ArchS390X     -> panic "trivColorable ArchS390X"
                             ArchRISCV64   -> panic "trivColorable ArchRISCV64"
+                            ArchLoongArch64->panic "trivColorable ArchLoongArch64"
                             ArchJavaScript-> panic "trivColorable ArchJavaScript"
                             ArchWasm32    -> panic "trivColorable ArchWasm32"
                             ArchUnknown   -> panic "trivColorable ArchUnknown")
@@ -185,6 +187,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu
                             ArchMipsel    -> panic "trivColorable ArchMipsel"
                             ArchS390X     -> panic "trivColorable ArchS390X"
                             ArchRISCV64   -> panic "trivColorable ArchRISCV64"
+                            ArchLoongArch64->panic "trivColorable ArchLoongArch64"
                             ArchJavaScript-> panic "trivColorable ArchJavaScript"
                             ArchWasm32    -> panic "trivColorable ArchWasm32"
                             ArchUnknown   -> panic "trivColorable ArchUnknown")
diff --git a/compiler/GHC/CmmToAsm/Reg/Linear.hs b/compiler/GHC/CmmToAsm/Reg/Linear.hs
index 8469242214fe478ddc6275a5d061e1f97dce8047..3064bf0d912387c4a763ff150635ead838db284c 100644
--- a/compiler/GHC/CmmToAsm/Reg/Linear.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Linear.hs
@@ -224,6 +224,7 @@ linearRegAlloc config entry_ids block_live sccs
       ArchMipseb     -> panic "linearRegAlloc ArchMipseb"
       ArchMipsel     -> panic "linearRegAlloc ArchMipsel"
       ArchRISCV64    -> panic "linearRegAlloc ArchRISCV64"
+      ArchLoongArch64-> panic "linearRegAlloc ArchLoongArch64"
       ArchJavaScript -> panic "linearRegAlloc ArchJavaScript"
       ArchWasm32     -> panic "linearRegAlloc ArchWasm32"
       ArchUnknown    -> panic "linearRegAlloc ArchUnknown"
diff --git a/compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs b/compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
index 65c2805e9bf20a264286396605a247043071df5c..519ea55fca88056a375e5bfc7f993666e6b9ed03 100644
--- a/compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
@@ -77,6 +77,7 @@ maxSpillSlots config = case platformArch (ncgPlatform config) of
    ArchMipseb    -> panic "maxSpillSlots ArchMipseb"
    ArchMipsel    -> panic "maxSpillSlots ArchMipsel"
    ArchRISCV64   -> panic "maxSpillSlots ArchRISCV64"
+   ArchLoongArch64->panic "maxSpillSlots ArchLoongArch64"
    ArchJavaScript-> panic "maxSpillSlots ArchJavaScript"
    ArchWasm32    -> panic "maxSpillSlots ArchWasm32"
    ArchUnknown   -> panic "maxSpillSlots ArchUnknown"
diff --git a/compiler/GHC/CmmToAsm/Reg/Target.hs b/compiler/GHC/CmmToAsm/Reg/Target.hs
index 97440d1ac6239e4a74b91fbb060bb1a3cb5f0687..a94010987a0fd8a8ae592bd1af10c5ff2a8549d5 100644
--- a/compiler/GHC/CmmToAsm/Reg/Target.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Target.hs
@@ -50,6 +50,7 @@ targetVirtualRegSqueeze platform
       ArchMipseb    -> panic "targetVirtualRegSqueeze ArchMipseb"
       ArchMipsel    -> panic "targetVirtualRegSqueeze ArchMipsel"
       ArchRISCV64   -> panic "targetVirtualRegSqueeze ArchRISCV64"
+      ArchLoongArch64->panic "targetVirtualRegSqueeze ArchLoongArch64"
       ArchJavaScript-> panic "targetVirtualRegSqueeze ArchJavaScript"
       ArchWasm32    -> panic "targetVirtualRegSqueeze ArchWasm32"
       ArchUnknown   -> panic "targetVirtualRegSqueeze ArchUnknown"
@@ -69,6 +70,7 @@ targetRealRegSqueeze platform
       ArchMipseb    -> panic "targetRealRegSqueeze ArchMipseb"
       ArchMipsel    -> panic "targetRealRegSqueeze ArchMipsel"
       ArchRISCV64   -> panic "targetRealRegSqueeze ArchRISCV64"
+      ArchLoongArch64->panic "targetRealRegSqueeze ArchLoongArch64"
       ArchJavaScript-> panic "targetRealRegSqueeze ArchJavaScript"
       ArchWasm32    -> panic "targetRealRegSqueeze ArchWasm32"
       ArchUnknown   -> panic "targetRealRegSqueeze ArchUnknown"
@@ -87,6 +89,7 @@ targetClassOfRealReg platform
       ArchMipseb    -> panic "targetClassOfRealReg ArchMipseb"
       ArchMipsel    -> panic "targetClassOfRealReg ArchMipsel"
       ArchRISCV64   -> panic "targetClassOfRealReg ArchRISCV64"
+      ArchLoongArch64->panic "targetClassOfRealReg ArchLoongArch64"
       ArchJavaScript-> panic "targetClassOfRealReg ArchJavaScript"
       ArchWasm32    -> panic "targetClassOfRealReg ArchWasm32"
       ArchUnknown   -> panic "targetClassOfRealReg ArchUnknown"
@@ -105,6 +108,7 @@ targetMkVirtualReg platform
       ArchMipseb    -> panic "targetMkVirtualReg ArchMipseb"
       ArchMipsel    -> panic "targetMkVirtualReg ArchMipsel"
       ArchRISCV64   -> panic "targetMkVirtualReg ArchRISCV64"
+      ArchLoongArch64->panic "targetMkVirtualReg ArchLoongArch64"
       ArchJavaScript-> panic "targetMkVirtualReg ArchJavaScript"
       ArchWasm32    -> panic "targetMkVirtualReg ArchWasm32"
       ArchUnknown   -> panic "targetMkVirtualReg ArchUnknown"
@@ -123,6 +127,7 @@ targetRegDotColor platform
       ArchMipseb    -> panic "targetRegDotColor ArchMipseb"
       ArchMipsel    -> panic "targetRegDotColor ArchMipsel"
       ArchRISCV64   -> panic "targetRegDotColor ArchRISCV64"
+      ArchLoongArch64->panic "targetRegDotColor ArchLoongArch64"
       ArchJavaScript-> panic "targetRegDotColor ArchJavaScript"
       ArchWasm32    -> panic "targetRegDotColor ArchWasm32"
       ArchUnknown   -> panic "targetRegDotColor ArchUnknown"
diff --git a/compiler/GHC/Driver/Pipeline/Execute.hs b/compiler/GHC/Driver/Pipeline/Execute.hs
index bd9ee7805a02650a47eda5a95d7bfcbf74d3cbd5..7c8dcaaa88e9962ed0c8a2ed52b6f8780ffa2809 100644
--- a/compiler/GHC/Driver/Pipeline/Execute.hs
+++ b/compiler/GHC/Driver/Pipeline/Execute.hs
@@ -1015,6 +1015,7 @@ llvmOptions llvm_config dflags =
         abi :: String
         abi = case platformArch (targetPlatform dflags) of
                 ArchRISCV64 -> "lp64d"
+                ArchLoongArch64 -> "lp64d"
                 _           -> ""
 
 -- | What phase to run after one of the backend code generators has run
diff --git a/compiler/GHC/Platform.hs b/compiler/GHC/Platform.hs
index b345d1535a5e196da1263fd5033760bf33ca8c45..a630e0c1d31a86b7f1e646aa8cd44bb85f648457 100644
--- a/compiler/GHC/Platform.hs
+++ b/compiler/GHC/Platform.hs
@@ -263,6 +263,7 @@ platformCConvNeedsExtension platform = case platformArch platform of
   ArchPPC_64 _ -> True
   ArchS390X    -> True
   ArchRISCV64  -> True
+  ArchLoongArch64 -> True
   ArchAArch64
       -- Apple's AArch64 ABI requires that the caller sign-extend
       -- small integer arguments. See
diff --git a/compiler/GHC/Platform/LoongArch64.hs b/compiler/GHC/Platform/LoongArch64.hs
new file mode 100644
index 0000000000000000000000000000000000000000..deabbbb4c08df13911428a40f299bfe564bf7a4a
--- /dev/null
+++ b/compiler/GHC/Platform/LoongArch64.hs
@@ -0,0 +1,9 @@
+{-# 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
diff --git a/compiler/GHC/Platform/Regs.hs b/compiler/GHC/Platform/Regs.hs
index 7f1ad5adc6553af84938e3e397a1bd6fa35b4a75..429f977a99c54859a2c5769ff6f424b4d3721783 100644
--- a/compiler/GHC/Platform/Regs.hs
+++ b/compiler/GHC/Platform/Regs.hs
@@ -16,6 +16,7 @@ import qualified GHC.Platform.X86        as X86
 import qualified GHC.Platform.X86_64     as X86_64
 import qualified GHC.Platform.RISCV64    as RISCV64
 import qualified GHC.Platform.Wasm32     as Wasm32
+import qualified GHC.Platform.LoongArch64 as LoongArch64
 import qualified GHC.Platform.NoRegs     as NoRegs
 
 -- | Returns 'True' if this global register is stored in a caller-saves
@@ -33,6 +34,7 @@ callerSaves platform
    ArchAArch64 -> AArch64.callerSaves
    ArchRISCV64 -> RISCV64.callerSaves
    ArchWasm32  -> Wasm32.callerSaves
+   ArchLoongArch64 -> LoongArch64.callerSaves
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.callerSaves
@@ -56,6 +58,7 @@ activeStgRegs platform
    ArchAArch64 -> AArch64.activeStgRegs
    ArchRISCV64 -> RISCV64.activeStgRegs
    ArchWasm32  -> Wasm32.activeStgRegs
+   ArchLoongArch64 -> LoongArch64.activeStgRegs
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.activeStgRegs
@@ -74,6 +77,7 @@ haveRegBase platform
    ArchAArch64 -> AArch64.haveRegBase
    ArchRISCV64 -> RISCV64.haveRegBase
    ArchWasm32  -> Wasm32.haveRegBase
+   ArchLoongArch64 -> LoongArch64.haveRegBase
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.haveRegBase
@@ -92,6 +96,7 @@ globalRegMaybe platform
    ArchAArch64 -> AArch64.globalRegMaybe
    ArchRISCV64 -> RISCV64.globalRegMaybe
    ArchWasm32  -> Wasm32.globalRegMaybe
+   ArchLoongArch64 -> LoongArch64.globalRegMaybe
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.globalRegMaybe
@@ -110,6 +115,7 @@ freeReg platform
    ArchAArch64 -> AArch64.freeReg
    ArchRISCV64 -> RISCV64.freeReg
    ArchWasm32  -> Wasm32.freeReg
+   ArchLoongArch64 -> LoongArch64.freeReg
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.freeReg
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 34ccc26270859800417f6435341a598da40ae16d..3ad827112792acfffeaf05a8f5b3e365c4b387f2 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -569,6 +569,7 @@ Library
         GHC.Platform.Reg.Class
         GHC.Platform.Regs
         GHC.Platform.RISCV64
+        GHC.Platform.LoongArch64
         GHC.Platform.S390X
         GHC.Platform.Wasm32
         GHC.Platform.Ways
diff --git a/configure.ac b/configure.ac
index 2e683cdef33150657aa75258c50779aa5af43136..09c48d592c19f4a5a7616974ea1f5835c4bfc97a 100644
--- a/configure.ac
+++ b/configure.ac
@@ -333,7 +333,7 @@ AC_SUBST(TablesNextToCode)
 dnl ** Does target have runtime linker support?
 dnl --------------------------------------------------------------
 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
         ;;
     *)
diff --git a/hadrian/src/Oracles/Flag.hs b/hadrian/src/Oracles/Flag.hs
index 41fc723b445ac1cc45cd67c42a03e6e07175440d..836834cbfc8f076e5a365cbb6ed6edafe5e19c9b 100644
--- a/hadrian/src/Oracles/Flag.hs
+++ b/hadrian/src/Oracles/Flag.hs
@@ -118,7 +118,8 @@ targetSupportsSMP = do
                             , "arm"
                             , "aarch64"
                             , "s390x"
-                            , "riscv64"]
+                            , "riscv64"
+                            , "loongarch64"]
   if   -- The THREADED_RTS requires `BaseReg` to be in a register and the
        -- Unregisterised mode doesn't allow that.
      | unreg                -> return False
diff --git a/libraries/base/System/Info.hs b/libraries/base/System/Info.hs
index 39ef75bd0f75897f84de42aa1cc9dc45df06daac..0d5d0ce429b323329820939d3d54f0e4662932fe 100644
--- a/libraries/base/System/Info.hs
+++ b/libraries/base/System/Info.hs
@@ -89,6 +89,8 @@ os = HOST_OS
 --    * "powerpc64le"
 --    * "riscv32"
 --    * "riscv64"
+--    * "loongarch32"
+--    * "loongarch64"
 --    * "rs6000"
 --    * "s390"
 --    * "s390x"
diff --git a/libraries/ghc-boot/GHC/Platform/ArchOS.hs b/libraries/ghc-boot/GHC/Platform/ArchOS.hs
index fa8042671af32e504ae1ce21dfcc642cc20d0b72..3a2774db7d7a5d4e2bc12a26fee1411990ef4d30 100644
--- a/libraries/ghc-boot/GHC/Platform/ArchOS.hs
+++ b/libraries/ghc-boot/GHC/Platform/ArchOS.hs
@@ -44,6 +44,7 @@ data Arch
    | ArchMipseb
    | ArchMipsel
    | ArchRISCV64
+   | ArchLoongArch64
    | ArchJavaScript
    | ArchWasm32
    deriving (Read, Show, Eq, Ord)
@@ -134,6 +135,7 @@ stringEncodeArch = \case
   ArchMipseb        -> "mipseb"
   ArchMipsel        -> "mipsel"
   ArchRISCV64       -> "riscv64"
+  ArchLoongArch64   -> "loongarch64"
   ArchJavaScript    -> "js"
   ArchWasm32        -> "wasm32"
 
diff --git a/llvm-targets b/llvm-targets
index eb254cffde0c19c4e93bb98a33968373f3e6b310..213a2ea4d6c05fcaa7e4b5c49dc946d5fcd69af6 100644
--- a/llvm-targets
+++ b/llvm-targets
@@ -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", ""))
 ,("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"))
+,("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", ""))
 ,("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"))
diff --git a/m4/fptools_set_haskell_platform_vars.m4 b/m4/fptools_set_haskell_platform_vars.m4
index d0c091e57d8172343ce534aa273da01af64f4f8b..1a32b3046bed1792cf3b682d09f7b8fbc251b94e 100644
--- a/m4/fptools_set_haskell_platform_vars.m4
+++ b/m4/fptools_set_haskell_platform_vars.m4
@@ -45,7 +45,10 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS_SHELL_FUNCTIONS],
         wasm32)
             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"
             ;;
         js)
diff --git a/m4/ghc_convert_cpu.m4 b/m4/ghc_convert_cpu.m4
index 8c1f1925e735e067260468e045de89c36776b8f1..b3f1789bbc1f15236383096dea1c610eca168b60 100644
--- a/m4/ghc_convert_cpu.m4
+++ b/m4/ghc_convert_cpu.m4
@@ -56,6 +56,12 @@ case "$1" in
   riscv|riscv32*)
     $2="riscv32"
     ;;
+  loongarch64*)
+    $2="loongarch64"
+    ;;
+  loongarch32*)
+    $2="loongarch32"
+    ;;
   rs6000)
     $2="rs6000"
     ;;
diff --git a/m4/ghc_tables_next_to_code.m4 b/m4/ghc_tables_next_to_code.m4
index 3e0ced2137dfaa0f0a1798ac1867aa7e0f25a65c..8acf250c4474782f13b7576665e97a8ff27bebbb 100644
--- a/m4/ghc_tables_next_to_code.m4
+++ b/m4/ghc_tables_next_to_code.m4
@@ -17,7 +17,7 @@ AC_DEFUN([GHC_TABLES_NEXT_TO_CODE],
   case "$Unregisterised" in
       NO)
           case "$TargetArch" in
-              ia64|powerpc64|powerpc64le|s390x|wasm32)
+              ia64|powerpc64|powerpc64le|s390x|wasm32|loongarch64)
                   TablesNextToCodeDefault=NO
                   AC_MSG_RESULT([no])
                   ;;
diff --git a/m4/ghc_unregisterised.m4 b/m4/ghc_unregisterised.m4
index aafb92e1655c181008327966c84cc06648d6ff69..38b445067de18f6efb9347a8ebfc63023213f407 100644
--- a/m4/ghc_unregisterised.m4
+++ b/m4/ghc_unregisterised.m4
@@ -5,7 +5,7 @@ AC_DEFUN([GHC_UNREGISTERISED],
 [
   AC_MSG_CHECKING(whether target supports a registerised ABI)
   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
           AC_MSG_RESULT([yes])
           ;;
diff --git a/rts/StgCRunAsm.S b/rts/StgCRunAsm.S
index 9216e6c759813f89b00db470cb707f3ed5eb24b3..d4172c5af4c57bbffa89a53fed45a8e5a53f5bae 100644
--- a/rts/StgCRunAsm.S
+++ b/rts/StgCRunAsm.S
@@ -370,6 +370,126 @@ StgReturn:
 	ret
 	.cfi_endproc
 	.size StgReturn, .-StgReturn
+
+#elif defined(loongarch64_HOST_ARCH)
+# define STACK_FRAME_SIZE (RESERVED_C_STACK_BYTES+160)
+	.text
+	.align 1
+	.globl StgRun
+	.type StgRun, @function
+StgRun:
+	.cfi_startproc
+	addi.d	$sp,$sp,-160
+	.cfi_def_cfa_offset 160
+	/* save callee-saved registers plus ra */
+	st.d	$ra,$sp,152
+	st.d    $fp,$sp,144
+	st.d	$s0,$sp,136
+	st.d	$s1,$sp,128
+	st.d	$s2,$sp,120
+	st.d	$s3,$sp,112
+	st.d	$s4,$sp,104
+	st.d	$s5,$sp,96
+	st.d	$s6,$sp,88
+	st.d	$s7,$sp,80
+	st.d	$s8,$sp,72
+	fst.d	$fs0,$sp,56
+	fst.d	$fs1,$sp,48
+	fst.d	$fs2,$sp,40
+	fst.d	$fs3,$sp,32
+	fst.d	$fs4,$sp,24
+	fst.d	$fs5,$sp,16
+	fst.d	$fs6,$sp,8
+	fst.d	$fs7,$sp,0
+	/* allocate stack frame */
+	li.d	$t0,RESERVED_C_STACK_BYTES
+	sub.d	$sp,$sp,$t0
+	.cfi_def_cfa_offset STACK_FRAME_SIZE
+	.cfi_offset 1, -8
+	.cfi_offset 22, -16
+	.cfi_offset 23, -24
+	.cfi_offset 24, -32
+	.cfi_offset 25, -40
+	.cfi_offset 26, -48
+	.cfi_offset 27, -56
+	.cfi_offset 28, -64
+	.cfi_offset 29, -72
+	.cfi_offset 30, -80
+	.cfi_offset 31, -88
+	.cfi_offset 56, -104
+	.cfi_offset 57, -112
+	.cfi_offset 58, -120
+	.cfi_offset 59, -128
+	.cfi_offset 60, -136
+	.cfi_offset 61, -144
+	.cfi_offset 62, -152
+	.cfi_offset 63, -160
+	/* set STGs BaseReg from LoongArch a1 */
+	move	$s0,$a1
+	/* jump to STG function */
+	jr	$a0
+	.cfi_endproc
+	.size StgRun, .-StgRun
+
+	.text
+	.align 2
+	.globl StgReturn
+	.type StgReturn, @function
+StgReturn:
+	.cfi_startproc
+	/* set return value from STGs R1 (LoongArch64 s3) */
+	move	$a0,$s3
+	/* deallocate stack frame */
+	li.d	$t0,RESERVED_C_STACK_BYTES
+	add.d	$sp,$sp,$t0
+	.cfi_def_cfa_offset 160
+	/* restore callee-saved registers and ra */
+	ld.d	$ra,$sp,152
+	.cfi_restore 1
+	ld.d	$fp,$sp,144
+	.cfi_restore 22
+	ld.d	$s0,$sp,136
+	.cfi_restore 23 
+	ld.d	$s1,$sp,128
+	.cfi_restore 24
+	ld.d	$s2,$sp,120
+	.cfi_restore 25
+	ld.d	$s3,$sp,112
+	.cfi_restore 26
+	ld.d	$s4,$sp,104
+	.cfi_restore 27
+	ld.d	$s5,$sp,96
+	.cfi_restore 28
+	ld.d	$s6,$sp,88
+	.cfi_restore 29
+	ld.d	$s7,$sp,80
+	.cfi_restore 30
+	ld.d	$s8,$sp,72
+	.cfi_restore 31
+	fld.d	$fs0,$sp,56
+	.cfi_restore 56
+	fld.d	$fs1,$sp,48
+	.cfi_restore 57
+	fld.d	$fs2,$sp,40
+	.cfi_restore 58
+	fld.d	$fs3,$sp,32
+	.cfi_restore 59
+	fld.d	$fs4,$sp,24
+	.cfi_restore 60
+	fld.d	$fs5,$sp,16
+	.cfi_restore 61
+	fld.d	$fs6,$sp,8
+	.cfi_restore 62
+	fld.d	$fs7,$sp,0
+	.cfi_restore 63
+	addi.d	$sp,$sp,160
+	.cfi_def_cfa_offset 0
+	/* jump back to caller of StgRun() */
+	ret
+	.cfi_endproc
+	.size StgReturn, .-StgReturn
+
+	.section	.note.GNU-stack,"",@progbits
 #endif
 
 #endif /* !USE_MINIINTERPRETER */
diff --git a/rts/include/stg/MachRegs.h b/rts/include/stg/MachRegs.h
index 2563f938caedf1073e0393ce0efdf30fd6a5a16c..f0253865ea3b49abd2ab5f0d4075cc5347d59052 100644
--- a/rts/include/stg/MachRegs.h
+++ b/rts/include/stg/MachRegs.h
@@ -626,6 +626,57 @@ the stack. See Note [Overlapping global registers] for implications.
 #define REG_HpLim          27
 #define REG_CCCS           28
 
+/* -----------------------------------------------------------------------------
+   The loongarch64 register mapping
+
+   Register    | Role(s)                                 | Call effect
+   ------------+-----------------------------------------+-------------
+   zero        | Hard-wired zero                         | -
+   ra          | Return address                          | caller-saved
+   tp          | Thread pointer                          | -
+   sp          | Stack pointer                           | callee-saved
+   a0,a1       | Arguments / return values               | caller-saved
+   a2..a7      | Arguments                               | caller-saved
+   t0..t8      | -                                       | caller-saved
+   u0          | Reserve                                 | -
+   fp          | Frame pointer                           | callee-saved
+   s0..s8      | -                                       | callee-saved
+   fa0,fa1     | Arguments / return values               | caller-saved
+   fa2..fa7    | Arguments                               | caller-saved
+   ft0..ft15   | -                                       | caller-saved
+   fs0..fs7    | -                                       | callee-saved
+
+   Each general purpose register as well as each floating-point
+   register is 64 bits wide, also, the u0 register is called r21 in some cases.
+
+   -------------------------------------------------------------------------- */
+#elif defined(MACHREGS_loongarch64)
+
+#define REG(x) __asm__("$" #x)
+
+#define REG_Base        s0
+#define REG_Sp          s1
+#define REG_Hp          s2
+#define REG_R1          s3
+#define REG_R2          s4
+#define REG_R3          s5
+#define REG_R4          s6
+#define REG_R5          s7
+#define REG_SpLim       s8
+
+#define REG_F1          fs0
+#define REG_F2          fs1
+#define REG_F3          fs2
+#define REG_F4          fs3
+
+#define REG_D1          fs4
+#define REG_D2          fs5
+#define REG_D3          fs6
+#define REG_D4          fs7
+
+#define MAX_REAL_FLOAT_REG   4
+#define MAX_REAL_DOUBLE_REG  4
+
 #else
 
 #error Cannot find platform to give register info for
diff --git a/rts/include/stg/MachRegsForHost.h b/rts/include/stg/MachRegsForHost.h
index 78f823d95c49e8d56a6dbeeccad3820ade79b942..6452df41581738ce4901fc52beb48cf8f7a15175 100644
--- a/rts/include/stg/MachRegsForHost.h
+++ b/rts/include/stg/MachRegsForHost.h
@@ -79,6 +79,10 @@
 #define MACHREGS_NO_REGS 1
 #endif
 
+#if defined(loongarch64_HOST_ARCH)
+#define MACHREGS_loongarch64  1
+#endif
+
 #endif
 
 #include "MachRegs.h"
diff --git a/rts/include/stg/SMP.h b/rts/include/stg/SMP.h
index b8f72a12481f33d78ce000622a0accd68152ceb5..aaa54e8435e4dde0239f1893a07372a5f29042fd 100644
--- a/rts/include/stg/SMP.h
+++ b/rts/include/stg/SMP.h
@@ -393,6 +393,8 @@ write_barrier(void) {
     __asm__ __volatile__ ("dmb  st" : : : "memory");
 #elif defined(riscv64_HOST_ARCH)
     __asm__ __volatile__ ("fence w,w" : : : "memory");
+#elif defined(loongarch64_HOST_ARCH)
+    __asm__ __volatile__ ("dbar 0" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
 #endif
@@ -417,6 +419,8 @@ store_load_barrier(void) {
     __asm__ __volatile__ ("dmb sy" : : : "memory");
 #elif defined(riscv64_HOST_ARCH)
     __asm__ __volatile__ ("fence w,r" : : : "memory");
+#elif defined(loongarch64_HOST_ARCH)
+    __asm__ __volatile__ ("dbar 0" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
 #endif
@@ -441,6 +445,8 @@ load_load_barrier(void) {
     __asm__ __volatile__ ("dmb ld" : : : "memory");
 #elif defined(riscv64_HOST_ARCH)
     __asm__ __volatile__ ("fence r,r" : : : "memory");
+#elif defined(loongarch64_HOST_ARCH)
+    __asm__ __volatile__ ("dbar 0" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
 #endif
diff --git a/rts/linker/Elf.c b/rts/linker/Elf.c
index bbcd8b4208243544b767327b4dc3190962f7710f..3595a4c3d4d0dfd03a6bc07c217a47f4ab56f798 100644
--- a/rts/linker/Elf.c
+++ b/rts/linker/Elf.c
@@ -416,6 +416,12 @@ ocVerifyImage_ELF ( ObjectCode* oc )
           errorBelch("%s: RTS linker not implemented on riscv",
                      oc->fileName);
           return 0;
+#endif
+#if defined(EM_LOONGARCH)
+      case EM_LOONGARCH:  IF_DEBUG(linker,debugBelch( "loongarch64" ));
+          errorBelch("%s: RTS linker not implemented on loongarch64",
+                     oc->fileName);
+          return 0;
 #endif
        default:       IF_DEBUG(linker,debugBelch( "unknown" ));
                      errorBelch("%s: unknown architecture (e_machine == %d)"
diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in
index 9cdaae0bbe31139576a320ea57c425ccf3dcd5e9..e4a78a64cfbdd57420c650569f0ca8614cfeb67e 100644
--- a/rts/rts.cabal.in
+++ b/rts/rts.cabal.in
@@ -516,7 +516,7 @@ library
           c-sources: adjustor/NativeIA64.c
 
       -- Use assembler STG entrypoint on architectures where it is used
-      if arch(ppc) || arch(ppc64) || arch(s390x) || arch(riscv64)
+      if arch(ppc) || arch(ppc64) || arch(s390x) || arch(riscv64) || arch(loongarch64)
         asm-sources: StgCRunAsm.S
 
       c-sources: Adjustor.c
diff --git a/testsuite/tests/count-deps/CountDepsAst.stdout b/testsuite/tests/count-deps/CountDepsAst.stdout
index 8db15009b198f0ed4acdb2537a928391073b93b1..c3b067c31ead453310b94ff9c9e9354001bfb36a 100644
--- a/testsuite/tests/count-deps/CountDepsAst.stdout
+++ b/testsuite/tests/count-deps/CountDepsAst.stdout
@@ -155,6 +155,7 @@ GHC.Platform
 GHC.Platform.AArch64
 GHC.Platform.ARM
 GHC.Platform.Constants
+GHC.Platform.LoongArch64
 GHC.Platform.NoRegs
 GHC.Platform.PPC
 GHC.Platform.Profile
diff --git a/testsuite/tests/count-deps/CountDepsParser.stdout b/testsuite/tests/count-deps/CountDepsParser.stdout
index 8e41f78ac512843c0e495d65e88aea165f16417c..8ff84fd40d4663f262b3073830c7a687b9e0228b 100644
--- a/testsuite/tests/count-deps/CountDepsParser.stdout
+++ b/testsuite/tests/count-deps/CountDepsParser.stdout
@@ -162,6 +162,7 @@ GHC.Platform
 GHC.Platform.AArch64
 GHC.Platform.ARM
 GHC.Platform.Constants
+GHC.Platform.LoongArch64
 GHC.Platform.NoRegs
 GHC.Platform.PPC
 GHC.Platform.Profile
diff --git a/utils/llvm-targets/gen-data-layout.sh b/utils/llvm-targets/gen-data-layout.sh
index 2a506b189dba9fca5e7b3be483170d7863f84d5b..e5ead7ddeb0d33107283419b8112bf97dec854cf 100755
--- a/utils/llvm-targets/gen-data-layout.sh
+++ b/utils/llvm-targets/gen-data-layout.sh
@@ -82,6 +82,9 @@ TARGETS=(
     # Linux riscv64
     "riscv64-unknown-linux-gnu"
     "riscv64-unknown-linux"
+    # Linux loongarch64
+    "loongarch64-unknown-linux-gnu"
+    "loongarch64-unknown-linux"
 
     #########################
     # Darwin