diff --git a/Cabal/Distribution/PackageDescription/FieldGrammar.hs b/Cabal/Distribution/PackageDescription/FieldGrammar.hs
index 285a01b5e45aa2f2946c98cb8a33e0c6be4b7a90..5a7fc41f67c58f31a4f108c1cebd408dbeeee128 100644
--- a/Cabal/Distribution/PackageDescription/FieldGrammar.hs
+++ b/Cabal/Distribution/PackageDescription/FieldGrammar.hs
@@ -390,7 +390,9 @@ buildInfoFieldGrammar = BuildInfo
         -- I.e. we don't want trigger unknown field warning
     <*> monoidalFieldAla "cpp-options"          (alaList' NoCommaFSep Token') L.cppOptions
     <*> monoidalFieldAla "asm-options"          (alaList' NoCommaFSep Token') L.asmOptions
+        ^^^ availableSince CabalSpecV3_0 []
     <*> monoidalFieldAla "cmm-options"          (alaList' NoCommaFSep Token') L.cmmOptions
+        ^^^ availableSince CabalSpecV3_0 []
     <*> monoidalFieldAla "cc-options"           (alaList' NoCommaFSep Token') L.ccOptions
     <*> monoidalFieldAla "cxx-options"          (alaList' NoCommaFSep Token') L.cxxOptions
         ^^^ availableSince CabalSpecV2_2 []
