Skip to content
Snippets Groups Projects
Unverified Commit 03d98294 authored by mergify[bot]'s avatar mergify[bot] Committed by GitHub
Browse files

Merge pull request #9988 from sheaf/no-implicit-prelude-setup

Add NoImplicitPrelude to buildTypeScript
parents 47e72959 42b8dc1f
No related branches found
No related tags found
No related merge requests found
......@@ -133,11 +133,10 @@ mkDefaultSetupDeps compiler platform pkg =
-- For other build types (like Simple) if we still need to compile an
-- external Setup.hs, it'll be one of the simple ones that only depends
-- on Cabal and base.
-- on Cabal.
SetupNonCustomExternalLib ->
Just
[ Dependency cabalPkgname cabalConstraint mainLibSet
, Dependency basePkgname anyVersion mainLibSet
]
where
cabalConstraint = orLaterVersion (csvToVersion (specVersion pkg))
......@@ -217,9 +216,8 @@ packageSetupScriptSpecVersion _ pkg libDepGraph deps =
fromMaybe [] $
Graph.closure libDepGraph (CD.setupDeps deps)
cabalPkgname, basePkgname :: PackageName
cabalPkgname :: PackageName
cabalPkgname = mkPackageName "Cabal"
basePkgname = mkPackageName "base"
legacyCustomSetupPkgs :: Compiler -> Platform -> [PackageName]
legacyCustomSetupPkgs compiler (Platform _ os) =
......
......@@ -181,6 +181,7 @@ import Distribution.Utils.NubList
import Distribution.Verbosity
import Data.List (foldl1')
import qualified Data.Map.Lazy as Map
import Distribution.Simple.Setup (globalCommand)
import Distribution.Client.Compat.ExecutablePath (getExecutablePath)
import Distribution.Compat.Process (proc)
......@@ -858,7 +859,7 @@ getExternalSetupMethod verbosity options pkg bt = do
rewriteFileLBS verbosity (i setupHs) (buildTypeScript cabalLibVersion)
buildTypeScript :: Version -> BS.ByteString
buildTypeScript cabalLibVersion = case bt of
buildTypeScript cabalLibVersion = "{-# LANGUAGE NoImplicitPrelude #-}\n" <> case bt of
Simple -> "import Distribution.Simple; main = defaultMain\n"
Configure
| cabalLibVersion >= mkVersion [1, 3, 10] -> "import Distribution.Simple; main = defaultMainWithHooks autoconfUserHooks\n"
......@@ -1111,6 +1112,13 @@ getExternalSetupMethod verbosity options pkg bt = do
| useVersionMacros options'
]
, ghcOptExtra = extraOpts
, ghcOptExtensions = toNubListR $
if bt == Custom || any (isBasePkgId . snd) selectedDeps
then []
else [ Simple.DisableExtension Simple.ImplicitPrelude ]
-- Pass -WNoImplicitPrelude to avoid depending on base
-- when compiling a Simple Setup.hs file.
, ghcOptExtensionMap = Map.fromList . Simple.compilerExtensions $ compiler
}
let ghcCmdLine = renderGhcOptions compiler platform ghcOptions
when (useVersionMacros options') $
......@@ -1131,5 +1139,6 @@ getExternalSetupMethod verbosity options pkg bt = do
hPutStr logHandle output
return $ i setupProgFile
isCabalPkgId :: PackageIdentifier -> Bool
isCabalPkgId, isBasePkgId :: PackageIdentifier -> Bool
isCabalPkgId (PackageIdentifier pname _) = pname == mkPackageName "Cabal"
isBasePkgId (PackageIdentifier pname _) = pname == mkPackageName "base"
{-# LANGUAGE NoImplicitPrelude #-}
module A where {}
{-# LANGUAGE NoImplicitPrelude #-}
module SetupHooks ( setupHooks ) where
import Distribution.Simple.SetupHooks ( SetupHooks, noSetupHooks )
setupHooks :: SetupHooks
setupHooks = noSetupHooks
packages: .
import Test.Cabal.Prelude
-- Test that we can compile the Setup.hs script for a package with
-- build-type:Hooks without requiring a dependency on 'base'.
--
-- NB: we specifically don't include a 'Setup.hs' file in this package,
-- as we rely on 'cabal-install' generating one that does not incur an extra
-- dependency on base.
main = cabalTest $ do
mpkgdb <- testPackageDbPath <$> getTestEnv
case mpkgdb of
Nothing -> skip "Cabal-hooks library unavailable."
Just _pkgdb -> recordMode DoNotRecord $ do
cabal "v2-build" [ "all" ]
cabal-version: 3.14
name: setup-hooks-no-base-test
version: 0.1.0.0
synopsis: Test that we can build Setup.hs without base
license: BSD-3-Clause
author: NA
maintainer: NA
category: Testing
build-type: Hooks
custom-setup
setup-depends: Cabal-hooks
library
exposed-modules: A
default-language: Haskell2010
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment