diff --git a/aclocal.m4 b/aclocal.m4
index 15cebfb18f51a8f6c190bc7a1e4ad5a654323347..be132387f2cbe3f45ed88ccc1643b808a6e8fc71 100644
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -229,7 +229,10 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS],
         mipsel)
             test -z "[$]2" || eval "[$]2=ArchMipsel"
             ;;
-        hppa|hppa1_1|ia64|m68k|nios2|riscv32|riscv64|rs6000|s390|sh4|vax)
+        riscv64)
+            test -z "[$]2" || eval "[$]2=ArchRISCV64"
+            ;;
+        hppa|hppa1_1|ia64|m68k|nios2|riscv32|rs6000|s390|sh4|vax)
             test -z "[$]2" || eval "[$]2=ArchUnknown"
             ;;
         *)
diff --git a/compiler/GHC/CmmToAsm.hs b/compiler/GHC/CmmToAsm.hs
index 5eda3f03a89429b1dbdea27294684d7506b67ef2..d331d63098b87e5d99267d7e9f7798ac6e195c07 100644
--- a/compiler/GHC/CmmToAsm.hs
+++ b/compiler/GHC/CmmToAsm.hs
@@ -168,6 +168,7 @@ nativeCodeGen logger dflags this_mod modLoc h us cmms
       ArchAlpha     -> panic "nativeCodeGen: No NCG for Alpha"
       ArchMipseb    -> panic "nativeCodeGen: No NCG for mipseb"
       ArchMipsel    -> panic "nativeCodeGen: No NCG for mipsel"
+      ArchRISCV64   -> panic "nativeCodeGen: No NCG for RISCV64"
       ArchUnknown   -> panic "nativeCodeGen: No NCG for unknown arch"
       ArchJavaScript-> panic "nativeCodeGen: No NCG for JavaScript"
 
diff --git a/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs b/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
index 105e2ebdf9cc2350f7b298d4353238fcda4442f4..07eca93ac3bed52dafa1c19b47a458dec48e7f2e 100644
--- a/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
@@ -120,6 +120,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl
                             ArchMipseb    -> panic "trivColorable ArchMipseb"
                             ArchMipsel    -> panic "trivColorable ArchMipsel"
                             ArchS390X     -> panic "trivColorable ArchS390X"
+                            ArchRISCV64   -> panic "trivColorable ArchRISCV64"
                             ArchJavaScript-> panic "trivColorable ArchJavaScript"
                             ArchUnknown   -> panic "trivColorable ArchUnknown")
         , count2        <- accSqueeze 0 cALLOCATABLE_REGS_INTEGER
@@ -151,6 +152,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus
                             ArchMipseb    -> panic "trivColorable ArchMipseb"
                             ArchMipsel    -> panic "trivColorable ArchMipsel"
                             ArchS390X     -> panic "trivColorable ArchS390X"
+                            ArchRISCV64   -> panic "trivColorable ArchRISCV64"
                             ArchJavaScript-> panic "trivColorable ArchJavaScript"
                             ArchUnknown   -> panic "trivColorable ArchUnknown")
         , count2        <- accSqueeze 0 cALLOCATABLE_REGS_FLOAT
@@ -184,6 +186,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu
                             ArchMipseb    -> panic "trivColorable ArchMipseb"
                             ArchMipsel    -> panic "trivColorable ArchMipsel"
                             ArchS390X     -> panic "trivColorable ArchS390X"
+                            ArchRISCV64   -> panic "trivColorable ArchRISCV64"
                             ArchJavaScript-> panic "trivColorable ArchJavaScript"
                             ArchUnknown   -> panic "trivColorable ArchUnknown")
         , count2        <- accSqueeze 0 cALLOCATABLE_REGS_DOUBLE
diff --git a/compiler/GHC/CmmToAsm/Reg/Linear.hs b/compiler/GHC/CmmToAsm/Reg/Linear.hs
index 4b44c14b6c2fc27cea823a52ab8d444986f84db4..b8159c0907ec80428a3e67bcc45a65fd831ccd7d 100644
--- a/compiler/GHC/CmmToAsm/Reg/Linear.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Linear.hs
@@ -228,6 +228,7 @@ linearRegAlloc config entry_ids block_live sccs
       ArchAlpha      -> panic "linearRegAlloc ArchAlpha"
       ArchMipseb     -> panic "linearRegAlloc ArchMipseb"
       ArchMipsel     -> panic "linearRegAlloc ArchMipsel"
+      ArchRISCV64    -> panic "linearRegAlloc ArchRISCV64"
       ArchJavaScript -> panic "linearRegAlloc ArchJavaScript"
       ArchUnknown    -> panic "linearRegAlloc ArchUnknown"
  where
diff --git a/compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs b/compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
index b89c056a82309573771c5a87d682e8befa210b42..1768422f5cb7152032c806197eb6b71b29c3aa5c 100644
--- a/compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
@@ -83,5 +83,6 @@ maxSpillSlots config = case platformArch (ncgPlatform config) of
    ArchAlpha     -> panic "maxSpillSlots ArchAlpha"
    ArchMipseb    -> panic "maxSpillSlots ArchMipseb"
    ArchMipsel    -> panic "maxSpillSlots ArchMipsel"
+   ArchRISCV64   -> panic "maxSpillSlots ArchRISCV64"
    ArchJavaScript-> panic "maxSpillSlots ArchJavaScript"
    ArchUnknown   -> panic "maxSpillSlots ArchUnknown"
diff --git a/compiler/GHC/CmmToAsm/Reg/Target.hs b/compiler/GHC/CmmToAsm/Reg/Target.hs
index 99baaa50fbb1367fcf84bb6ef26e5c865ce77abf..e93db955e75b09f7ab1d65a0979cac4fca9b57ad 100644
--- a/compiler/GHC/CmmToAsm/Reg/Target.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Target.hs
@@ -52,6 +52,7 @@ targetVirtualRegSqueeze platform
       ArchAlpha     -> panic "targetVirtualRegSqueeze ArchAlpha"
       ArchMipseb    -> panic "targetVirtualRegSqueeze ArchMipseb"
       ArchMipsel    -> panic "targetVirtualRegSqueeze ArchMipsel"
+      ArchRISCV64   -> panic "targetVirtualRegSqueeze ArchRISCV64"
       ArchJavaScript-> panic "targetVirtualRegSqueeze ArchJavaScript"
       ArchUnknown   -> panic "targetVirtualRegSqueeze ArchUnknown"
 
@@ -71,6 +72,7 @@ targetRealRegSqueeze platform
       ArchAlpha     -> panic "targetRealRegSqueeze ArchAlpha"
       ArchMipseb    -> panic "targetRealRegSqueeze ArchMipseb"
       ArchMipsel    -> panic "targetRealRegSqueeze ArchMipsel"
+      ArchRISCV64   -> panic "targetRealRegSqueeze ArchRISCV64"
       ArchJavaScript-> panic "targetRealRegSqueeze ArchJavaScript"
       ArchUnknown   -> panic "targetRealRegSqueeze ArchUnknown"
 
@@ -89,6 +91,7 @@ targetClassOfRealReg platform
       ArchAlpha     -> panic "targetClassOfRealReg ArchAlpha"
       ArchMipseb    -> panic "targetClassOfRealReg ArchMipseb"
       ArchMipsel    -> panic "targetClassOfRealReg ArchMipsel"
+      ArchRISCV64   -> panic "targetClassOfRealReg ArchRISCV64"
       ArchJavaScript-> panic "targetClassOfRealReg ArchJavaScript"
       ArchUnknown   -> panic "targetClassOfRealReg ArchUnknown"
 
@@ -107,6 +110,7 @@ targetMkVirtualReg platform
       ArchAlpha     -> panic "targetMkVirtualReg ArchAlpha"
       ArchMipseb    -> panic "targetMkVirtualReg ArchMipseb"
       ArchMipsel    -> panic "targetMkVirtualReg ArchMipsel"
+      ArchRISCV64   -> panic "targetMkVirtualReg ArchRISCV64"
       ArchJavaScript-> panic "targetMkVirtualReg ArchJavaScript"
       ArchUnknown   -> panic "targetMkVirtualReg ArchUnknown"
 
@@ -125,6 +129,7 @@ targetRegDotColor platform
       ArchAlpha     -> panic "targetRegDotColor ArchAlpha"
       ArchMipseb    -> panic "targetRegDotColor ArchMipseb"
       ArchMipsel    -> panic "targetRegDotColor ArchMipsel"
+      ArchRISCV64   -> panic "targetRegDotColor ArchRISCV64"
       ArchJavaScript-> panic "targetRegDotColor ArchJavaScript"
       ArchUnknown   -> panic "targetRegDotColor ArchUnknown"
 
diff --git a/compiler/GHC/Driver/Pipeline.hs b/compiler/GHC/Driver/Pipeline.hs
index e0367d08d448409d1b4458f683574af96ac2bbb9..f2e740ac4103448bb70938453574c7bce836fef2 100644
--- a/compiler/GHC/Driver/Pipeline.hs
+++ b/compiler/GHC/Driver/Pipeline.hs
@@ -1043,6 +1043,7 @@ llvmOptions dflags =
     ++ [("", "-mcpu=" ++ mcpu)   | not (null mcpu)
                                  , not (any (isInfixOf "-mcpu") (getOpts dflags opt_lc)) ]
     ++ [("", "-mattr=" ++ attrs) | not (null attrs) ]
+    ++ [("", "-target-abi=" ++ abi) | not (null abi) ]
 
   where target = platformMisc_llvmTarget $ platformMisc dflags
         Just (LlvmTarget _ mcpu mattr) = lookup target (llvmTargets $ llvmConfig dflags)
@@ -1074,6 +1075,11 @@ llvmOptions dflags =
               ++ ["+bmi"     | isBmiEnabled dflags      ]
               ++ ["+bmi2"    | isBmi2Enabled dflags     ]
 
+        abi :: String
+        abi = case platformArch (targetPlatform dflags) of
+                ArchRISCV64 -> "lp64d"
+                _           -> ""
+
 -- -----------------------------------------------------------------------------
 -- | Each phase in the pipeline returns the next phase to execute, and the
 -- name of the file in which the output was placed.
diff --git a/compiler/GHC/Platform/RISCV64.hs b/compiler/GHC/Platform/RISCV64.hs
new file mode 100644
index 0000000000000000000000000000000000000000..88754d48380d3b81d96f1df5c585b7c9ec0f51c6
--- /dev/null
+++ b/compiler/GHC/Platform/RISCV64.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE CPP #-}
+
+module GHC.Platform.RISCV64 where
+
+import GHC.Prelude
+
+#define MACHREGS_NO_REGS 0
+#define MACHREGS_riscv64 1
+#include "../../../includes/CodeGen.Platform.hs"
+
diff --git a/compiler/GHC/Platform/Regs.hs b/compiler/GHC/Platform/Regs.hs
index 1bf21370c7da945c11d8eb2fa54cf3fe1bbfa827..e0bdf5d6e50bc7b1802308004f8b7c6f5e757849 100644
--- a/compiler/GHC/Platform/Regs.hs
+++ b/compiler/GHC/Platform/Regs.hs
@@ -15,6 +15,7 @@ import qualified GHC.Platform.S390X      as S390X
 import qualified GHC.Platform.SPARC      as SPARC
 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.NoRegs     as NoRegs
 
 -- | Returns 'True' if this global register is stored in a caller-saves
@@ -31,6 +32,7 @@ callerSaves platform
    ArchSPARC   -> SPARC.callerSaves
    ArchARM {}  -> ARM.callerSaves
    ArchAArch64 -> AArch64.callerSaves
+   ArchRISCV64 -> RISCV64.callerSaves
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.callerSaves
@@ -53,6 +55,7 @@ activeStgRegs platform
    ArchSPARC   -> SPARC.activeStgRegs
    ArchARM {}  -> ARM.activeStgRegs
    ArchAArch64 -> AArch64.activeStgRegs
+   ArchRISCV64 -> RISCV64.activeStgRegs
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.activeStgRegs
@@ -70,6 +73,7 @@ haveRegBase platform
    ArchSPARC   -> SPARC.haveRegBase
    ArchARM {}  -> ARM.haveRegBase
    ArchAArch64 -> AArch64.haveRegBase
+   ArchRISCV64 -> RISCV64.haveRegBase
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.haveRegBase
@@ -87,6 +91,7 @@ globalRegMaybe platform
    ArchSPARC   -> SPARC.globalRegMaybe
    ArchARM {}  -> ARM.globalRegMaybe
    ArchAArch64 -> AArch64.globalRegMaybe
+   ArchRISCV64 -> RISCV64.globalRegMaybe
    arch
     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
         PPC.globalRegMaybe
@@ -104,6 +109,7 @@ freeReg platform
    ArchSPARC   -> SPARC.freeReg
    ArchARM {}  -> ARM.freeReg
    ArchAArch64 -> AArch64.freeReg
+   ArchRISCV64 -> RISCV64.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 8e479fa1980b0be38d8a1e7ab5fc17b735867130..cb1ba59db9e9aabfff88162b108f834c05433d7b 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -492,6 +492,7 @@ Library
         GHC.Platform.Reg
         GHC.Platform.Reg.Class
         GHC.Platform.Regs
+        GHC.Platform.RISCV64
         GHC.Platform.S390X
         GHC.Platform.SPARC
         GHC.Platform.Ways