@@ -399,7 +401,9 @@ buildInfoFieldGrammar = BuildInfo
     <*> monoidalFieldAla "frameworks"           (alaList' FSep Token)         L.frameworks
     <*> monoidalFieldAla "extra-framework-dirs" (alaList' FSep FilePathNT)    L.extraFrameworkDirs
     <*> monoidalFieldAla "asm-sources"          (alaList' VCat FilePathNT)    L.asmSources
+        ^^^ availableSince CabalSpecV3_0 []
     <*> monoidalFieldAla "cmm-sources"          (alaList' VCat FilePathNT)    L.cmmSources
+        ^^^ availableSince CabalSpecV3_0 []
     <*> monoidalFieldAla "c-sources"            (alaList' VCat FilePathNT)    L.cSources
     <*> monoidalFieldAla "cxx-sources"          (alaList' VCat FilePathNT)    L.cxxSources
         ^^^ availableSince CabalSpecV2_2 []
diff --git a/Cabal/Distribution/Simple/Build.hs b/Cabal/Distribution/Simple/Build.hs
index 331c367d8ded53d8726f7b675f63ef0677a1c85d..f8039fa86dbdb886341bf7eb6f0b321298c61dd6 100644
--- a/Cabal/Distribution/Simple/Build.hs
+++ b/Cabal/Distribution/Simple/Build.hs
@@ -216,7 +216,13 @@ buildComponent verbosity numJobs pkg_descr lbi suffixes
     setupMessage' verbosity "Building" (packageId pkg_descr)
       (componentLocalName clbi) (maybeComponentInstantiatedWith clbi)
     let libbi = libBuildInfo lib
-        lib' = lib { libBuildInfo = addExtraCxxSources (addExtraCSources libbi extras) extras }
+        lib' = lib { libBuildInfo = flip addExtraAsmSources extras
+                                  $ flip addExtraCmmSources extras
+                                  $ flip addExtraCxxSources extras
+                                  $ flip addExtraCSources   extras
+                                  $ libbi
+                   }
+
     buildLib verbosity numJobs pkg_descr lbi lib' clbi
 
     let oneComponentRequested (OneComponentRequestedSpec _) = True
@@ -356,6 +362,24 @@ addExtraCxxSources bi extras = bi { cxxSources = new }
         exs = Set.fromList extras
 
 
+-- | Add extra C-- sources generated by preprocessing to build
+-- information.
+addExtraCmmSources :: BuildInfo -> [FilePath] -> BuildInfo
+addExtraCmmSources bi extras = bi { cmmSources = new }
+  where new = Set.toList $ old `Set.union` exs
+        old = Set.fromList $ cmmSources bi
+        exs = Set.fromList extras
+
+
+-- | Add extra ASM sources generated by preprocessing to build
+-- information.
+addExtraAsmSources :: BuildInfo -> [FilePath] -> BuildInfo
+addExtraAsmSources bi extras = bi { asmSources = new }
+  where new = Set.toList $ old `Set.union` exs
+        old = Set.fromList $ asmSources bi
+        exs = Set.fromList extras
+
+
 replComponent :: [String]
               -> Verbosity
               -> PackageDescription
diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs
index 67a5c2d4d5c41e1c9a36df63be3eac2141baeed0..3b4b96b066c3acbaaaa5eb28f7af792a441b2633 100644
--- a/Cabal/Distribution/Simple/GHC.hs
+++ b/Cabal/Distribution/Simple/GHC.hs
@@ -545,8 +545,12 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
   createDirectoryIfMissingVerbose verbosity True libTargetDir
   -- TODO: do we need to put hs-boot files into place for mutually recursive
   -- modules?
-  let cLikeFiles  = fromNubListR $
-                    toNubListR (cSources libBi) <> toNubListR (cxxSources libBi)
+  let cLikeFiles  = fromNubListR $ mconcat
+                      [ toNubListR (cSources   libBi)
+                      , toNubListR (cxxSources libBi)
+                      , toNubListR (cmmSources libBi)
+                      , toNubListR (asmSources libBi)
+                      ]
       cObjs       = map (`replaceExtension` objExtension) cLikeFiles
       baseOpts    = componentGhcOptions verbosity lbi libBi clbi libTargetDir
       vanillaOpts = baseOpts `mappend` mempty {
@@ -667,7 +671,6 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
     ifReplLib (runGhcProg replOpts)
 
   -- build any C sources
-  -- TODO: Add support for S and CMM files.
   unless (not has_code || null (cSources libBi)) $ do
     info verbosity "Building C Sources..."
     sequence_
@@ -698,6 +701,68 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
            unless forRepl $ whenProfLib (runGhcProgIfNeeded profCcOpts)
       | filename <- cSources libBi]
 
+  -- build any ASM sources
+  unless (not has_code || null (asmSources libBi)) $ do
+    info verbosity "Building Assembler Sources..."
+    sequence_
+      [ do let baseAsmOpts    = Internal.componentAsmGhcOptions verbosity implInfo
+                                lbi libBi clbi libTargetDir filename
+               vanillaAsmOpts = if isGhcDynamic
+                                -- Dynamic GHC requires objects to be built
+                                -- with -fPIC for REPL to work. See #2207.
+                                then baseAsmOpts { ghcOptFPic = toFlag True }
+                                else baseAsmOpts
+               profAsmOpts    = vanillaAsmOpts `mappend` mempty {
+                                 ghcOptProfilingMode = toFlag True,
+                                 ghcOptObjSuffix     = toFlag "p_o"
+                               }
+               sharedAsmOpts  = vanillaAsmOpts `mappend` mempty {
+                                 ghcOptFPic        = toFlag True,
+                                 ghcOptDynLinkMode = toFlag GhcDynamicOnly,
+                                 ghcOptObjSuffix   = toFlag "dyn_o"
+                               }
+               odir           = fromFlag (ghcOptObjDir vanillaAsmOpts)
+           createDirectoryIfMissingVerbose verbosity True odir
+           let runGhcProgIfNeeded asmOpts = do
+                 needsRecomp <- checkNeedsRecompilation filename asmOpts
+                 when needsRecomp $ runGhcProg asmOpts
+           runGhcProgIfNeeded vanillaAsmOpts
+           unless forRepl $
+             whenSharedLib forceSharedLib (runGhcProgIfNeeded sharedAsmOpts)
+           unless forRepl $ whenProfLib (runGhcProgIfNeeded profAsmOpts)
+      | filename <- asmSources libBi]
+
+  -- build any Cmm sources
+  unless (not has_code || null (cmmSources libBi)) $ do
+    info verbosity "Building C-- Sources..."
+    sequence_
+      [ do let baseCmmOpts    = Internal.componentCmmGhcOptions verbosity implInfo
+                                lbi libBi clbi libTargetDir filename
+               vanillaCmmOpts = if isGhcDynamic
+                                -- Dynamic GHC requires C sources to be built
+                                -- with -fPIC for REPL to work. See #2207.
+                                then baseCmmOpts { ghcOptFPic = toFlag True }
+                                else baseCmmOpts
+               profCmmOpts    = vanillaCmmOpts `mappend` mempty {
+                                 ghcOptProfilingMode = toFlag True,
+                                 ghcOptObjSuffix     = toFlag "p_o"
+                               }
+               sharedCmmOpts  = vanillaCmmOpts `mappend` mempty {
+                                 ghcOptFPic        = toFlag True,
+                                 ghcOptDynLinkMode = toFlag GhcDynamicOnly,
+                                 ghcOptObjSuffix   = toFlag "dyn_o"
+                               }
+               odir          = fromFlag (ghcOptObjDir vanillaCmmOpts)
+           createDirectoryIfMissingVerbose verbosity True odir
+           let runGhcProgIfNeeded cmmOpts = do
+                 needsRecomp <- checkNeedsRecompilation filename cmmOpts
+                 when needsRecomp $ runGhcProg cmmOpts
+           runGhcProgIfNeeded vanillaCmmOpts
+           unless forRepl $
+             whenSharedLib forceSharedLib (runGhcProgIfNeeded sharedCmmOpts)
+           unless forRepl $ whenProfLib (runGhcProgIfNeeded profCmmOpts)
+      | filename <- cmmSources libBi]
+
   -- TODO: problem here is we need the .c files built first, so we can load them
   -- with ghci, but .c files can depend on .h files generated by ghc by ffi
   -- exports.
@@ -1932,6 +1997,8 @@ installLib verbosity lbi targetDir dynlibTargetDir _builtDir pkg lib clbi = do
     hasLib    = not $ null (allLibModules lib clbi)
                    && null (cSources (libBuildInfo lib))
                    && null (cxxSources (libBuildInfo lib))
+                   && null (cmmSources (libBuildInfo lib))
+                   && null (asmSources (libBuildInfo lib))
     has_code = not (componentIsIndefinite clbi)
     whenHasCode = when has_code
     whenVanilla = when (hasLib && withVanillaLib lbi)
diff --git a/Cabal/Distribution/Simple/GHC/Internal.hs b/Cabal/Distribution/Simple/GHC/Internal.hs
index 4be581132d775627629663eda16864e5a8ed01df..aa1b791a67f7f0560f78030c8fbe0d4b5773fbaa 100644
--- a/Cabal/Distribution/Simple/GHC/Internal.hs
+++ b/Cabal/Distribution/Simple/GHC/Internal.hs
@@ -19,7 +19,9 @@ module Distribution.Simple.GHC.Internal (
         targetPlatform,
         getGhcInfo,
         componentCcGhcOptions,
+        componentCmmGhcOptions,
         componentCxxGhcOptions,
+        componentAsmGhcOptions,
         componentGhcOptions,
         mkGHCiLibName,
         mkGHCiProfLibName,
@@ -335,6 +337,42 @@ componentCxxGhcOptions verbosity _implInfo lbi bi clbi odir filename =
     }
 
 
+componentAsmGhcOptions :: Verbosity -> GhcImplInfo -> LocalBuildInfo
+                      -> BuildInfo -> ComponentLocalBuildInfo
+                      -> FilePath -> FilePath
+                      -> GhcOptions
+componentAsmGhcOptions verbosity _implInfo lbi bi clbi odir filename =
+    mempty {
+      -- Respect -v0, but don't crank up verbosity on GHC if
+      -- Cabal verbosity is requested. For that, use --ghc-option=-v instead!
+      ghcOptVerbosity      = toFlag (min verbosity normal),
+      ghcOptMode           = toFlag GhcModeCompile,
+      ghcOptInputFiles     = toNubListR [filename],
+
+      ghcOptCppIncludePath = toNubListR $ [autogenComponentModulesDir lbi clbi
+                                          ,autogenPackageModulesDir lbi
+                                          ,odir]
+                                          -- includes relative to the package
+                                          ++ PD.includeDirs bi
+                                          -- potential includes generated by `configure'
+                                          -- in the build directory
+                                          ++ [buildDir lbi </> dir | dir <- PD.includeDirs bi],
+      ghcOptHideAllPackages= toFlag True,
+      ghcOptPackageDBs     = withPackageDB lbi,
+      ghcOptPackages       = toNubListR $ mkGhcOptPackages clbi,
+      ghcOptAsmOptions     = (case withOptimization lbi of
+                                  NoOptimisation -> []
+                                  _              -> ["-O2"]) ++
+                             (case withDebugInfo lbi of
+                                  NoDebugInfo   -> []
+                                  MinimalDebugInfo -> ["-g1"]
+                                  NormalDebugInfo  -> ["-g"]
+                                  MaximalDebugInfo -> ["-g3"]) ++
+                                  PD.asmOptions bi,
+      ghcOptObjDir         = toFlag odir
+    }
+
+
 componentGhcOptions :: Verbosity -> GhcImplInfo -> LocalBuildInfo
                     -> BuildInfo -> ComponentLocalBuildInfo -> FilePath
                     -> GhcOptions
@@ -396,15 +434,50 @@ componentGhcOptions verbosity implInfo lbi bi clbi odir =
       ghcOptExtensionMap    = Map.fromList . compilerExtensions $ (compiler lbi)
     }
   where
-    toGhcOptimisation NoOptimisation      = mempty --TODO perhaps override?
-    toGhcOptimisation NormalOptimisation  = toFlag GhcNormalOptimisation
-    toGhcOptimisation MaximumOptimisation = toFlag GhcMaximumOptimisation
-
     exe_paths = [ componentBuildDir lbi (targetCLBI exe_tgt)
                 | uid <- componentExeDeps clbi
                 -- TODO: Ugh, localPkgDescr
                 , Just exe_tgt <- [unitIdTarget' (localPkgDescr lbi) lbi uid] ]
 
+toGhcOptimisation :: OptimisationLevel -> Flag GhcOptimisation
+toGhcOptimisation NoOptimisation      = mempty --TODO perhaps override?
+toGhcOptimisation NormalOptimisation  = toFlag GhcNormalOptimisation
+toGhcOptimisation MaximumOptimisation = toFlag GhcMaximumOptimisation
+
+
+componentCmmGhcOptions :: Verbosity -> GhcImplInfo -> LocalBuildInfo
+                      -> BuildInfo -> ComponentLocalBuildInfo
+                      -> FilePath -> FilePath
+                      -> GhcOptions
+componentCmmGhcOptions verbosity _implInfo lbi bi clbi odir filename =
+    mempty {
+      -- Respect -v0, but don't crank up verbosity on GHC if
+      -- Cabal verbosity is requested. For that, use --ghc-option=-v instead!
+      ghcOptVerbosity      = toFlag (min verbosity normal),
+      ghcOptMode           = toFlag GhcModeCompile,
+      ghcOptInputFiles     = toNubListR [filename],
+
+      ghcOptCppIncludePath = toNubListR $ [autogenComponentModulesDir lbi clbi
+                                          ,autogenPackageModulesDir lbi
+                                          ,odir]
+                                          -- includes relative to the package
+                                          ++ PD.includeDirs bi
+                                          -- potential includes generated by `configure'
+                                          -- in the build directory
+                                          ++ [buildDir lbi </> dir | dir <- PD.includeDirs bi],
+      ghcOptCppOptions     = cppOptions bi,
+      ghcOptCppIncludes    = toNubListR $
+                             [autogenComponentModulesDir lbi clbi </> cppHeaderName],
+      ghcOptHideAllPackages= toFlag True,
+      ghcOptPackageDBs     = withPackageDB lbi,
+      ghcOptPackages       = toNubListR $ mkGhcOptPackages clbi,
+      ghcOptOptimisation   = toGhcOptimisation (withOptimization lbi),
+      ghcOptDebugInfo      = toFlag (withDebugInfo lbi),
+      ghcOptExtra          = cmmOptions bi,
+      ghcOptObjDir         = toFlag odir
+    }
+
+
 -- | Strip out flags that are not supported in ghci
 filterGhciFlags :: [String] -> [String]
 filterGhciFlags = filter supported
diff --git a/Cabal/Distribution/Simple/Program/GHC.hs b/Cabal/Distribution/Simple/Program/GHC.hs
index 935224951839ce56058452bb61486c82201a1a0d..bc7868828549041d596da6e8601c10dedf9b1d7e 100644
--- a/Cabal/Distribution/Simple/Program/GHC.hs
+++ b/Cabal/Distribution/Simple/Program/GHC.hs
@@ -413,6 +413,9 @@ data GhcOptions = GhcOptions {
   -- | Options to pass through to the C++ compiler.
   ghcOptCxxOptions     :: [String],
 
+  -- | Options to pass through to the Assembler.
+  ghcOptAsmOptions     :: [String],
+
   -- | Options to pass through to CPP; the @ghc -optP@ flag.
   ghcOptCppOptions    :: [String],
 
@@ -665,6 +668,7 @@ renderGhcOptions comp _platform@(Platform _arch os) opts
            | inc <- flags ghcOptCppIncludes ]
   , [ "-optc" ++ opt | opt <- ghcOptCcOptions opts]
   , [ "-optc" ++ opt | opt <- ghcOptCxxOptions opts]
+  , [ "-opta" ++ opt | opt <- ghcOptAsmOptions opts]
 
   -----------------
   -- Linker stuff
diff --git a/Cabal/Distribution/Simple/SrcDist.hs b/Cabal/Distribution/Simple/SrcDist.hs
index 8e0cae09224b28beb793f86a35afc7994b316822..6bc637df670a6dd2ecf23a156c4f7e62556a0e2b 100644
--- a/Cabal/Distribution/Simple/SrcDist.hs
+++ b/Cabal/Distribution/Simple/SrcDist.hs
@@ -459,7 +459,8 @@ allSourcesBuildInfo verbosity bi pps modules = do
       in findFileWithExtension fileExts (hsSourceDirs bi) file
     | module_ <- modules ++ otherModules bi ]
 
-  return $ sources ++ catMaybes bootFiles ++ cSources bi ++ cxxSources bi ++ jsSources bi
+  return $ sources ++ catMaybes bootFiles ++ cSources bi ++ cxxSources bi ++
+           cmmSources bi ++ asmSources bi ++ jsSources bi
 
   where
     nonEmpty x _ [] = x
diff --git a/Cabal/doc/developing-packages.rst b/Cabal/doc/developing-packages.rst
index eb471606d3121738e88751889adeb5c1e5f4a41a..d29722266e803ea64396d31a14c848a25a95eb88 100644
--- a/Cabal/doc/developing-packages.rst
+++ b/Cabal/doc/developing-packages.rst
@@ -2478,12 +2478,13 @@ system-dependent values for these fields.
     appropriately.
 
 .. pkg-field:: asm-sources: filename list
-    :since: 2.2
+    :since: 3.0
 
     A list of assembly source files to be compiled and linked with the
     Haskell files.
 
 .. pkg-field:: cmm-sources: filename list
+    :since: 3.0
 
     A list of C-- source files to be compiled and linked with the Haskell
     files.
@@ -2550,8 +2551,14 @@ system-dependent values for these fields.
     command-line arguments with the :pkg-field:`cc-options` and the
     :pkg-field:`cxx-options` fields.
 
+.. pkg-field:: cmm-options: token list
+    :since: 3.0
+
+    Command-line arguments to be passed to the compiler when compiling
+    C-- code. See also :pkg-field:`cmm-sources`.
+
 .. pkg-field:: asm-options: token list
-    :since: 2.2
+    :since: 3.0
 
     Command-line arguments to be passed to the assembler when compiling
     assembler code. See also :pkg-field:`asm-sources`.
diff --git a/Cabal/doc/file-format-changelog.rst b/Cabal/doc/file-format-changelog.rst
index 60469eb4b6ed74ed50874fab2c726141106bc0f6..9ea718ed8ee022543ee5eb1269b74ef2c4d041d8 100644
--- a/Cabal/doc/file-format-changelog.rst
+++ b/Cabal/doc/file-format-changelog.rst
@@ -69,6 +69,14 @@ relative to the respective preceding *published* version.
 * New :pkg-field:`autogen-includes` for specifying :pkg-field:`install-includes`
   which are autogenerated (e.g. by a ``configure`` script).
 
+* New :pkg-field:`asm-sources` and :pkg-field:`asm-options` fields
+  added for suppporting bundled foreign routines implemented in
+  assembler.
+
+* New :pkg-field:`cmm-sources` and :pkg-field:`cmm-options` fields
+  added for suppporting bundled foreign primops implemented in
+  C--.
+
 ``cabal-version: 2.4``
 ----------------------
 
@@ -104,10 +112,6 @@ relative to the respective preceding *published* version.
 * New :pkg-field:`cxx-sources` and :pkg-field:`cxx-options` fields
   added for suppporting bundled foreign routines implemented in C++.
 
-* New :pkg-field:`asm-sources` and :pkg-field:`asm-options` fields
-  added for suppporting bundled foreign routines implemented in
-  assembler.
-
 * New :pkg-field:`extra-bundled-libraries` field for specifying
   additional custom library objects to be installed.