diff --git a/Cabal/src/Distribution/PackageDescription/Check.hs b/Cabal/src/Distribution/PackageDescription/Check.hs
index 449c53558396a2a2675a7708685147885cde90fd..4b0f0e0e7189bef4fcd3de344b0965c23dcd9433 100644
--- a/Cabal/src/Distribution/PackageDescription/Check.hs
+++ b/Cabal/src/Distribution/PackageDescription/Check.hs
@@ -52,6 +52,7 @@ import Distribution.Simple.Glob
 import Distribution.Simple.Utils                     hiding (findPackageDesc, notice)
 import Distribution.System
 import Distribution.Types.ComponentRequestedSpec
+import Distribution.Types.PackageName.Magic
 import Distribution.Utils.Generic                    (isAscii)
 import Distribution.Verbosity
 import Distribution.Version
@@ -284,8 +285,9 @@ checkExecutable pkg exe =
     check (null (modulePath exe)) $
       PackageBuildImpossible $
         "No 'main-is' field found for executable " ++ prettyShow (exeName exe)
-
-  , check (not (null (modulePath exe))
+  -- This check does not apply to scripts.
+  , check (package pkg /= fakePackageId
+       && not (null (modulePath exe))
        && (not $ fileExtensionSupportedLanguage $ modulePath exe)) $
       PackageBuildImpossible $
            "The 'main-is' field must specify a '.hs' or '.lhs' file "
diff --git a/Cabal/src/Distribution/Simple/GHC.hs b/Cabal/src/Distribution/Simple/GHC.hs
index 7d416b572b427088bab32199deb716f1fb7515c0..641a49c18b94f71615dce2cd1e66b321fb0bf3f5 100644
--- a/Cabal/src/Distribution/Simple/GHC.hs
+++ b/Cabal/src/Distribution/Simple/GHC.hs
@@ -103,6 +103,7 @@ import qualified Distribution.Simple.Setup as Cabal
 import Distribution.Simple.Compiler
 import Distribution.Version
 import Distribution.System
+import Distribution.Types.PackageName.Magic
 import Distribution.Verbosity
 import Distribution.Pretty
 import Distribution.Utils.NubList
@@ -1190,11 +1191,12 @@ data BuildSources = BuildSources {
 
 -- | Locate and return the 'BuildSources' required to build and link.
 gbuildSources :: Verbosity
+              -> PackageId
               -> CabalSpecVersion
               -> FilePath
               -> GBuildMode
               -> IO BuildSources
-gbuildSources verbosity specVer tmpDir bm =
+gbuildSources verbosity pkgId specVer tmpDir bm =
     case bm of
       GBuildExe  exe  -> exeSources exe
       GReplExe   _ exe  -> exeSources exe
@@ -1207,7 +1209,8 @@ gbuildSources verbosity specVer tmpDir bm =
       let mainModName = fromMaybe ModuleName.main $ exeMainModuleName exe
           otherModNames = exeModules exe
 
-      if isHaskell main
+      -- Scripts have fakePackageId and are always Haskell but can have any extension.
+      if isHaskell main || pkgId == fakePackageId
         then
           if specVer < CabalSpecV2_0 && (mainModName `elem` otherModNames)
           then do
@@ -1263,12 +1266,13 @@ gbuildSources verbosity specVer tmpDir bm =
             inputSourceModules = foreignLibModules flib
         }
 
-    isHaskell :: FilePath -> Bool
-    isHaskell fp = elem (takeExtension fp) [".hs", ".lhs"]
-
     isCxx :: FilePath -> Bool
     isCxx fp = elem (takeExtension fp) [".cpp", ".cxx", ".c++"]
 
+-- | FilePath has a Haskell extension: .hs or .lhs
+isHaskell :: FilePath -> Bool
+isHaskell fp = elem (takeExtension fp) [".hs", ".lhs"]
+
 replNoLoad :: Ord a => ReplOptions -> NubListR a -> NubListR a
 replNoLoad replFlags l
     | replOptionsNoLoad replFlags == Flag True = mempty
@@ -1314,7 +1318,7 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
         | otherwise         = mempty
 
   rpaths <- getRPaths lbi clbi
-  buildSources <- gbuildSources verbosity (specVersion pkg_descr) tmpDir bm
+  buildSources <- gbuildSources verbosity (package pkg_descr) (specVersion pkg_descr) tmpDir bm
 
   let cSrcs               = cSourcesFiles buildSources
       cxxSrcs             = cxxSourceFiles buildSources
@@ -1331,7 +1335,12 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
       baseOpts   = (componentGhcOptions verbosity lbi bnfo clbi tmpDir)
                     `mappend` mempty {
                       ghcOptMode         = toFlag GhcModeMake,
-                      ghcOptInputFiles   = toNubListR inputFiles,
+                      ghcOptInputFiles   = toNubListR $ if package pkg_descr == fakePackageId
+                                                        then filter isHaskell inputFiles
+                                                        else inputFiles,
+                      ghcOptInputScripts = toNubListR $ if package pkg_descr == fakePackageId
+                                                        then filter (not . isHaskell) inputFiles
+                                                        else [],
                       ghcOptInputModules = toNubListR inputModules
                     }
       staticOpts = baseOpts `mappend` mempty {
diff --git a/Cabal/src/Distribution/Simple/GHCJS.hs b/Cabal/src/Distribution/Simple/GHCJS.hs
index 780267b728ea851148d254f444a82b02816b5e32..a2ff905b98f77ecd487e6a6ab7341613af5875bf 100644
--- a/Cabal/src/Distribution/Simple/GHCJS.hs
+++ b/Cabal/src/Distribution/Simple/GHCJS.hs
@@ -67,6 +67,7 @@ import Distribution.Simple.Compiler
 import Distribution.CabalSpecVersion
 import Distribution.Version
 import Distribution.System
+import Distribution.Types.PackageName.Magic
 import Distribution.Verbosity
 import Distribution.Pretty
 import Distribution.Utils.NubList
@@ -961,11 +962,12 @@ data BuildSources = BuildSources {
 
 -- | Locate and return the 'BuildSources' required to build and link.
 gbuildSources :: Verbosity
+              -> PackageId
               -> CabalSpecVersion
               -> FilePath
               -> GBuildMode
               -> IO BuildSources
-gbuildSources verbosity specVer tmpDir bm =
+gbuildSources verbosity pkgId specVer tmpDir bm =
     case bm of
       GBuildExe  exe  -> exeSources exe
       GReplExe   _ exe  -> exeSources exe
@@ -978,7 +980,8 @@ gbuildSources verbosity specVer tmpDir bm =
       let mainModName = fromMaybe ModuleName.main $ exeMainModuleName exe
           otherModNames = exeModules exe
 
-      if isHaskell main
+      -- Scripts have fakePackageId and are always Haskell but can have any extension.
+      if isHaskell main || pkgId == fakePackageId
         then
           if specVer < CabalSpecV2_0 && (mainModName `elem` otherModNames)
           then do
@@ -1033,12 +1036,13 @@ gbuildSources verbosity specVer tmpDir bm =
             inputSourceModules = foreignLibModules flib
         }
 
-    isHaskell :: FilePath -> Bool
-    isHaskell fp = elem (takeExtension fp) [".hs", ".lhs"]
-
     isCxx :: FilePath -> Bool
     isCxx fp = elem (takeExtension fp) [".cpp", ".cxx", ".c++"]
 
+-- | FilePath has a Haskell extension: .hs or .lhs
+isHaskell :: FilePath -> Bool
+isHaskell fp = elem (takeExtension fp) [".hs", ".lhs"]
+
 -- | Generic build function. See comment for 'GBuildMode'.
 gbuild :: Verbosity          -> Cabal.Flag (Maybe Int)
        -> PackageDescription -> LocalBuildInfo
@@ -1079,7 +1083,7 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
         | otherwise         = mempty
 
   rpaths <- getRPaths lbi clbi
-  buildSources <- gbuildSources verbosity (specVersion pkg_descr) tmpDir bm
+  buildSources <- gbuildSources verbosity (package pkg_descr) (specVersion pkg_descr) tmpDir bm
 
   let cSrcs               = cSourcesFiles buildSources
       cxxSrcs             = cxxSourceFiles buildSources
@@ -1102,7 +1106,12 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
       baseOpts   = (componentGhcOptions verbosity lbi bnfo clbi tmpDir)
                     `mappend` mempty {
                       ghcOptMode         = toFlag GhcModeMake,
-                      ghcOptInputFiles   = toNubListR inputFiles,
+                      ghcOptInputFiles   = toNubListR $ if package pkg_descr == fakePackageId
+                                                        then filter isHaskell inputFiles
+                                                        else inputFiles,
+                      ghcOptInputScripts = toNubListR $ if package pkg_descr == fakePackageId
+                                                        then filter (not . isHaskell) inputFiles
+                                                        else [],
                       ghcOptInputModules = toNubListR inputModules,
                       -- for all executable components (exe/test/bench),
                       -- GHCJS must be passed the "-build-runner" option
diff --git a/Cabal/src/Distribution/Simple/PreProcess.hs b/Cabal/src/Distribution/Simple/PreProcess.hs
index a9142a3d7101b5be3732cce9e706c77df80c7f54..5290012299f6179ef2f2f9b14a55e6410436a611 100644
--- a/Cabal/src/Distribution/Simple/PreProcess.hs
+++ b/Cabal/src/Distribution/Simple/PreProcess.hs
@@ -51,6 +51,7 @@ import Distribution.Simple.Program
 import Distribution.Simple.Program.ResponseFile
 import Distribution.Simple.Test.LibV09
 import Distribution.System
+import Distribution.Types.PackageName.Magic
 import Distribution.Pretty
 import Distribution.Version
 import Distribution.Verbosity
@@ -171,60 +172,63 @@ preprocessComponent :: PackageDescription
                     -> Verbosity
                     -> [PPSuffixHandler]
                     -> IO ()
-preprocessComponent pd comp lbi clbi isSrcDist verbosity handlers = do
- -- NB: never report instantiation here; we'll report it properly when
- -- building.
- setupMessage' verbosity "Preprocessing" (packageId pd)
-    (componentLocalName clbi) (Nothing :: Maybe [(ModuleName, Module)])
- case comp of
-  (CLib lib@Library{ libBuildInfo = bi }) -> do
-    let dirs = map getSymbolicPath (hsSourceDirs bi) ++
-             [ autogenComponentModulesDir lbi clbi ,autogenPackageModulesDir lbi]
-    let hndlrs = localHandlers bi
-    mods <- orderingFromHandlers verbosity dirs hndlrs (allLibModules lib clbi)
-    for_ (map ModuleName.toFilePath mods) $
-      pre dirs (componentBuildDir lbi clbi) hndlrs
-  (CFLib flib@ForeignLib { foreignLibBuildInfo = bi, foreignLibName = nm }) -> do
-    let nm' = unUnqualComponentName nm
-    let flibDir = buildDir lbi </> nm' </> nm' ++ "-tmp"
-        dirs    = map getSymbolicPath (hsSourceDirs bi) ++ [autogenComponentModulesDir lbi clbi
-                                     ,autogenPackageModulesDir lbi]
-    let hndlrs = localHandlers bi
-    mods <- orderingFromHandlers verbosity dirs hndlrs (foreignLibModules flib)
-    for_ (map ModuleName.toFilePath mods) $
-      pre dirs flibDir hndlrs
-  (CExe exe@Executable { buildInfo = bi, exeName = nm }) -> do
-    let nm' = unUnqualComponentName nm
-    let exeDir = buildDir lbi </> nm' </> nm' ++ "-tmp"
-        dirs   = map getSymbolicPath (hsSourceDirs bi) ++ [autogenComponentModulesDir lbi clbi
-                                    ,autogenPackageModulesDir lbi]
-    let hndlrs = localHandlers bi
-    mods <- orderingFromHandlers verbosity dirs hndlrs (otherModules bi)
-    for_ (map ModuleName.toFilePath mods) $
-      pre dirs exeDir hndlrs
-    pre (map getSymbolicPath (hsSourceDirs bi)) exeDir (localHandlers bi) $
-      dropExtensions (modulePath exe)
-  CTest test@TestSuite{ testName = nm } -> do
-    let nm' = unUnqualComponentName nm
-    case testInterface test of
-      TestSuiteExeV10 _ f ->
-          preProcessTest test f $ buildDir lbi </> nm' </> nm' ++ "-tmp"
-      TestSuiteLibV09 _ _ -> do
-          let testDir = buildDir lbi </> stubName test
-                  </> stubName test ++ "-tmp"
-          writeSimpleTestStub test testDir
-          preProcessTest test (stubFilePath test) testDir
-      TestSuiteUnsupported tt ->
-          die' verbosity $ "No support for preprocessing test "
-                        ++ "suite type " ++ prettyShow tt
-  CBench bm@Benchmark{ benchmarkName = nm } -> do
-    let nm' = unUnqualComponentName nm
-    case benchmarkInterface bm of
-      BenchmarkExeV10 _ f ->
-          preProcessBench bm f $ buildDir lbi </> nm' </> nm' ++ "-tmp"
-      BenchmarkUnsupported tt ->
-          die' verbosity $ "No support for preprocessing benchmark "
-                        ++ "type " ++ prettyShow tt
+preprocessComponent pd comp lbi clbi isSrcDist verbosity handlers =
+  -- Skip preprocessing for scripts since they should be regular Haskell files,
+  -- but may have no or unknown extensions.
+  when (package pd /= fakePackageId) $ do
+   -- NB: never report instantiation here; we'll report it properly when
+   -- building.
+   setupMessage' verbosity "Preprocessing" (packageId pd)
+      (componentLocalName clbi) (Nothing :: Maybe [(ModuleName, Module)])
+   case comp of
+    (CLib lib@Library{ libBuildInfo = bi }) -> do
+      let dirs = map getSymbolicPath (hsSourceDirs bi) ++
+               [ autogenComponentModulesDir lbi clbi ,autogenPackageModulesDir lbi]
+      let hndlrs = localHandlers bi
+      mods <- orderingFromHandlers verbosity dirs hndlrs (allLibModules lib clbi)
+      for_ (map ModuleName.toFilePath mods) $
+        pre dirs (componentBuildDir lbi clbi) hndlrs
+    (CFLib flib@ForeignLib { foreignLibBuildInfo = bi, foreignLibName = nm }) -> do
+      let nm' = unUnqualComponentName nm
+      let flibDir = buildDir lbi </> nm' </> nm' ++ "-tmp"
+          dirs    = map getSymbolicPath (hsSourceDirs bi) ++ [autogenComponentModulesDir lbi clbi
+                                       ,autogenPackageModulesDir lbi]
+      let hndlrs = localHandlers bi
+      mods <- orderingFromHandlers verbosity dirs hndlrs (foreignLibModules flib)
+      for_ (map ModuleName.toFilePath mods) $
+        pre dirs flibDir hndlrs
+    (CExe exe@Executable { buildInfo = bi, exeName = nm }) -> do
+      let nm' = unUnqualComponentName nm
+      let exeDir = buildDir lbi </> nm' </> nm' ++ "-tmp"
+          dirs   = map getSymbolicPath (hsSourceDirs bi) ++ [autogenComponentModulesDir lbi clbi
+                                      ,autogenPackageModulesDir lbi]
+      let hndlrs = localHandlers bi
+      mods <- orderingFromHandlers verbosity dirs hndlrs (otherModules bi)
+      for_ (map ModuleName.toFilePath mods) $
+        pre dirs exeDir hndlrs
+      pre (map getSymbolicPath (hsSourceDirs bi)) exeDir (localHandlers bi) $
+        dropExtensions (modulePath exe)
+    CTest test@TestSuite{ testName = nm } -> do
+      let nm' = unUnqualComponentName nm
+      case testInterface test of
+        TestSuiteExeV10 _ f ->
+            preProcessTest test f $ buildDir lbi </> nm' </> nm' ++ "-tmp"
+        TestSuiteLibV09 _ _ -> do
+            let testDir = buildDir lbi </> stubName test
+                    </> stubName test ++ "-tmp"
+            writeSimpleTestStub test testDir
+            preProcessTest test (stubFilePath test) testDir
+        TestSuiteUnsupported tt ->
+            die' verbosity $ "No support for preprocessing test "
+                          ++ "suite type " ++ prettyShow tt
+    CBench bm@Benchmark{ benchmarkName = nm } -> do
+      let nm' = unUnqualComponentName nm
+      case benchmarkInterface bm of
+        BenchmarkExeV10 _ f ->
+            preProcessBench bm f $ buildDir lbi </> nm' </> nm' ++ "-tmp"
+        BenchmarkUnsupported tt ->
+            die' verbosity $ "No support for preprocessing benchmark "
+                          ++ "type " ++ prettyShow tt
   where
     orderingFromHandlers v d hndlrs mods =
       foldM (\acc (_,pp) -> ppOrdering pp v d acc) mods hndlrs
diff --git a/Cabal/src/Distribution/Simple/Program/GHC.hs b/Cabal/src/Distribution/Simple/Program/GHC.hs
index e65662fcdd8c6d18cb6345d10e4dcbb8b4393fa0..6aebf62bc3e345c5e56dbe28372c2c1244145041 100644
--- a/Cabal/src/Distribution/Simple/Program/GHC.hs
+++ b/Cabal/src/Distribution/Simple/Program/GHC.hs
@@ -333,6 +333,9 @@ data GhcOptions = GhcOptions {
   -- | The main input files; could be .hs, .hi, .c, .o, depending on mode.
   ghcOptInputFiles    :: NubListR FilePath,
 
+  -- | Script files with irregular extensions that need -x hs.
+  ghcOptInputScripts  :: NubListR FilePath,
+
   -- | The names of input Haskell modules, mainly for @--make@ mode.
   ghcOptInputModules  :: NubListR ModuleName,
 
@@ -779,6 +782,7 @@ renderGhcOptions comp _platform@(Platform _arch os) opts
   -- Specify the input file(s) first, so that in ghci the `main-is` module is
   -- in scope instead of the first module defined in `other-modules`.
   , flags ghcOptInputFiles
+  , concat [ [ "-x", "hs", script] | script <- flags ghcOptInputScripts ]
   , [ prettyShow modu | modu <- flags ghcOptInputModules ]
 
   , concat [ [ "-o",    out] | out <- flag ghcOptOutputFile ]
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdBuild/Script/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdBuild/Script/cabal.out
index 732deece54046e3d47eaa439ae4514b8248d83f1..e36af55eb8099c8995a98948ea318c4d37860c10 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdBuild/Script/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdBuild/Script/cabal.out
@@ -4,5 +4,4 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptBuildRepl/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptBuildRepl/cabal.out
index 84e095157e1520fbc9fb2fd0e521046e6caf033c..236acd3eb59cbae2cc14a34c66b0a18d58c1018d 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptBuildRepl/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptBuildRepl/cabal.out
@@ -4,10 +4,8 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-repl
 Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (ephemeral targets)
-Preprocessing executable 'script' for fake-package-0..
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptBuildRun/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptBuildRun/cabal.out
index 238ec82dc8a96c91b31f7608b306255a9f63f8c2..c834bfbbc129381dad59cf28acb0cbaee107e106 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptBuildRun/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptBuildRun/cabal.out
@@ -4,7 +4,6 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-run
 Up to date
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptRerun/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptRerun/cabal.out
index a3a2453901c5c18a3e5c5ea6ebd5f53928af4132..8959c065706a9a22386f93ca30ae43200167e423 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptRerun/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdBuild/ScriptRerun/cabal.out
@@ -4,7 +4,6 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-build
 Up to date
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdClean/Keep/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdClean/Keep/cabal.out
index 4d11e547d3e2d9a436573bfe62518eec56b6f443..3ef003f5fca8d604769cb18226df7a3e5bb8ec12 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdClean/Keep/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdClean/Keep/cabal.out
@@ -4,7 +4,6 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-build
 Resolving dependencies...
@@ -12,6 +11,5 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (configuration changed)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-clean
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdClean/Orphan/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdClean/Orphan/cabal.out
index 4d11e547d3e2d9a436573bfe62518eec56b6f443..3ef003f5fca8d604769cb18226df7a3e5bb8ec12 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdClean/Orphan/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdClean/Orphan/cabal.out
@@ -4,7 +4,6 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-build
 Resolving dependencies...
@@ -12,6 +11,5 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (configuration changed)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-clean
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdClean/Script/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdClean/Script/cabal.out
index 7fe551a7e7164b98fa28e7d3ebdb71415a6f47e9..8950f7c21f7c708a07ed1f31c6584936c8c95fcf 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdClean/Script/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdClean/Script/cabal.out
@@ -4,6 +4,5 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-clean
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdRepl/Script/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdRepl/Script/cabal.out
index 09411fe70a76f7657b69098dee82ba8c0fa1d17c..cfca4898f506473a115d4351aab968c98da4511a 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdRepl/Script/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdRepl/Script/cabal.out
@@ -4,4 +4,3 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdRepl/ScriptRerun/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdRepl/ScriptRerun/cabal.out
index 7df4356db59e42d90da881fa85572029d8f09ade..13b77ec4a65da6363cf86d2fa0054e23a528ebcb 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdRepl/ScriptRerun/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdRepl/ScriptRerun/cabal.out
@@ -4,9 +4,7 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 # cabal v2-repl
 Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
-Preprocessing executable 'script' for fake-package-0..
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdRun/Script/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdRun/Script/cabal.out
index 31d7de3ca732c25d1b9181bcb6cacb09116db808..ff4a38632f5436c0a3130382c2b91961285cf595 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdRun/Script/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdRun/Script/cabal.out
@@ -4,5 +4,4 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptLiterate/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptLiterate/cabal.out
index 31d7de3ca732c25d1b9181bcb6cacb09116db808..ff4a38632f5436c0a3130382c2b91961285cf595 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptLiterate/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptLiterate/cabal.out
@@ -4,5 +4,4 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/cabal.out
new file mode 100644
index 0000000000000000000000000000000000000000..ff4a38632f5436c0a3130382c2b91961285cf595
--- /dev/null
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/cabal.out
@@ -0,0 +1,7 @@
+# cabal v2-run
+Resolving dependencies...
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - fake-package-0 (exe:script) (first run)
+Configuring executable 'script' for fake-package-0..
+Building executable 'script' for fake-package-0..
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/cabal.test.hs b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/cabal.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..bb3b6b4b2f7cbf3e4abed296a1f78acb8ce3a18c
--- /dev/null
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/cabal.test.hs
@@ -0,0 +1,4 @@
+import Test.Cabal.Prelude
+
+main = cabalTest . void $ do
+    cabal' "v2-run" ["./script"] >>= assertOutputContains "Hello World"
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/script b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/script
new file mode 100644
index 0000000000000000000000000000000000000000..cd2fae4e8f47a7da5997e046201fad61da6c8d2b
--- /dev/null
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptNoExtention/script
@@ -0,0 +1,6 @@
+{- cabal:
+build-depends: base
+-}
+
+main :: IO ()
+main = putStrLn "Hello World"
diff --git a/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptRerun/cabal.out b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptRerun/cabal.out
index 65fdda7f7368169fefba973bf81110eaced32aa9..1db558594b2eff06d04a0eed4f8db8e1984a5357 100644
--- a/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptRerun/cabal.out
+++ b/cabal-testsuite/PackageTests/NewBuild/CmdRun/ScriptRerun/cabal.out
@@ -4,7 +4,6 @@ Build profile: -w ghc-<GHCVER> -O1
 In order, the following will be built:
  - fake-package-0 (exe:script) (first run)
 Configuring executable 'script' for fake-package-0..
-Preprocessing executable 'script' for fake-package-0..
 Building executable 'script' for fake-package-0..
 # cabal v2-run
 Up to date