diff --git a/configure.ac b/configure.ac
index 9fdb312f970f72d7b378890404d376c99caf82d1..fcf74567d343939459cc640f3256ba3ee22bb18b 100644
--- a/configure.ac
+++ b/configure.ac
@@ -284,7 +284,7 @@ dnl --------------------------------------------------------------
 
 AC_MSG_CHECKING(whether target supports a registerised ABI)
 case "$TargetArch" in
-    i386|x86_64|powerpc|powerpc64|powerpc64le|s390x|arm|aarch64)
+    i386|x86_64|powerpc|powerpc64|powerpc64le|s390x|arm|aarch64|riscv64)
         UnregisterisedDefault=NO
         AC_MSG_RESULT([yes])
         ;;
@@ -319,7 +319,7 @@ AC_MSG_CHECKING(whether target supports tables next to code)
 case "$Unregisterised" in
     NO)
         case "$TargetArch" in
-            ia64|powerpc64|powerpc64le|s390x)
+            ia64|powerpc64|powerpc64le|s390x|riscv64)
                 TablesNextToCodeDefault=NO
                 AC_MSG_RESULT([no])
                 ;;
@@ -348,7 +348,7 @@ AC_SUBST(TablesNextToCode)
 dnl ** Does target have runtime linker support?
 dnl --------------------------------------------------------------
 case "$target" in
-    powerpc64-*|powerpc64le-*|powerpc-ibm-aix*|s390x-ibm-linux)
+    powerpc64-*|powerpc64le-*|powerpc-ibm-aix*|s390x-ibm-linux|riscv64-*)
         TargetHasRTSLinker=NO
         ;;
     *)
diff --git a/hadrian/src/Oracles/Flag.hs b/hadrian/src/Oracles/Flag.hs
index 960036fa898c0568af56c494c3d6a5903790e85c..86521e4aa8a7908c1fee921b6ea71112df5617a6 100644
--- a/hadrian/src/Oracles/Flag.hs
+++ b/hadrian/src/Oracles/Flag.hs
@@ -70,7 +70,7 @@ targetSupportsSMP :: Action Bool
 targetSupportsSMP = do
   unreg <- flag GhcUnregisterised
   armVer <- targetArmVersion
-  goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc", "arm", "aarch64", "s390x"]
+  goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc", "arm", "aarch64", "s390x", "riscv64"]
   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/includes/CodeGen.Platform.hs b/includes/CodeGen.Platform.hs
index b00acfa38a1bdacdd5db7c0dd5cf690c28ae7bda..8c942662e6b0bad7a6ae573df1395c0daf870edf 100644
--- a/includes/CodeGen.Platform.hs
+++ b/includes/CodeGen.Platform.hs
@@ -380,6 +380,74 @@ import GHC.Platform.Reg
 # define f14 30
 # define f15 31
 
+#elif defined(MACHREGS_riscv64)
+
+# define zero 0
+# define ra   1
+# define sp   2
+# define gp   3
+# define tp   4
+# define t0   5
+# define t1   6
+# define t2   7
+# define s0   8
+# define s1   9
+# define a0  10
+# define a1  11
+# define a2  12
+# define a3  13
+# define a4  14
+# define a5  15
+# define a6  16
+# define a7  17
+# define s2  18
+# define s3  19
+# define s4  20
+# define s5  21
+# define s6  22
+# define s7  23
+# define s8  24
+# define s9  25
+# define s10 26
+# define s11 27
+# define t3  28
+# define t4  29
+# define t5  30
+# define t6  31
+
+# define ft0  32
+# define ft1  33
+# define ft2  34
+# define ft3  35
+# define ft4  36
+# define ft5  37
+# define ft6  38
+# define ft7  39
+# define fs0  40
+# define fs1  41
+# define fa0  42
+# define fa1  43
+# define fa2  44
+# define fa3  45
+# define fa4  46
+# define fa5  47
+# define fa6  48
+# define fa7  49
+# define fs2  50
+# define fs3  51
+# define fs4  52
+# define fs5  53
+# define fs6  54
+# define fs7  55
+# define fs8  56
+# define fs9  57
+# define fs10 58
+# define fs11 59
+# define ft8  60
+# define ft9  61
+# define ft10 62
+# define ft11 63
+
 #endif
 
 callerSaves :: GlobalReg -> Bool
@@ -667,7 +735,7 @@ globalRegMaybe :: GlobalReg -> Maybe RealReg
 #if defined(MACHREGS_i386) || defined(MACHREGS_x86_64) \
     || defined(MACHREGS_sparc) || defined(MACHREGS_powerpc) \
     || defined(MACHREGS_arm) || defined(MACHREGS_aarch64) \
-    || defined(MACHREGS_s390x)
+    || defined(MACHREGS_s390x) || defined(MACHREGS_riscv64)
 # if defined(REG_Base)
 globalRegMaybe BaseReg                  = Just (RealRegSingle REG_Base)
 # endif
diff --git a/includes/stg/MachRegs.h b/includes/stg/MachRegs.h
index a04452e0e7fcb841b25ad7c47eb34cd0dfda7c21..4b0991891ec15b77c6451a3982cf0207e297307e 100644
--- a/includes/stg/MachRegs.h
+++ b/includes/stg/MachRegs.h
@@ -663,6 +663,68 @@ the stack. See Note [Overlapping global registers] for implications.
 #define CALLER_SAVES_D5
 #define CALLER_SAVES_D6
 
+/* -----------------------------------------------------------------------------
+   The riscv64 register mapping
+
+   Register    | Role(s)                                 | Call effect
+   ------------+-----------------------------------------+-------------
+   zero        | Hard-wired zero                         | -
+   ra          | Return address                          | caller-saved
+   sp          | Stack pointer                           | callee-saved
+   gp          | Global pointer                          | callee-saved
+   tp          | Thread pointer                          | callee-saved
+   t0,t1,t2    | -                                       | caller-saved
+   s0          | Frame pointer                           | callee-saved
+   s1          | -                                       | callee-saved
+   a0,a1       | Arguments / return values               | caller-saved
+   a2..a7      | Arguments                               | caller-saved
+   s2..s11     | -                                       | callee-saved
+   t3..t6      | -                                       | caller-saved
+   ft0..ft7    | -                                       | caller-saved
+   fs0,fs1     | -                                       | callee-saved
+   fa0,fa1     | Arguments / return values               | caller-saved
+   fa2..fa7    | Arguments                               | caller-saved
+   fs2..fs11   | -                                       | callee-saved
+   ft8..ft11   | -                                       | caller-saved
+
+   Each general purpose register as well as each floating-point
+   register is 64 bits wide.
+
+   -------------------------------------------------------------------------- */
+
+#elif defined(MACHREGS_riscv64)
+
+#define REG(x) __asm__(#x)
+
+#define REG_Base        s1
+#define REG_Sp          s2
+#define REG_Hp          s3
+#define REG_R1          s4
+#define REG_R2          s5
+#define REG_R3          s6
+#define REG_R4          s7
+#define REG_R5          s8
+#define REG_R6          s9
+#define REG_R7          s10
+#define REG_SpLim       s11
+
+#define REG_F1          fs0
+#define REG_F2          fs1
+#define REG_F3          fs2
+#define REG_F4          fs3
+#define REG_F5          fs4
+#define REG_F6          fs5
+
+#define REG_D1          fs6
+#define REG_D2          fs7
+#define REG_D3          fs8
+#define REG_D4          fs9
+#define REG_D5          fs10
+#define REG_D6          fs11
+
+#define MAX_REAL_FLOAT_REG   6
+#define MAX_REAL_DOUBLE_REG  6
+
 #else
 
 #error Cannot find platform to give register info for
diff --git a/includes/stg/MachRegsForHost.h b/includes/stg/MachRegsForHost.h
index 3597b2be9010772e156ccd97fdf6db5832210228..e902d528f6c22f05f9f14025f374df7702a962d3 100644
--- a/includes/stg/MachRegsForHost.h
+++ b/includes/stg/MachRegsForHost.h
@@ -71,6 +71,10 @@
 #define MACHREGS_s390x    1
 #endif
 
+#if defined(riscv64_HOST_ARCH)
+#define MACHREGS_riscv64  1
+#endif
+
 #endif
 
 #include "MachRegs.h"
