aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorDaniel Gröber <dxld@darkboxed.org>2020-01-11 07:46:33 +0100
committerDaniel Gröber <dxld@darkboxed.org>2020-05-02 15:44:26 +0200
commit852dbc69d276e19add3917d17dff5541d84e29d4 (patch)
treeb01a16ee9a03fb491dfdf50a7bc717b76e95d445
parentf0741c61bd82ec0f94edcfa8d950f349eac86c33 (diff)
Fix Cabal version selection for build-type:Custom
Previously we would pick up Stack's Cabal version with ghc-pkg on the global package-db. This however ignores that Stack also supports custom Setup.hs with the Cabal version from the snapshot instead. In cabal v2-build we have a similar problem. We used to assume that plan.json's cabal-lib-version is used uniformly across units but this is similarly untrue. To fix both of these we re-stage the cabal version query to after reconfiguring a unit, then we can just lookup the Cabal version in setup-config. Fixes #95
-rw-r--r--cabal-helper.cabal5
-rw-r--r--lib/Distribution/Helper.hs170
-rw-r--r--src/CabalHelper/Compiletime/Cabal.hs14
-rw-r--r--src/CabalHelper/Compiletime/Compile.hs12
-rw-r--r--src/CabalHelper/Compiletime/Types.hs12
-rw-r--r--tests/CompileTest.hs6
-rw-r--r--tests/GhcSession.hs34
-rw-r--r--tests/custom-setup/Lib.hs8
-rw-r--r--tests/custom-setup/Setup.hs2
-rw-r--r--tests/custom-setup/custom-setup.cabal13
-rw-r--r--tests/custom-setup/packages.list1
-rw-r--r--tests/custom-setup/stack.yaml3
12 files changed, 176 insertions, 104 deletions
diff --git a/cabal-helper.cabal b/cabal-helper.cabal
index d059338..20ad842 100644
--- a/cabal-helper.cabal
+++ b/cabal-helper.cabal
@@ -39,6 +39,11 @@ extra-source-files: README.md
tests/fliblib/stack.yaml
tests/fliblib/lib/*.hs
+ tests/custom-setup/*.hs
+ tests/custom-setup/*.cabal
+ tests/custom-setup/packages.list
+ tests/custom-setup/stack.yaml
+
tests/bkpregex/*.hs
tests/bkpregex/*.cabal
tests/bkpregex/packages.list
diff --git a/lib/Distribution/Helper.hs b/lib/Distribution/Helper.hs
index 428afd1..84c1c30 100644
--- a/lib/Distribution/Helper.hs
+++ b/lib/Distribution/Helper.hs
@@ -282,19 +282,25 @@ getUnitModTimes
package_yaml_path = pSourceDir </> "package.yaml"
setup_config_path = distdirv1 </> "setup-config"
+-- | Get a random unit from the project. Sometimes we need to get info we
+-- can only get after configuring _any_ unit but we do assume that this
+-- info is uniform across units.
+someUnit :: ProjInfo pt -> Unit pt
+someUnit proj_info =
+ NonEmpty.head $ pUnits $
+ NonEmpty.head $ piPackages proj_info
-- | The version of GHC the project is configured to use for compilation.
compilerVersion :: Query pt (String, Version)
compilerVersion = Query $ \qe ->
getProjInfo qe >>= \proj_info ->
- let someUnit = NonEmpty.head $ pUnits $
- NonEmpty.head $ piPackages proj_info in
+ let unit = someUnit proj_info in
-- ^ ASSUMPTION: Here we assume the compiler version is uniform across all
-- units so we just pick any one.
case piImpl proj_info of
- ProjInfoV1 {} -> uiCompilerId <$> getUnitInfo qe someUnit
+ ProjInfoV1 {} -> uiCompilerId <$> getUnitInfo qe unit
ProjInfoV2 { piV2CompilerId } -> return piV2CompilerId
- ProjInfoStack {} -> uiCompilerId <$> getUnitInfo qe someUnit
+ ProjInfoStack {} -> uiCompilerId <$> getUnitInfo qe unit
-- | All local packages currently active in a project\'s build plan.
projectPackages :: Query pt (NonEmpty (Package pt))
@@ -410,6 +416,25 @@ getProjInfo qe = do
readProjInfo qe proj_conf mtime pre_info
}
+
+-- | Get the cabal version we need to build for this project.
+getCabalLibVersion :: QueryEnv pt -> Reconfigured pt -> ProjInfo pt -> IO CabalVersion
+getCabalLibVersion _ _ ProjInfo{piImpl=ProjInfoV1 {piV1CabalVersion}} =
+ return piV1CabalVersion
+getCabalLibVersion qe reconf proj_info = do
+ unit <- case reconf of
+ AlreadyReconfigured unit ->
+ return unit
+ Haven'tReconfigured -> do
+ let unit = someUnit proj_info
+ reconfigureUnit qe unit
+ return unit
+ let DistDirLib distdir = uDistDir $ unit
+ hdr <- readSetupConfigHeader $ distdir </> "setup-config"
+ let ("Cabal", cabalVer) = uhSetupId hdr
+ return $ CabalVersion cabalVer
+
+
getUnitInfo :: QueryEnv pt -> Unit pt -> IO UnitInfo
getUnitInfo qe@QueryEnv{..} unit@Unit{uDistDir} = do
pre_info <- getPreInfo qe
@@ -427,8 +452,9 @@ getUnitInfo qe@QueryEnv{..} unit@Unit{uDistDir} = do
, cKeyValid = (==)
, cRegen = \mtimes -> do
- reconfigureUnit qe unit
- helper <- getHelper pre_info proj_info qe
+ reconf <- reconfigureUnit qe unit
+ cabal_ver <- getCabalLibVersion qe reconf proj_info
+ helper <- getHelper qe pre_info proj_info cabal_ver
readUnitInfo helper unit mtimes
}
@@ -457,8 +483,11 @@ shallowReconfigureProject QueryEnv
shallowReconfigureProject qe = do
buildProjectTarget qe Nothing DryRun
-reconfigureUnit :: QueryEnvI c pt -> Unit pt -> IO ()
-reconfigureUnit qe u = buildProjectTarget qe (Just u) OnlyCfg
+data Reconfigured pt = AlreadyReconfigured (Unit pt) | Haven'tReconfigured
+reconfigureUnit :: QueryEnvI c pt -> Unit pt -> IO (Reconfigured pt)
+reconfigureUnit qe u = do
+ buildProjectTarget qe (Just u) OnlyCfg
+ return (AlreadyReconfigured u)
buildUnits :: [Unit pt] -> Query pt ()
buildUnits units = Query $ \qe -> do
@@ -489,6 +518,8 @@ buildProjectTarget qe mu stage = do
cmd <- return $ case stage of
DryRun | SCV1 <- cpt ->
CabalInstall.CIConfigure
+ -- TODO: in v1 we configure twice because we do configure for
+ -- DryRun and OnlyCfg.
OnlyCfg ->
CabalInstall.CIConfigure
_ ->
@@ -538,43 +569,39 @@ getFileModTime f = do
readProjInfo
:: QueryEnvI c pt -> ProjConf pt -> ProjConfModTimes -> PreInfo pt -> IO (ProjInfo pt)
-readProjInfo qe pc pcm pi = withVerbosity $ do
+readProjInfo qe pc pcm _pi = withVerbosity $ do
let projloc = qeProjLoc qe
case (qeDistDir qe, pc) of
(DistDirCabal SCV1 distdir, ProjConfV1{pcV1CabalFile}) -> do
setup_config_path <- canonicalizePath (distdir </> "setup-config")
- mhdr <- readSetupConfigHeader setup_config_path
- case mhdr of
- Just hdr@(UnitHeader (pkg_name_bs, _pkg_ver) ("Cabal", hdrCabalVersion) _compId) -> do
- let
- v3_0_0_0 = makeVersion [3,0,0,0]
- pkg_name
- | hdrCabalVersion >= v3_0_0_0 = BSU.toString pkg_name_bs
- | otherwise = BS8.unpack pkg_name_bs
- pkg = Package
- { pPackageName = pkg_name
- , pSourceDir = plCabalProjectDir projloc
- , pCabalFile = CabalFile pcV1CabalFile
- , pFlags = []
- , pUnits = (:|[]) Unit
- { uUnitId = UnitId pkg_name
- , uPackage = pkg { pUnits = () }
- , uDistDir = DistDirLib distdir
- , uImpl = UnitImplV1
- }
- }
- piImpl = ProjInfoV1 { piV1SetupHeader = hdr }
- return ProjInfo
- { piCabalVersion = hdrCabalVersion
- , piProjConfModTimes = pcm
- , piPackages = pkg :| []
- , piImpl
+ hdr@(UnitHeader (pkg_name_bs, _pkg_ver) ("Cabal", hdrCabalVersion) _)
+ <- readSetupConfigHeader setup_config_path
+ let
+ v3_0_0_0 = makeVersion [3,0,0,0]
+ pkg_name
+ | hdrCabalVersion >= v3_0_0_0 = BSU.toString pkg_name_bs
+ | otherwise = BS8.unpack pkg_name_bs
+ pkg = Package
+ { pPackageName = pkg_name
+ , pSourceDir = plCabalProjectDir projloc
+ , pCabalFile = CabalFile pcV1CabalFile
+ , pFlags = []
+ , pUnits = (:|[]) Unit
+ { uUnitId = UnitId pkg_name
+ , uPackage = pkg { pUnits = () }
+ , uDistDir = DistDirLib distdir
+ , uImpl = UnitImplV1
}
- Just UnitHeader {uhSetupId=(setup_name, _)} ->
- panicIO $ printf "Unknown Setup package-id in setup-config header '%s': '%s'"
- (BS8.unpack setup_name) setup_config_path
- Nothing ->
- panicIO $ printf "Could not read '%s' header" setup_config_path
+ }
+ piImpl = ProjInfoV1
+ { piV1SetupHeader = hdr
+ , piV1CabalVersion = CabalVersion hdrCabalVersion
+ }
+ return ProjInfo
+ { piProjConfModTimes = pcm
+ , piPackages = pkg :| []
+ , piImpl
+ }
(DistDirCabal SCV2 distdirv2, _) -> do
let plan_path = distdirv2 </> "cache" </> "plan.json"
@@ -591,8 +618,7 @@ readProjInfo qe pc pcm pi = withVerbosity $ do
Just pkgs <- NonEmpty.nonEmpty <$> CabalInstall.planPackages plan
return ProjInfo
- { piCabalVersion = makeDataVersion pjCabalLibVersion
- , piProjConfModTimes = pcm
+ { piProjConfModTimes = pcm
, piPackages = NonEmpty.sortWith pPackageName pkgs
, piImpl = ProjInfoV2
{ piV2Plan = plan
@@ -603,32 +629,12 @@ readProjInfo qe pc pcm pi = withVerbosity $ do
(DistDirStack{}, _) -> do
Just cabal_files <- NonEmpty.nonEmpty <$> Stack.listPackageCabalFiles qe
pkgs <- mapM (Stack.getPackage qe) cabal_files
- Just (cabalVer:_) <- runMaybeT $
- let ?progs = qePrograms qe in
- let PreInfoStack {piStackProjPaths} = pi in
- GHC.listCabalVersions (Just (sppGlobalPkgDb piStackProjPaths))
- -- ^ See [Note Stack Cabal Version]
return ProjInfo
- { piCabalVersion = cabalVer
- , piProjConfModTimes = pcm
+ { piProjConfModTimes = pcm
, piPackages = NonEmpty.sortWith pPackageName pkgs
, piImpl = ProjInfoStack
}
--- [Note Stack Cabal Version]
---
--- Stack just uses ghc-pkg on the global-pkg-db to determine the
--- appropriate Cabal version for a resolver when building, see
--- Stack.Setup.pathsFromCompiler(cabalPkgVer). We do essentially the same
--- thing here.
---
--- The code for building Setup.hs is in Stack.Build.Execute and the version
--- of cabal is set in withSingleContext.withCabal.getPackageArgs.
---
--- Note there is some special casing going on (see 'depsMinusCabal'), they
--- use the packages from the snapshot pkg-db except Cabal which comes from
--- the global pkg-db.
-
readUnitInfo :: Helper pt -> Unit pt -> UnitModTimes -> IO UnitInfo
readUnitInfo helper u@Unit{uImpl=ui@UnitImplV2{uiV2Components}} umt
| ChSetupHsName `elem` map fst uiV2Components = do
@@ -712,7 +718,8 @@ prepare :: Query pt ()
prepare = Query $ \qe -> do
pre_info <- getPreInfo qe
proj_info <- getProjInfo qe
- void $ getHelper pre_info proj_info qe
+ cabal_ver <- getCabalLibVersion qe Haven'tReconfigured proj_info
+ void $ getHelper qe pre_info proj_info cabal_ver
-- | Create @cabal_macros.h@, @Paths_\<pkg\>.hs@ and other generated files
-- in the usual place. See 'Distribution.Simple.Build.initialBuildSteps'.
@@ -723,7 +730,8 @@ writeAutogenFiles :: Unit pt -> Query pt ()
writeAutogenFiles unit = Query $ \qe -> do
pre_info <- getPreInfo qe
proj_info <- getProjInfo qe
- helper <- getHelper pre_info proj_info qe
+ cabal_ver <- getCabalLibVersion qe Haven'tReconfigured proj_info
+ helper <- getHelper qe pre_info proj_info cabal_ver
void $ runHelper helper unit ["write-autogen-files"]
-- | Get the path to the sandbox package-db in a project
@@ -780,19 +788,19 @@ configurePrograms qe@QueryEnv{..} pre_info = withVerbosity $ do
newtype Helper pt
= Helper { runHelper :: Unit pt -> [String] -> IO [Maybe ChResponse] }
-getHelper :: PreInfo pt -> ProjInfo pt -> QueryEnvI c pt -> IO (Helper pt)
-getHelper _pre_info ProjInfo{piCabalVersion} qe@QueryEnv{..}
- | CabalVersion piCabalVersion == bultinCabalVersion = return $ Helper $
+getHelper :: QueryEnvI c pt -> PreInfo pt -> ProjInfo pt -> CabalVersion -> IO (Helper pt)
+getHelper qe@QueryEnv{..} _pre_info _proj_info cabal_ver
+ | cabal_ver == bultinCabalVersion = return $ Helper $
\Unit{ uDistDir=DistDirLib distdir
, uPackage=Package{pCabalFile=CabalFile cabal_file}
} args ->
let pt = dispHelperProjectType (projTypeOfQueryEnv qe) in
helper_main $ cabal_file : distdir : pt : args
-getHelper pre_info proj_info qe@QueryEnv{..} = do
+getHelper qe@QueryEnv{..} pre_info proj_info cabal_ver = do
withVerbosity $ do
let ?progs = qePrograms
t0 <- Clock.getTime Monotonic
- eexe <- compileHelper $ mkCompHelperEnv qeProjLoc qeDistDir pre_info proj_info
+ eexe <- compileHelper $ mkCompHelperEnv qeProjLoc qeDistDir pre_info proj_info cabal_ver
t1 <- Clock.getTime Monotonic
let dt = (/10^9) $ fromInteger $ Clock.toNanoSecs $ Clock.diffTimeSpec t0 t1
dt :: Float
@@ -819,17 +827,19 @@ mkCompHelperEnv
-> DistDir pt
-> PreInfo pt
-> ProjInfo pt
+ -> CabalVersion
-> CompHelperEnv
mkCompHelperEnv
projloc
(DistDirCabal SCV1 distdir)
PreInfoCabal
- ProjInfo{piCabalVersion}
+ ProjInfo {}
+ cabal_ver
= CompHelperEnv
- { cheCabalVer = CabalVersion piCabalVersion
+ { cheCabalVer = cabal_ver
, cheProjDir = plCabalProjectDir projloc
, cheProjLocalCacheDir = distdir
- , chePkgDb = Nothing
+ , chePkgDb = []
, chePlanJson = Nothing
, cheDistV2 = Nothing
}
@@ -838,12 +848,13 @@ mkCompHelperEnv
(DistDirCabal SCV2 distdir)
PreInfoCabal
ProjInfo{piImpl=ProjInfoV2{piV2Plan=plan}}
+ cabal_ver
= CompHelperEnv {..}
where
cheProjDir = plCabalProjectDir projloc
- cheCabalVer = CabalVersion $ makeDataVersion pjCabalLibVersion
+ cheCabalVer = cabal_ver
cheProjLocalCacheDir = distdir </> "cache"
- chePkgDb = Nothing
+ chePkgDb = []
chePlanJson = Just plan
cheDistV2 = Just distdir
PlanJson {pjCabalLibVersion=Ver pjCabalLibVersion } = plan
@@ -852,16 +863,17 @@ mkCompHelperEnv
(DistDirStack mworkdir)
PreInfoStack
{ piStackProjPaths=StackProjPaths
- { sppGlobalPkgDb }
+ { sppGlobalPkgDb, sppSnapPkgDb, sppLocalPkgDb }
}
- ProjInfo { piCabalVersion }
+ ProjInfo {}
+ cabal_ver
= let workdir = fromMaybe ".stack-work" $ unRelativePath <$> mworkdir in
let projdir = takeDirectory stack_yaml in
CompHelperEnv
- { cheCabalVer = CabalVersion $ piCabalVersion
+ { cheCabalVer = cabal_ver
, cheProjDir = projdir
, cheProjLocalCacheDir = projdir </> workdir
- , chePkgDb = Just sppGlobalPkgDb
+ , chePkgDb = [sppGlobalPkgDb, sppSnapPkgDb, sppLocalPkgDb]
, chePlanJson = Nothing
, cheDistV2 = Nothing
}
diff --git a/src/CabalHelper/Compiletime/Cabal.hs b/src/CabalHelper/Compiletime/Cabal.hs
index aad004c..1ecf01f 100644
--- a/src/CabalHelper/Compiletime/Cabal.hs
+++ b/src/CabalHelper/Compiletime/Cabal.hs
@@ -31,6 +31,7 @@ import Data.Version
import System.Directory
import System.FilePath
import System.IO
+import Text.Printf
import Distribution.Verbosity (Verbosity, silent, normal, verbose, deafening)
@@ -223,9 +224,18 @@ complainIfNoCabalFile pkgdir Nothing =
bultinCabalVersion :: CabalVersion
bultinCabalVersion = CabalVersion $ parseVer VERSION_Cabal
-readSetupConfigHeader :: FilePath -> IO (Maybe UnitHeader)
+readSetupConfigHeader :: FilePath -> IO UnitHeader
readSetupConfigHeader file = bracket (openFile file ReadMode) hClose $ \h -> do
- parseSetupHeader <$> BS.hGetLine h
+ mhdr <- parseSetupHeader <$> BS.hGetLine h
+ case mhdr of
+ Just hdr@(UnitHeader _PkgId ("Cabal", _hdrCabalVersion) _compId) -> do
+ return hdr
+ Just UnitHeader {uhSetupId=(setup_name, _)} -> panicIO $
+ printf "Unknown Setup package-id in setup-config header '%s': '%s'"
+ (BS8.unpack setup_name) file
+ Nothing -> panicIO $
+ printf "Could not read '%s' header" file
+
parseSetupHeader :: BS.ByteString -> Maybe UnitHeader
parseSetupHeader header = case BS8.words header of
diff --git a/src/CabalHelper/Compiletime/Compile.hs b/src/CabalHelper/Compiletime/Compile.hs
index 2993906..4c92fba 100644
--- a/src/CabalHelper/Compiletime/Compile.hs
+++ b/src/CabalHelper/Compiletime/Compile.hs
@@ -91,7 +91,7 @@ data CompilationProductScope = CPSGlobal | CPSProject
type CompHelperEnv = CompHelperEnv' CabalVersion
data CompHelperEnv' cv = CompHelperEnv
{ cheCabalVer :: !cv
- , chePkgDb :: !(Maybe PackageDbDir)
+ , chePkgDb :: ![PackageDbDir]
-- ^ A package-db where we are guaranteed to find Cabal-`cheCabalVer`.
, cheProjDir :: !FilePath
, chePlanJson :: !(Maybe PlanJson)
@@ -120,7 +120,7 @@ compileHelper' CompHelperEnv {..} = do
CabalVersion cabalVerPlain -> do
runMaybeT $ msum $ map (\f -> f ghcVer cabalVerPlain) $
case chePkgDb of
- Nothing ->
+ [] ->
[ compileWithCabalV2Inplace
, compileWithCabalV2GhcEnv
, compileCabalSource
@@ -128,8 +128,8 @@ compileHelper' CompHelperEnv {..} = do
, compileGlobal
, compileWithCabalInPrivatePkgDb
]
- Just db ->
- [ ((.).(.)) liftIO (compilePkgDb db)
+ dbs ->
+ [ ((.).(.)) liftIO (compilePkgDbs dbs)
]
appdir <- appCacheDir
let cp@CompPaths {compExePath} = compPaths appdir cheProjLocalCacheDir comp
@@ -149,11 +149,11 @@ compileHelper' CompHelperEnv {..} = do
-- for relaxed deps: find (sameMajorVersionAs cheCabalVer) . reverse . sort
- compilePkgDb db _ghcVer cabalVer = return $
+ compilePkgDbs dbs _ghcVer cabalVer = return $
(,)
(pure ())
CompileWithCabalPackage
- { compPackageSource = GPSPackageDBs [db]
+ { compPackageSource = GPSPackageDBs dbs
, compCabalVersion = CabalVersion cabalVer
, compProductTarget = CPSProject
}
diff --git a/src/CabalHelper/Compiletime/Types.hs b/src/CabalHelper/Compiletime/Types.hs
index bb36df8..07596a9 100644
--- a/src/CabalHelper/Compiletime/Types.hs
+++ b/src/CabalHelper/Compiletime/Types.hs
@@ -456,8 +456,7 @@ newtype ProjConfModTimes = ProjConfModTimes [(FilePath, EpochTime)]
-- | Project-scope information cache.
data ProjInfo pt = ProjInfo
- { piCabalVersion :: !Version
- , piPackages :: !(NonEmpty (Package pt))
+ { piPackages :: !(NonEmpty (Package pt))
, piImpl :: !(ProjInfoImpl pt)
, piProjConfModTimes :: !ProjConfModTimes
-- ^ Key for cache invalidation. When this is not equal to the return
@@ -466,13 +465,14 @@ data ProjInfo pt = ProjInfo
data ProjInfoImpl pt where
ProjInfoV1 ::
- { piV1SetupHeader :: !UnitHeader
+ { piV1SetupHeader :: !UnitHeader
+ , piV1CabalVersion :: !CabalVersion
} -> ProjInfoImpl ('Cabal 'CV1)
ProjInfoV2 ::
- { piV2Plan :: !PlanJson
- , piV2PlanModTime :: !EpochTime
- , piV2CompilerId :: !(String, Version)
+ { piV2Plan :: !PlanJson
+ , piV2PlanModTime :: !EpochTime
+ , piV2CompilerId :: !(String, Version)
} -> ProjInfoImpl ('Cabal 'CV2)
ProjInfoStack :: ProjInfoImpl 'Stack
diff --git a/tests/CompileTest.hs b/tests/CompileTest.hs
index 02580f8..e77e3de 100644
--- a/tests/CompileTest.hs
+++ b/tests/CompileTest.hs
@@ -155,11 +155,11 @@ testCabalVersions versions = do
mcabalVersions <- runMaybeT $ listCabalVersions (Just db)
case mcabalVersions of
Just [hdver] ->
- return $ che0 (CabalVersion hdver) (Just db)
+ return $ che0 (CabalVersion hdver) [db]
_ ->
- return $ che0 (CabalHEAD ()) Nothing
+ return $ che0 (CabalHEAD ()) []
(CabalVersion ver) ->
- return $ che0 (CabalVersion ver) Nothing
+ return $ che0 (CabalVersion ver) []
compileHelper che
diff --git a/tests/GhcSession.hs b/tests/GhcSession.hs
index a4e7d62..c776164 100644
--- a/tests/GhcSession.hs
+++ b/tests/GhcSession.hs
@@ -2,8 +2,8 @@
DataKinds, ExistentialQuantification, PolyKinds, ViewPatterns,
DeriveFunctor, MonoLocalBinds, GADTs, MultiWayIf #-}
-{-| This test ensures we can get a GHC API session up and running in a variety of
- project environments.
+{-| This test ensures we can get a GHC API session up and running in a
+ variety of project environments.
-}
module Main where
@@ -126,13 +126,31 @@ main = do
-- fucking awesome store cache to keep CI times down.
--
-- TODO: Better test coverage for helper compilation with the other two!
- [ TC (TN "exelib") (parseVer "1.10") (parseVer "0") []
- , TC (TN "exeintlib") (parseVer "2.0") (parseVer "0") []
- , TC (TN "fliblib") (parseVer "2.0") (parseVer "0") []
- , TC (TN "bkpregex") (parseVer "2.0") (parseVer "8.1") [Cabal CV2, Cabal CV1]
- , TC (TN "src-repo") (parseVer "2.4") (parseVer "0") [Cabal CV2]
+ [ TC (TN "exelib") (parseVer "1.10") (parseVer "0") []
+ , TC (TN "exeintlib") (parseVer "2.0") (parseVer "0") []
+ , TC (TN "fliblib") (parseVer "2.0") (parseVer "0") []
+ , TC (TN "custom-setup") (parseVer "1.24") (parseVer "0") [Cabal CV2, Stack]
+ -- ^ Custom setup has issues in v1. Specifically we can get into the
+ -- situation where v1-configure --with-ghc=... will pick one Cabal
+ -- lib version but then v1-build (without --with-ghc) will pick
+ -- another because the system ghc has different packages available
+ -- than the --with-ghc one.
+ --
+ -- At this point a setup recompile happens and hell breaks loose
+ -- because setup-config is mismatched. The reason we can't just pass
+ -- --with-ghc to v1-build to fix this is that it will actually ignore
+ -- it as far as setup compilation is concerned while v1-configure
+ -- will pick it up.
+ --
+ -- We could fuck around with $PATH in the v1-build case too but I
+ -- really don't think that many people use v1 still and with
+ -- built-type:custom no less.
+ --
+ -- See haskell/cabal#6749
+ , TC (TN "bkpregex") (parseVer "2.0") (parseVer "8.1") [Cabal CV2, Cabal CV1]
+ , TC (TN "src-repo") (parseVer "2.4") (parseVer "0") [Cabal CV2]
, let multipkg_loc = TF "tests/multipkg/" "proj/" "proj/proj.cabal" in
- TC multipkg_loc (parseVer "1.10") (parseVer "0") [Cabal CV2, Stack]
+ TC multipkg_loc (parseVer "1.10") (parseVer "0") [Cabal CV2, Stack]
-- min Cabal lib ver -^ min GHC ver -^
]
diff --git a/tests/custom-setup/Lib.hs b/tests/custom-setup/Lib.hs
new file mode 100644
index 0000000..417a0ad
--- /dev/null
+++ b/tests/custom-setup/Lib.hs
@@ -0,0 +1,8 @@
+module Lib where
+
+import System.Directory
+import System.FilePath
+
+filepath = "a" </> "b"
+directory = doesFileExist "Exe.hs"
+foo = 1
diff --git a/tests/custom-setup/Setup.hs b/tests/custom-setup/Setup.hs
new file mode 100644
index 0000000..9a994af
--- /dev/null
+++ b/tests/custom-setup/Setup.hs
@@ -0,0 +1,2 @@
+import Distribution.Simple
+main = defaultMain
diff --git a/tests/custom-setup/custom-setup.cabal b/tests/custom-setup/custom-setup.cabal
new file mode 100644
index 0000000..63410ac
--- /dev/null
+++ b/tests/custom-setup/custom-setup.cabal
@@ -0,0 +1,13 @@
+name: custom-setup
+version: 0
+build-type: Custom
+cabal-version: >=1.10
+extra-source-files: stack.yaml
+
+custom-setup
+ setup-depends: base, Cabal
+
+library
+ exposed-modules: Lib
+ build-depends: base, filepath, directory
+ default-language: Haskell2010
diff --git a/tests/custom-setup/packages.list b/tests/custom-setup/packages.list
new file mode 100644
index 0000000..80e52ce
--- /dev/null
+++ b/tests/custom-setup/packages.list
@@ -0,0 +1 @@
+./
diff --git a/tests/custom-setup/stack.yaml b/tests/custom-setup/stack.yaml
new file mode 100644
index 0000000..27cc995
--- /dev/null
+++ b/tests/custom-setup/stack.yaml
@@ -0,0 +1,3 @@
+resolver: lts-0.0 # will be overridden on the commandline
+packages:
+- ./