diff --git a/includes/stg/SMP.h b/includes/stg/SMP.h
index 589bde82667e6465688541a0fb753aba27529baa..57eb618592079263b040b0884b6ec01d991974ba 100644
--- a/includes/stg/SMP.h
+++ b/includes/stg/SMP.h
@@ -395,6 +395,8 @@ write_barrier(void) {
     __asm__ __volatile__ ("" : : : "memory");
 #elif defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)
     __asm__ __volatile__ ("dmb  st" : : : "memory");
+#elif defined(riscv64_HOST_ARCH)
+    __asm__ __volatile__ ("fence w,w" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
 #endif
@@ -419,6 +421,8 @@ store_load_barrier(void) {
     __asm__ __volatile__ ("dmb" : : : "memory");
 #elif defined(aarch64_HOST_ARCH)
     __asm__ __volatile__ ("dmb sy" : : : "memory");
+#elif defined(riscv64_HOST_ARCH)
+    __asm__ __volatile__ ("fence w,r" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
 #endif
@@ -444,6 +448,8 @@ load_load_barrier(void) {
     __asm__ __volatile__ ("dmb" : : : "memory");
 #elif defined(aarch64_HOST_ARCH)
     __asm__ __volatile__ ("dmb sy" : : : "memory");
+#elif defined(riscv64_HOST_ARCH)
+    __asm__ __volatile__ ("fence w,r" : : : "memory");
 #else
 #error memory barriers unimplemented on this architecture
 #endif
diff --git a/libraries/ghc-boot/GHC/Platform/ArchOS.hs b/libraries/ghc-boot/GHC/Platform/ArchOS.hs
index 2f641739bdda674ac2d35383609de17c1a90d9ff..55c22fb1680aabb6331bbe18598bee34b62210e2 100644
--- a/libraries/ghc-boot/GHC/Platform/ArchOS.hs
+++ b/libraries/ghc-boot/GHC/Platform/ArchOS.hs
@@ -45,6 +45,7 @@ data Arch
    | ArchAlpha
    | ArchMipseb
    | ArchMipsel
+   | ArchRISCV64
    | ArchJavaScript
    deriving (Read, Show, Eq)
 
@@ -134,6 +135,7 @@ stringEncodeArch = \case
   ArchAlpha         -> "alpha"
   ArchMipseb        -> "mipseb"
   ArchMipsel        -> "mipsel"
+  ArchRISCV64       -> "riscv64"
   ArchJavaScript    -> "js"
 
 -- | See Note [Platform Syntax].
diff --git a/llvm-targets b/llvm-targets
index e259ca29c59993e1ed87cdc2e8600123b7a78304..9ea787d6b119190e808c9229c0b957050ff7a0ab 100644
--- a/llvm-targets
+++ b/llvm-targets
@@ -38,6 +38,8 @@
 ,("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", ""))
+,("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"))
 ,("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"))
diff --git a/mk/config.mk.in b/mk/config.mk.in
index e2c15918603073d40202883e5a40c468b07621a7..9e6c3d8c4055b3caeb95527781e1b262edd75961 100644
--- a/mk/config.mk.in
+++ b/mk/config.mk.in
@@ -179,7 +179,7 @@ ifeq "$(TargetArch_CPP)" "arm"
 # We don't support load/store barriers pre-ARMv7. See #10433.
 ArchSupportsSMP=$(if $(filter $(ARM_ISA),ARMv5 ARMv6),NO,YES)
 else
-ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc powerpc64 powerpc64le s390x aarch64)))
+ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc powerpc64 powerpc64le s390x aarch64 riscv64)))
 endif
 
 # The THREADED_RTS requires `BaseReg` to be in a register and the
diff --git a/rts/StgCRunAsm.S b/rts/StgCRunAsm.S
index 60f1bf9a13b7ede07672661f7f641298cdbae426..aed3241d12a2243c8995ae60074c1dcdb5e5edc8 100644
--- a/rts/StgCRunAsm.S
+++ b/rts/StgCRunAsm.S
@@ -231,6 +231,150 @@ StgReturn:
 	.cfi_endproc
 	.size StgReturn, .-StgReturn
 
+	.section	.note.GNU-stack,"",@progbits
+
+#elif defined(riscv64_HOST_ARCH)
+# define STACK_FRAME_SIZE (RESERVED_C_STACK_BYTES+208)
+	.text
+	.align 1
+	.globl StgRun
+	.type StgRun, @function
+StgRun:
+	.cfi_startproc
+	addi	sp,sp,-208
+	.cfi_def_cfa_offset 208
+	/* save callee-saved registers plus ra */
+	sd	ra,200(sp)
+	sd	s0,192(sp)
+	sd	s1,184(sp)
+	sd	s2,176(sp)
+	sd	s3,168(sp)
+	sd	s4,160(sp)
+	sd	s5,152(sp)
+	sd	s6,144(sp)
+	sd	s7,136(sp)
+	sd	s8,128(sp)
+	sd	s9,120(sp)
+	sd	s10,112(sp)
+	sd	s11,104(sp)
+	fsd	fs0,88(sp)
+	fsd	fs1,80(sp)
+	fsd	fs2,72(sp)
+	fsd	fs3,64(sp)
+	fsd	fs4,56(sp)
+	fsd	fs5,48(sp)
+	fsd	fs6,40(sp)
+	fsd	fs7,32(sp)
+	fsd	fs8,24(sp)
+	fsd	fs9,16(sp)
+	fsd	fs10,8(sp)
+	fsd	fs11,0(sp)
+	/* allocate stack frame */
+	li	t0,RESERVED_C_STACK_BYTES
+	sub	sp,sp,t0
+	.cfi_def_cfa_offset STACK_FRAME_SIZE
+	.cfi_offset 1, -8
+	.cfi_offset 8, -16
+	.cfi_offset 9, -24
+	.cfi_offset 18, -32
+	.cfi_offset 19, -40
+	.cfi_offset 20, -48
+	.cfi_offset 21, -56
+	.cfi_offset 22, -64
+	.cfi_offset 23, -72
+	.cfi_offset 24, -80
+	.cfi_offset 25, -88
+	.cfi_offset 26, -96
+	.cfi_offset 27, -104
+	.cfi_offset 40, -120
+	.cfi_offset 41, -128
+	.cfi_offset 50, -136
+	.cfi_offset 51, -144
+	.cfi_offset 52, -152
+	.cfi_offset 53, -160
+	.cfi_offset 54, -168
+	.cfi_offset 55, -176
+	.cfi_offset 56, -184
+	.cfi_offset 57, -192
+	.cfi_offset 58, -200
+	.cfi_offset 59, -208
+	/* set STGs BaseReg from RISCV a1 */
+	mv	s1,a1
+	/* jump to STG function */
+	jr	a0
+	.cfi_endproc
+	.size StgRun, .-StgRun
+
+	.text
+	.align 1
+	.globl StgReturn
+	.type StgReturn, @function
+StgReturn:
+	.cfi_startproc
+	/* set return value from STGs R1 (RISCV s4) */
+	mv	a0,s4
+	/* deallocate stack frame */
+	li	t0,RESERVED_C_STACK_BYTES
+	add	sp,sp,t0
+	.cfi_def_cfa_offset 208
+	/* restore callee-saved registers and ra */
+	ld	ra,200(sp)
+	.cfi_restore 1
+	ld	s0,192(sp)
+	.cfi_restore 8
+	ld	s1,184(sp)
+	.cfi_restore 9
+	ld	s2,176(sp)
+	.cfi_restore 18
+	ld	s3,168(sp)
+	.cfi_restore 19
+	ld	s4,160(sp)
+	.cfi_restore 20
+	ld	s5,152(sp)
+	.cfi_restore 21
+	ld	s6,144(sp)
+	.cfi_restore 22
+	ld	s7,136(sp)
+	.cfi_restore 23
+	ld	s8,128(sp)
+	.cfi_restore 24
+	ld	s9,120(sp)
+	.cfi_restore 25
+	ld	s10,112(sp)
+	.cfi_restore 26
+	ld	s11,104(sp)
+	.cfi_restore 27
+	fld	fs0,88(sp)
+	.cfi_restore 40
+	fld	fs1,80(sp)
+	.cfi_restore 41
+	fld	fs2,72(sp)
+	.cfi_restore 50
+	fld	fs3,64(sp)
+	.cfi_restore 51
+	fld	fs4,56(sp)
+	.cfi_restore 52
+	fld	fs5,48(sp)
+	.cfi_restore 53
+	fld	fs6,40(sp)
+	.cfi_restore 54
+	fld	fs7,32(sp)
+	.cfi_restore 55
+	fld	fs8,24(sp)
+	.cfi_restore 56
+	fld	fs9,16(sp)
+	.cfi_restore 57
+	fld	fs10,8(sp)
+	.cfi_restore 58
+	fld	fs11,0(sp)
+	.cfi_restore 59
+	addi	sp,sp,208
+	.cfi_def_cfa_offset 0
+	/* jump back to caller of StgRun() */
+	ret
+	.cfi_endproc
+	.size StgReturn, .-StgReturn
+
 	.section	.note.GNU-stack,"",@progbits
 #endif
 
diff --git a/rts/ghc.mk b/rts/ghc.mk
index 32c49d90990d7c11c31571cbb2dd99fbc879bd1a..010146ce8a33fc5eb8f576d29a99d0e8a42952a7 100644
--- a/rts/ghc.mk
+++ b/rts/ghc.mk
@@ -55,7 +55,7 @@ ifneq "$(findstring $(TargetArch_CPP), i386 powerpc powerpc64)" ""
 rts_S_SRCS += rts/AdjustorAsm.S
 endif
 # this matches substrings of powerpc64le, including "powerpc" and "powerpc64"
-ifneq "$(findstring $(TargetArch_CPP), powerpc64le s390x)" ""
+ifneq "$(findstring $(TargetArch_CPP), powerpc64le s390x riscv64)" ""
 # unregisterised builds use the mini interpreter
 ifneq "$(GhcUnregisterised)" "YES"
 rts_S_SRCS += rts/StgCRunAsm.S
diff --git a/rts/linker/Elf.c b/rts/linker/Elf.c
index 9aaaedc0b2c9a3448383e42ed946a312a23cee22..8037d52b7ca0af868d8c27e71dc391ed81fa68ce 100644
--- a/rts/linker/Elf.c
+++ b/rts/linker/Elf.c
@@ -413,6 +413,12 @@ ocVerifyImage_ELF ( ObjectCode* oc )
 #endif
 #if defined(EM_AARCH64)
       case EM_AARCH64: IF_DEBUG(linker,debugBelch( "aarch64" )); break;
+#endif
+#if defined(EM_RISCV)
+      case EM_RISCV:  IF_DEBUG(linker,debugBelch( "riscv" ));
+          errorBelch("%s: RTS linker not implemented on riscv",
+                     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 427c78c40f52356c079bfa32ed0ce06a53cda43d..3b42544116ee61c16b20d2c3128026cfe7cd494d 100644
--- a/rts/rts.cabal.in
+++ b/rts/rts.cabal.in
@@ -417,7 +417,7 @@ library
 
     if arch(i386) || arch(ppc) || arch(ppc64)
        asm-sources: AdjustorAsm.S
-    if arch(ppc) || arch(ppc64) || arch(s390x)
+    if arch(ppc) || arch(ppc64) || arch(s390x) || arch(riscv64)
        asm-sources: StgCRunAsm.S
 
     c-sources: Adjustor.c
diff --git a/testsuite/tests/parser/should_run/CountAstDeps.stdout b/testsuite/tests/parser/should_run/CountAstDeps.stdout
index a825c2bac7e626fb4b6ebce40bd533b7fedb5955..7553cdc3e309a7dbf3c564370c9dbd5ebe01bdda 100644
--- a/testsuite/tests/parser/should_run/CountAstDeps.stdout
+++ b/testsuite/tests/parser/should_run/CountAstDeps.stdout
@@ -1,4 +1,4 @@
-Found 241 Language.Haskell.Syntax module dependencies
+Found 242 Language.Haskell.Syntax module dependencies
 GHC.Builtin.Names
 GHC.Builtin.PrimOps
 GHC.Builtin.Types
@@ -114,6 +114,7 @@ GHC.Platform.Constants
 GHC.Platform.NoRegs
 GHC.Platform.PPC
 GHC.Platform.Profile
+GHC.Platform.RISCV64
 GHC.Platform.Reg
 GHC.Platform.Reg.Class
 GHC.Platform.Regs
diff --git a/testsuite/tests/parser/should_run/CountParserDeps.stdout b/testsuite/tests/parser/should_run/CountParserDeps.stdout
index e27ba93846302a26e615436b92e1756fd694c23f..c79c839f0a28bd044fabd05e1b2da5326a358790 100644
--- a/testsuite/tests/parser/should_run/CountParserDeps.stdout
+++ b/testsuite/tests/parser/should_run/CountParserDeps.stdout
@@ -1,4 +1,4 @@
-Found 249 GHC.Parser module dependencies
+Found 250 GHC.Parser module dependencies
 GHC.Builtin.Names
 GHC.Builtin.PrimOps
 GHC.Builtin.Types
@@ -122,6 +122,7 @@ GHC.Platform.Constants
 GHC.Platform.NoRegs
 GHC.Platform.PPC
 GHC.Platform.Profile
+GHC.Platform.RISCV64
 GHC.Platform.Reg
 GHC.Platform.Reg.Class
 GHC.Platform.Regs
diff --git a/utils/llvm-targets/gen-data-layout.sh b/utils/llvm-targets/gen-data-layout.sh
index 32032cb97e3ecded78d85e09c8506b4a875f843e..092e0892e5329620b2149ed9ac83bda404fb4bf1 100755
--- a/utils/llvm-targets/gen-data-layout.sh
+++ b/utils/llvm-targets/gen-data-layout.sh
@@ -76,6 +76,9 @@ TARGETS=(
     "powerpc64le-unknown-linux"
     # Linux s390x
     "s390x-ibm-linux"
+    # Linux riscv64
+    "riscv64-unknown-linux-gnu"
+    "riscv64-unknown-linux"
 
     #########################
     # Darwin