From 80fe5e176dca3e7099bc4607214607a4a64246f4 Mon Sep 17 00:00:00 2001 From: Michael Snoyman Date: Mon, 24 Jul 2017 09:55:10 +0300 Subject: [PATCH 1/7] Upgrade to Cabal 2.0 --- ChangeLog.md | 1 + Setup.hs | 19 ++++---- src/Stack/Build/ConstructPlan.hs | 2 +- src/Stack/BuildPlan.hs | 3 +- src/Stack/Config.hs | 9 ++-- src/Stack/Init.hs | 2 +- src/Stack/Options/Completion.hs | 7 +-- src/Stack/Package.hs | 74 +++++++++++++++++++------------- src/Stack/Setup.hs | 3 +- src/Stack/Snapshot.hs | 6 ++- src/Stack/Types/Config.hs | 4 +- src/Stack/Types/FlagName.hs | 6 +-- src/Stack/Types/PackageName.hs | 6 +-- src/Stack/Types/Version.hs | 6 +-- src/Stack/Upgrade.hs | 3 +- src/main/Main.hs | 3 +- stack-7.10.yaml | 2 +- stack-nightly.yaml | 1 + stack.cabal | 8 ++-- stack.yaml | 1 + 20 files changed, 97 insertions(+), 69 deletions(-) diff --git a/ChangeLog.md b/ChangeLog.md index 905b58c159..351b5e0e6b 100644 --- a/ChangeLog.md +++ b/ChangeLog.md @@ -11,6 +11,7 @@ Major changes: details, please see [the writeup on these changes](https://www.fpcomplete.com/blog/2017/07/stacks-new-extensible-snapshots). [PR #3249](https://github.com/commercialhaskell/stack/pull/3249), see the PR description for a number of related issues. +* Upgraded to version 2.0 of the Cabal library. Behavior changes: diff --git a/Setup.hs b/Setup.hs index 179845c1dd..6bae7f52c3 100644 --- a/Setup.hs +++ b/Setup.hs @@ -3,8 +3,7 @@ module Main (main) where import Data.List ( nub, sortBy ) import Data.Ord ( comparing ) -import Data.Version ( showVersion ) -import Distribution.Package ( PackageName(PackageName), PackageId, InstalledPackageId, packageVersion, packageName ) +import Distribution.Package ( PackageId, InstalledPackageId, packageVersion, packageName ) import Distribution.PackageDescription ( PackageDescription(), Executable(..) ) import Distribution.InstalledPackageInfo (sourcePackageId, installedPackageId) import Distribution.Simple ( defaultMainWithHooks, UserHooks(..), simpleUserHooks ) @@ -13,7 +12,10 @@ import Distribution.Simple.BuildPaths ( autogenModulesDir ) import Distribution.Simple.PackageIndex (allPackages, dependencyClosure) import Distribution.Simple.Setup ( BuildFlags(buildVerbosity), fromFlag ) import Distribution.Simple.LocalBuildInfo ( installedPkgs, withLibLBI, withExeLBI, LocalBuildInfo(), ComponentLocalBuildInfo(componentPackageDeps) ) +import Distribution.Types.PackageName (PackageName, unPackageName) +import Distribution.Types.UnqualComponentName (unUnqualComponentName) import Distribution.Verbosity ( Verbosity ) +import Distribution.Version ( showVersion ) import System.FilePath ( () ) main :: IO () @@ -29,27 +31,28 @@ generateBuildModule verbosity pkg lbi = do createDirectoryIfMissingVerbose verbosity True dir withLibLBI pkg lbi $ \_ libcfg -> do withExeLBI pkg lbi $ \exe clbi -> - rewriteFile (dir "Build_" ++ exeName exe ++ ".hs") $ unlines - [ "module Build_" ++ exeName exe ++ " where" + rewriteFile (dir "Build_" ++ exeName' exe ++ ".hs") $ unlines + [ "module Build_" ++ exeName' exe ++ " where" , "" , "deps :: [String]" , "deps = " ++ (show $ formatdeps (transDeps libcfg clbi)) ] where + exeName' = unUnqualComponentName . exeName formatdeps = map formatone . sortBy (comparing unPackageName') formatone p = unPackageName' p ++ "-" ++ showVersion (packageVersion p) - unPackageName' p = case packageName p of PackageName n -> n + unPackageName' = unPackageName . packageName transDeps xs ys = either (map sourcePackageId . allPackages) handleDepClosureFailure $ dependencyClosure allInstPkgsIdx availInstPkgIds where allInstPkgsIdx = installedPkgs lbi allInstPkgIds = map installedPackageId $ allPackages allInstPkgsIdx -- instPkgIds includes `stack-X.X.X`, which is not a depedency hence is missing from allInstPkgsIdx. Filter that out. - availInstPkgIds = filter (`elem` allInstPkgIds) . map fst $ testDeps xs ys + availInstPkgIds = filter (`elem` allInstPkgIds) $ testDeps xs ys handleDepClosureFailure unsatisfied = error $ "Computation of transitive dependencies failed." ++ if null unsatisfied then "" else " Unresolved dependencies: " ++ show unsatisfied -testDeps :: ComponentLocalBuildInfo -> ComponentLocalBuildInfo -> [(InstalledPackageId, PackageId)] -testDeps xs ys = nub $ componentPackageDeps xs ++ componentPackageDeps ys +testDeps :: ComponentLocalBuildInfo -> ComponentLocalBuildInfo -> [InstalledPackageId] +testDeps xs ys = map fst $ nub $ componentPackageDeps xs ++ componentPackageDeps ys diff --git a/src/Stack/Build/ConstructPlan.hs b/src/Stack/Build/ConstructPlan.hs index a8975582ef..9be0fe814e 100644 --- a/src/Stack/Build/ConstructPlan.hs +++ b/src/Stack/Build/ConstructPlan.hs @@ -795,7 +795,7 @@ packageDepsWithTools p = do ctx <- ask -- TODO: it would be cool to defer these warnings until there's an -- actual issue building the package. - let toEither (Cabal.Dependency (Cabal.PackageName name) _) mp = + let toEither (Cabal.Dependency (Cabal.unPackageName -> name) _) mp = case Map.toList mp of [] -> Left (NoToolFound name (packageName p)) [_] -> Right mp diff --git a/src/Stack/BuildPlan.hs b/src/Stack/BuildPlan.hs index b3aeeea7dd..7e44b5aab3 100644 --- a/src/Stack/BuildPlan.hs +++ b/src/Stack/BuildPlan.hs @@ -44,6 +44,7 @@ import Distribution.PackageDescription (GenericPackageDescription, flagName, genPackageFlags, condExecutables) import qualified Distribution.PackageDescription as C +import qualified Distribution.Types.UnqualComponentName as C import Distribution.System (Platform) import Distribution.Text (display) import qualified Distribution.Version as C @@ -186,7 +187,7 @@ getToolMap ls locals = -- worse case scenario is we build an extra package that wasn't -- strictly needed. gpdExes :: GenericPackageDescription -> [Text] - gpdExes = map (T.pack . fst) . condExecutables + gpdExes = map (T.pack . C.unUnqualComponentName . fst) . condExecutables gpdPackages :: [GenericPackageDescription] -> Map PackageName Version gpdPackages gpds = Map.fromList $ diff --git a/src/Stack/Config.hs b/src/Stack/Config.hs index 1c5ae21e6b..ee85860692 100644 --- a/src/Stack/Config.hs +++ b/src/Stack/Config.hs @@ -59,9 +59,10 @@ import qualified Data.Text as T import Data.Text.Encoding (encodeUtf8) import qualified Data.Yaml as Yaml import qualified Distribution.PackageDescription as C +import qualified Distribution.Types.UnqualComponentName as C import Distribution.System (OS (..), Platform (..), buildPlatform, Arch(OtherArch)) import qualified Distribution.Text -import Distribution.Version (simplifyVersionRange) +import Distribution.Version (simplifyVersionRange, mkVersion') import GHC.Conc (getNumProcessors) import Lens.Micro (lens) import Network.HTTP.Client (parseUrlThrow) @@ -473,7 +474,7 @@ loadConfigMaybeProject configArgs mresolver mproject = do LCSNoConfig _ -> configNoLocalConfig stackRoot mresolver configArgs LCSProject project -> loadHelper $ Just project LCSNoProject -> loadHelper Nothing - unless (fromCabalVersion Meta.version `withinRange` configRequireStackVersion config) + unless (fromCabalVersion (mkVersion' Meta.version) `withinRange` configRequireStackVersion config) (throwM (BadStackVersionException (configRequireStackVersion config))) let mprojectRoot = fmap (\(_, fp, _) -> parent fp) mproject @@ -708,9 +709,9 @@ getNamedComponents gpkg = Set.fromList $ concat ] where go :: (T.Text -> NamedComponent) - -> (C.GenericPackageDescription -> [String]) + -> (C.GenericPackageDescription -> [C.UnqualComponentName]) -> [NamedComponent] - go wrapper f = map (wrapper . T.pack) $ f gpkg + go wrapper f = map (wrapper . T.pack . C.unUnqualComponentName) $ f gpkg -- | Check if there are any duplicate package names and, if so, throw an -- exception. diff --git a/src/Stack/Init.hs b/src/Stack/Init.hs index e8381e8edc..0231058af4 100644 --- a/src/Stack/Init.hs +++ b/src/Stack/Init.hs @@ -293,7 +293,7 @@ renderStackYaml p ignoredPackages dupPackages = footerHelp = let major = toCabalVersion - $ toMajorVersion $ fromCabalVersion Meta.version + $ toMajorVersion $ fromCabalVersion $ C.mkVersion' Meta.version in commentHelp [ "Control whether we use the GHC we find on the path" , "system-ghc: true" diff --git a/src/Stack/Options/Completion.hs b/src/Stack/Options/Completion.hs index e316095d45..af26b2efac 100644 --- a/src/Stack/Options/Completion.hs +++ b/src/Stack/Options/Completion.hs @@ -18,6 +18,7 @@ import Data.Maybe import qualified Data.Set as Set import qualified Data.Text as T import qualified Distribution.PackageDescription as C +import qualified Distribution.Types.UnqualComponentName as C import Options.Applicative import Options.Applicative.Builder.Extra import Stack.Config (getLocalPackages) @@ -89,8 +90,8 @@ flagCompleter = buildConfigCompleter $ \input -> do (C.genPackageFlags (lpvGPD lpv))) $ Map.toList lpvs flagString name fl = - case C.flagName fl of - C.FlagName flname -> (if flagEnabled name fl then "-" else "") ++ flname + let flname = C.unFlagName $ C.flagName fl + in (if flagEnabled name fl then "-" else "") ++ flname flagEnabled name fl = fromMaybe (C.flagDefault fl) $ Map.lookup (fromCabalFlagName (C.flagName fl)) $ @@ -107,5 +108,5 @@ projectExeCompleter = buildConfigCompleter $ \input -> do return $ filter (input `isPrefixOf`) $ nubOrd $ - concatMap (\(_, lpv) -> map fst (C.condExecutables (lpvGPD lpv))) $ + concatMap (\(_, lpv) -> map (C.unUnqualComponentName . fst) (C.condExecutables (lpvGPD lpv))) $ Map.toList lpvs diff --git a/src/Stack/Package.hs b/src/Stack/Package.hs index f22fb33d36..3a028c0000 100644 --- a/src/Stack/Package.hs +++ b/src/Stack/Package.hs @@ -51,7 +51,6 @@ import qualified Data.Set as S import qualified Data.Text as T import Data.Text.Encoding (decodeUtf8, decodeUtf8With) import Data.Text.Encoding.Error (lenientDecode) -import Data.Version (showVersion) import Distribution.Compiler import Distribution.ModuleName (ModuleName) import qualified Distribution.ModuleName as Cabal @@ -65,7 +64,13 @@ import Distribution.ParseUtils import Distribution.Simple.Utils import Distribution.System (OS (..), Arch, Platform (..)) import qualified Distribution.Text as D +import qualified Distribution.Types.CondTree as Cabal +import qualified Distribution.Types.Dependency as Cabal +import qualified Distribution.Types.ExeDependency as Cabal +import qualified Distribution.Types.LegacyExeDependency as Cabal +import qualified Distribution.Types.UnqualComponentName as Cabal import qualified Distribution.Verbosity as D +import Distribution.Version (showVersion) import qualified Hpack import qualified Hpack.Config as Hpack import Path as FL @@ -116,7 +121,7 @@ readPackageUnresolvedBS source bs = rawParseGPD :: BS.ByteString -> Either PError ([PWarning], GenericPackageDescription) rawParseGPD bs = - case parsePackageDescription chars of + case parseGenericPackageDescription chars of ParseFailed per -> Left per ParseOk warnings gpkg -> Right (warnings,gpkg) where @@ -217,7 +222,9 @@ packageFromPackageDescription packageConfig pkgFlags pkg = , packageLicense = license pkg , packageDeps = deps , packageFiles = pkgFiles - , packageTools = packageDescTools pkg + , packageTools = map + (\(Cabal.ExeDependency name' _ range) -> Cabal.Dependency name' range) + (packageDescTools pkg) , packageGhcOptions = packageConfigGhcOptions packageConfig , packageFlags = packageConfigFlags packageConfig , packageDefaultFlags = M.fromList @@ -225,13 +232,14 @@ packageFromPackageDescription packageConfig pkgFlags pkg = , packageAllDeps = S.fromList (M.keys deps) , packageHasLibrary = maybe False (buildable . libBuildInfo) (library pkg) , packageTests = M.fromList - [(T.pack (testName t), testInterface t) | t <- testSuites pkg + [(T.pack (Cabal.unUnqualComponentName $ testName t), testInterface t) | t <- testSuites pkg , buildable (testBuildInfo t)] , packageBenchmarks = S.fromList - [T.pack (benchmarkName biBuildInfo) | biBuildInfo <- benchmarks pkg + [T.pack (Cabal.unUnqualComponentName $ benchmarkName biBuildInfo) | biBuildInfo <- benchmarks pkg , buildable (benchmarkBuildInfo biBuildInfo)] , packageExes = S.fromList - [T.pack (exeName biBuildInfo) | biBuildInfo <- executables pkg + [T.pack (Cabal.unUnqualComponentName $ exeName biBuildInfo) + | biBuildInfo <- executables pkg , buildable (buildInfo biBuildInfo)] -- This is an action used to collect info needed for "stack ghci". -- This info isn't usually needed, so computation of it is deferred. @@ -338,19 +346,19 @@ generatePkgDescOpts sourceMap installedMap omitPkgs addPkgs cabalfp pkg componen , fmap (\exe -> generate - (CExe (T.pack (exeName exe))) + (CExe (T.pack (Cabal.unUnqualComponentName (exeName exe)))) (buildInfo exe)) (executables pkg) , fmap (\bench -> generate - (CBench (T.pack (benchmarkName bench))) + (CBench (T.pack (Cabal.unUnqualComponentName (benchmarkName bench)))) (benchmarkBuildInfo bench)) (benchmarks pkg) , fmap (\test -> generate - (CTest (T.pack (testName test))) + (CTest (T.pack (Cabal.unUnqualComponentName (testName test)))) (testBuildInfo test)) (testSuites pkg)])) where @@ -531,13 +539,13 @@ packageDependencies pkg = packageToolDependencies :: PackageDescription -> Map Text VersionRange packageToolDependencies = M.fromList . - concatMap (fmap (packageNameText . depName &&& depRange) . + concatMap (fmap (\(Cabal.LegacyExeDependency name range) -> (T.pack name, range)) . buildTools) . allBuildInfo' -- | Get all dependencies of the package (buildable targets only). -packageDescTools :: PackageDescription -> [Dependency] -packageDescTools = concatMap buildTools . allBuildInfo' +packageDescTools :: PackageDescription -> [Cabal.ExeDependency] +packageDescTools = concatMap buildToolDepends . allBuildInfo' -- | This is a copy-paste from Cabal's @allBuildInfo@ function, but with the -- @buildable@ test removed. The implementation is broken. @@ -551,12 +559,10 @@ allBuildInfo' pkg_descr = [ bi | Just lib <- [library pkg_descr] , True || buildable bi ] ++ [ bi | tst <- testSuites pkg_descr , let bi = testBuildInfo tst - , True || buildable bi - , testEnabled tst ] + , True || buildable bi ] ++ [ bi | tst <- benchmarks pkg_descr , let bi = benchmarkBuildInfo tst - , True || buildable bi - , benchmarkEnabled tst ] + , True || buildable bi ] -- | Get all files referenced by the package. packageDescModulesAndFiles @@ -596,9 +602,9 @@ packageDescModulesAndFiles pkg = do return (modules, files, dfiles, warnings) where libComponent = const CLib - exeComponent = CExe . T.pack . exeName - testComponent = CTest . T.pack . testName - benchComponent = CBench . T.pack . benchmarkName + exeComponent = CExe . T.pack . Cabal.unUnqualComponentName . exeName + testComponent = CTest . T.pack . Cabal.unUnqualComponentName . testName + benchComponent = CBench . T.pack . Cabal.unUnqualComponentName . benchmarkName asModuleAndFileMap label f lib = do (a,b,c) <- f lib return (M.singleton (label lib) a, M.singleton (label lib) b, c) @@ -651,7 +657,7 @@ resolveGlobFiles = -- matchDirFileGlob_ :: (MonadLogger m, MonadIO m) => String -> String -> m [String] matchDirFileGlob_ dir filepath = case parseFileGlob filepath of - Nothing -> liftIO $ die $ + Nothing -> liftIO $ throwString $ "invalid file glob '" ++ filepath ++ "'. Wildcards '*' are only allowed in place of the file" ++ " name, not in the directory name or file extension." @@ -681,7 +687,7 @@ benchmarkFiles bench = do dir <- asks (parent . fst) (modules,files,warnings) <- resolveFilesAndDeps - (Just $ benchmarkName bench) + (Just $ Cabal.unUnqualComponentName $ benchmarkName bench) (dirs ++ [dir]) (bnames <> exposed) haskellModuleExts @@ -705,7 +711,7 @@ testFiles test = do dir <- asks (parent . fst) (modules,files,warnings) <- resolveFilesAndDeps - (Just $ testName test) + (Just $ Cabal.unUnqualComponentName $ testName test) (dirs ++ [dir]) (bnames <> exposed) haskellModuleExts @@ -730,7 +736,7 @@ executableFiles exe = do dir <- asks (parent . fst) (modules,files,warnings) <- resolveFilesAndDeps - (Just $ exeName exe) + (Just $ Cabal.unUnqualComponentName $ exeName exe) (dirs ++ [dir]) (map DotCabalModule (otherModules build) ++ [DotCabalMain (modulePath exe)]) @@ -782,7 +788,7 @@ targetJsSources = jsSources resolvePackageDescription :: PackageConfig -> GenericPackageDescription -> PackageDescription -resolvePackageDescription packageConfig (GenericPackageDescription desc defaultFlags mlib exes tests benches) = +resolvePackageDescription packageConfig (GenericPackageDescription desc defaultFlags mlib _subLibs _foreignLibs exes tests benches) = desc {library = fmap (resolveConditions rc updateLibDeps) mlib ,executables = @@ -811,12 +817,18 @@ resolvePackageDescription packageConfig (GenericPackageDescription desc defaultF (buildInfo exe) {targetBuildDepends = deps}} updateTestDeps test deps = test {testBuildInfo = - (testBuildInfo test) {targetBuildDepends = deps} - ,testEnabled = packageConfigEnableTests packageConfig} + (testBuildInfo test) + { targetBuildDepends = deps + , buildable = packageConfigEnableTests packageConfig + } + } updateBenchmarkDeps benchmark deps = benchmark {benchmarkBuildInfo = - (benchmarkBuildInfo benchmark) {targetBuildDepends = deps} - ,benchmarkEnabled = packageConfigEnableBenchmarks packageConfig} + (benchmarkBuildInfo benchmark) + { targetBuildDepends = deps + , buildable = packageConfigEnableBenchmarks packageConfig + } + } -- | Make a map from a list of flag specifications. -- @@ -854,7 +866,7 @@ resolveConditions :: (Monoid target,Show target) resolveConditions rc addDeps (CondNode lib deps cs) = basic <> children where basic = addDeps lib deps children = mconcat (map apply cs) - where apply (cond,node,mcs) = + where apply (Cabal.CondBranch cond node mcs) = if condSatisfied cond then resolveConditions rc addDeps node else maybe mempty (resolveConditions rc addDeps) mcs @@ -1256,10 +1268,10 @@ cabalFilePackageId :: (MonadIO m, MonadThrow m) => Path Abs File -> m PackageIdentifier cabalFilePackageId fp = do - pkgDescr <- liftIO (D.readPackageDescription D.silent $ toFilePath fp) + pkgDescr <- liftIO (D.readGenericPackageDescription D.silent $ toFilePath fp) (toStackPI . D.package . D.packageDescription) pkgDescr where - toStackPI (D.PackageIdentifier (D.PackageName name) ver) = do + toStackPI (D.PackageIdentifier (D.unPackageName -> name) ver) = do name' <- parsePackageNameFromString name ver' <- parseVersionFromString (showVersion ver) return (PackageIdentifier name' ver') diff --git a/src/Stack/Setup.hs b/src/Stack/Setup.hs index 8c357ba252..0573208508 100644 --- a/src/Stack/Setup.hs +++ b/src/Stack/Setup.hs @@ -63,6 +63,7 @@ import qualified Data.Yaml as Yaml import Distribution.System (OS, Arch (..), Platform (..)) import qualified Distribution.System as Cabal import Distribution.Text (simpleParse) +import Distribution.Version (mkVersion') import Lens.Micro (set) import Network.HTTP.Simple (getResponseBody, httpLBS, withResponse, getResponseStatusCode) import Network.HTTP.Download @@ -1939,4 +1940,4 @@ getDownloadVersion (StackReleaseInfo val) = do parseVersion $ T.drop 1 rawName stackVersion :: Version -stackVersion = fromCabalVersion Meta.version +stackVersion = fromCabalVersion (mkVersion' Meta.version) diff --git a/src/Stack/Snapshot.hs b/src/Stack/Snapshot.hs index ca6fd4be95..b599659893 100644 --- a/src/Stack/Snapshot.hs +++ b/src/Stack/Snapshot.hs @@ -38,6 +38,7 @@ import Data.Yaml (decodeFileEither, ParseException (AesonException)) import Distribution.InstalledPackageInfo (PError) import Distribution.PackageDescription (GenericPackageDescription) import qualified Distribution.PackageDescription as C +import qualified Distribution.Types.UnqualComponentName as C import Distribution.System (Platform) import Distribution.Text (display) import qualified Distribution.Version as C @@ -787,7 +788,10 @@ calculate gpd platform compilerVersion loc flags hide options = , lpiPackageDeps = Map.map fromVersionRange $ Map.filterWithKey (const . (/= name)) $ packageDependencies pd - , lpiProvidedExes = Set.fromList $ map (ExeName . T.pack . C.exeName) $ C.executables pd + , lpiProvidedExes = + Set.fromList + $ map (ExeName . T.pack . C.unUnqualComponentName . C.exeName) + $ C.executables pd , lpiNeededExes = Map.mapKeys ExeName $ Map.map fromVersionRange $ packageToolDependencies pd diff --git a/src/Stack/Types/Config.hs b/src/Stack/Types/Config.hs index cdc3ecda1a..73d7170d96 100644 --- a/src/Stack/Types/Config.hs +++ b/src/Stack/Types/Config.hs @@ -193,7 +193,7 @@ import Distribution.PackageDescription (GenericPackageDescription) import Distribution.ParseUtils (PError) import Distribution.System (Platform) import qualified Distribution.Text -import Distribution.Version (anyVersion) +import Distribution.Version (anyVersion, mkVersion') import Generics.Deriving.Monoid (memptydefault, mappenddefault) import Lens.Micro (Lens', lens, _1, _2, to) import Options.Applicative (ReadM) @@ -1031,7 +1031,7 @@ instance Show ConfigException where ] show (BadStackVersionException requiredRange) = concat [ "The version of stack you are using (" - , show (fromCabalVersion Meta.version) + , show (fromCabalVersion (mkVersion' Meta.version)) , ") is outside the required\n" ,"version range specified in stack.yaml (" , T.unpack (versionRangeText requiredRange) diff --git a/src/Stack/Types/FlagName.hs b/src/Stack/Types/FlagName.hs index 47abef62b7..f891ec6891 100644 --- a/src/Stack/Types/FlagName.hs +++ b/src/Stack/Types/FlagName.hs @@ -107,12 +107,12 @@ flagNameText (FlagName n) = n -- | Convert from a Cabal flag name. fromCabalFlagName :: Cabal.FlagName -> FlagName -fromCabalFlagName (Cabal.FlagName name) = - let !x = T.pack name +fromCabalFlagName name = + let !x = T.pack $ Cabal.unFlagName name in FlagName x -- | Convert to a Cabal flag name. toCabalFlagName :: FlagName -> Cabal.FlagName toCabalFlagName (FlagName name) = let !x = T.unpack name - in Cabal.FlagName x + in Cabal.mkFlagName x diff --git a/src/Stack/Types/PackageName.hs b/src/Stack/Types/PackageName.hs index de5fdb27c4..e31fe19c78 100644 --- a/src/Stack/Types/PackageName.hs +++ b/src/Stack/Types/PackageName.hs @@ -112,15 +112,15 @@ packageNameText (PackageName n) = n -- | Convert from a Cabal package name. fromCabalPackageName :: Cabal.PackageName -> PackageName -fromCabalPackageName (Cabal.PackageName name) = - let !x = T.pack name +fromCabalPackageName name = + let !x = T.pack $ Cabal.unPackageName name in PackageName x -- | Convert to a Cabal package name. toCabalPackageName :: PackageName -> Cabal.PackageName toCabalPackageName (PackageName name) = let !x = T.unpack name - in Cabal.PackageName x + in Cabal.mkPackageName x -- | Parse a package name from a file path. parsePackageNameFromFilePath :: MonadThrow m => Path a File -> m PackageName diff --git a/src/Stack/Types/Version.hs b/src/Stack/Types/Version.hs index 457db8d775..d2e4ba441e 100644 --- a/src/Stack/Types/Version.hs +++ b/src/Stack/Types/Version.hs @@ -139,12 +139,12 @@ versionText (Version v) = -- | Convert to a Cabal version. toCabalVersion :: Version -> Cabal.Version toCabalVersion (Version v) = - Cabal.Version (map fromIntegral (V.toList v)) [] + Cabal.mkVersion (map fromIntegral (V.toList v)) -- | Convert from a Cabal version. fromCabalVersion :: Cabal.Version -> Version -fromCabalVersion (Cabal.Version vs _) = - let !v = V.fromList (map fromIntegral vs) +fromCabalVersion vs = + let !v = V.fromList (map fromIntegral (Cabal.versionNumbers vs)) in Version v -- | Make a package version. diff --git a/src/Stack/Upgrade.hs b/src/Stack/Upgrade.hs index 5664381169..a596c059f0 100644 --- a/src/Stack/Upgrade.hs +++ b/src/Stack/Upgrade.hs @@ -17,6 +17,7 @@ import qualified Data.HashMap.Strict as HashMap import qualified Data.List import qualified Data.Map as Map import qualified Data.Text as T +import Distribution.Version (mkVersion') import Lens.Micro (set) import Options.Applicative import Path @@ -218,7 +219,7 @@ sourceUpgrade gConfigMonoid mresolver builtHash (SourceOpts gitRepo) = when (null versions) (throwString "No stack found in package indices") let version = Data.List.maximum versions - if version <= fromCabalVersion Paths.version + if version <= fromCabalVersion (mkVersion' Paths.version) then do $logInfo "Already at latest version, no upgrade required" return Nothing diff --git a/src/main/Main.hs b/src/main/Main.hs index 9b636da46d..7bdc47af81 100644 --- a/src/main/Main.hs +++ b/src/main/Main.hs @@ -34,6 +34,7 @@ import Development.GitRev (gitCommitCount, gitHash) #endif import Distribution.System (buildArch, buildPlatform) import Distribution.Text (display) +import Distribution.Version (mkVersion') import GHC.IO.Encoding (mkTextEncoding, textEncodingName) import Lens.Micro import Options.Applicative @@ -173,7 +174,7 @@ main = do case globalReExecVersion global of Just expectVersion -> do expectVersion' <- parseVersionFromString expectVersion - unless (checkVersion MatchMinor expectVersion' (fromCabalVersion Meta.version)) + unless (checkVersion MatchMinor expectVersion' (fromCabalVersion (mkVersion' Meta.version))) $ throwIO $ InvalidReExecVersion expectVersion (showVersion Meta.version) _ -> return () run global `catch` \e -> diff --git a/stack-7.10.yaml b/stack-7.10.yaml index 31626e7787..b4a5e01890 100644 --- a/stack-7.10.yaml +++ b/stack-7.10.yaml @@ -15,7 +15,7 @@ flags: mintty: win32-2-5: false extra-deps: -- Cabal-1.24.2.0 +- Cabal-2.0.0.2 - th-utilities-0.2.0.1 - store-0.4.1 - store-core-0.4 diff --git a/stack-nightly.yaml b/stack-nightly.yaml index 3056fe4c95..9278300ec6 100644 --- a/stack-nightly.yaml +++ b/stack-nightly.yaml @@ -13,6 +13,7 @@ flags: mintty: win32-2-5: false extra-deps: +- Cabal-2.0.0.2 - mintty-0.1.1 - text-metrics-0.3.0 - bindings-uname-0.1 diff --git a/stack.cabal b/stack.cabal index 28ed971b96..2586c02184 100644 --- a/stack.cabal +++ b/stack.cabal @@ -31,7 +31,7 @@ extra-source-files: CONTRIBUTING.md custom-setup setup-depends: base - , Cabal + , Cabal >= 2.0 && < 2.1 , filepath flag integration-tests @@ -188,7 +188,7 @@ library System.Process.Read System.Process.Run other-modules: Hackage.Security.Client.Repository.HttpLib.HttpClient - build-depends: Cabal >= 1.24 && < 1.25 + build-depends: Cabal >= 2.0 && < 2.1 , aeson (>= 1.0 && < 1.2) , ansi-terminal >= 0.6.2.3 , attoparsec >= 0.12.1.5 && < 0.14 @@ -284,7 +284,7 @@ executable stack if flag(static) ld-options: -static -pthread - build-depends: Cabal >= 1.18.1.5 && < 1.25 + build-depends: Cabal >= 2.0 && < 2.1 , base >=4.7 && < 5 , bytestring >= 0.10.4.0 , conduit >= 1.2.8 @@ -336,7 +336,7 @@ test-suite stack-test , Stack.SolverSpec , Stack.Untar.UntarSpec ghc-options: -threaded -Wall -fwarn-tabs -fwarn-incomplete-uni-patterns -fwarn-incomplete-record-updates - build-depends: Cabal >= 1.18.1.5 && < 1.25 + build-depends: Cabal >= 2.0 && < 2.1 , QuickCheck >= 2.8.2 && < 2.10 , attoparsec < 0.14 , base >=4.7 && <5 diff --git a/stack.yaml b/stack.yaml index 29f4caa59e..500eb03bca 100644 --- a/stack.yaml +++ b/stack.yaml @@ -17,6 +17,7 @@ flags: mintty: win32-2-5: false extra-deps: +- Cabal-2.0.0.2 - mintty-0.1.1 - text-metrics-0.3.0 - unicode-transforms-0.3.2 From deff91c1adf2c2e89d898c7a9c1f7fbf741b7379 Mon Sep 17 00:00:00 2001 From: Michael Snoyman Date: Wed, 26 Jul 2017 11:43:24 +0300 Subject: [PATCH 2/7] Proper grabbing of all build info --- src/Stack/Package.hs | 42 ++++++++++++++++++++---------------------- 1 file changed, 20 insertions(+), 22 deletions(-) diff --git a/src/Stack/Package.hs b/src/Stack/Package.hs index 3a028c0000..4b841e6ba5 100644 --- a/src/Stack/Package.hs +++ b/src/Stack/Package.hs @@ -532,7 +532,7 @@ packageDependencies :: PackageDescription -> Map PackageName VersionRange packageDependencies pkg = M.fromListWith intersectVersionRanges $ map (depName &&& depRange) $ - concatMap targetBuildDepends (allBuildInfo' pkg) ++ + concatMap targetBuildDepends (allBuildInfo pkg) ++ maybe [] setupDepends (setupBuildInfo pkg) -- | Get all build tool dependencies of the package (buildable targets only). @@ -541,28 +541,11 @@ packageToolDependencies = M.fromList . concatMap (fmap (\(Cabal.LegacyExeDependency name range) -> (T.pack name, range)) . buildTools) . - allBuildInfo' + allBuildInfo -- | Get all dependencies of the package (buildable targets only). packageDescTools :: PackageDescription -> [Cabal.ExeDependency] -packageDescTools = concatMap buildToolDepends . allBuildInfo' - --- | This is a copy-paste from Cabal's @allBuildInfo@ function, but with the --- @buildable@ test removed. The implementation is broken. --- See: https://github.com/haskell/cabal/issues/1725 -allBuildInfo' :: PackageDescription -> [BuildInfo] -allBuildInfo' pkg_descr = [ bi | Just lib <- [library pkg_descr] - , let bi = libBuildInfo lib - , True || buildable bi ] - ++ [ bi | exe <- executables pkg_descr - , let bi = buildInfo exe - , True || buildable bi ] - ++ [ bi | tst <- testSuites pkg_descr - , let bi = testBuildInfo tst - , True || buildable bi ] - ++ [ bi | tst <- benchmarks pkg_descr - , let bi = benchmarkBuildInfo tst - , True || buildable bi ] +packageDescTools = concatMap buildToolDepends . allBuildInfo -- | Get all files referenced by the package. packageDescModulesAndFiles @@ -809,12 +792,27 @@ resolvePackageDescription packageConfig (GenericPackageDescription desc defaultF (packageConfigPlatform packageConfig) flags + -- Due to https://github.com/haskell/cabal/issues/1725, + -- versions of Cabal before 2.0 would always require that the + -- dependencies for all libraries and executables be present, + -- even if they were not buildable. To ensure that Stack is + -- compatible with those older Cabal libraries (which may be + -- in use depending on the snapshot chosen), we set buildable + -- to True for libraries and executables. updateLibDeps lib deps = lib {libBuildInfo = - (libBuildInfo lib) {targetBuildDepends = deps}} + (libBuildInfo lib) + { targetBuildDepends = deps + , buildable = True + } + } updateExeDeps exe deps = exe {buildInfo = - (buildInfo exe) {targetBuildDepends = deps}} + (buildInfo exe) + { targetBuildDepends = deps + , buildable = True + } + } updateTestDeps test deps = test {testBuildInfo = (testBuildInfo test) From 0ef1401318825b19a6479b3f33b2388b574a7d49 Mon Sep 17 00:00:00 2001 From: Michael Snoyman Date: Wed, 26 Jul 2017 15:51:54 +0300 Subject: [PATCH 3/7] Proper build tool loading from Cabal files --- src/Stack/Build/ConstructPlan.hs | 52 +++++++++++++------------------- src/Stack/BuildPlan.hs | 10 +++--- src/Stack/Package.hs | 23 +++++++++----- src/Stack/Types/Package.hs | 5 ++- 4 files changed, 44 insertions(+), 46 deletions(-) diff --git a/src/Stack/Build/ConstructPlan.hs b/src/Stack/Build/ConstructPlan.hs index 9be0fe814e..fbf03c5518 100644 --- a/src/Stack/Build/ConstructPlan.hs +++ b/src/Stack/Build/ConstructPlan.hs @@ -30,7 +30,6 @@ import qualified Data.Set as Set import qualified Data.Text as T import Data.Text.Encoding (decodeUtf8With) import Data.Text.Encoding.Error (lenientDecode) -import qualified Distribution.Package as Cabal import qualified Distribution.Text as Cabal import qualified Distribution.Version as Cabal import Generics.Deriving.Monoid (memptydefault, mappenddefault) @@ -129,7 +128,7 @@ data Ctx = Ctx , baseConfigOpts :: !BaseConfigOpts , loadPackage :: !(PackageLocationIndex FilePath -> Map FlagName Bool -> [Text] -> IO Package) , combinedMap :: !CombinedMap - , toolToPackages :: !(Cabal.Dependency -> Map PackageName VersionRange) + , toolToPackages :: !(ExeName -> Map PackageName VersionRange) , ctxEnvConfig :: !EnvConfig , callStack :: ![PackageName] , extraToBuild :: !(Set PackageName) @@ -224,9 +223,9 @@ constructPlan ls0 baseConfigOpts0 locals extraToBuild0 localDumpPkgs loadPackage , baseConfigOpts = baseConfigOpts0 , loadPackage = loadPackage0 , combinedMap = combineMap sourceMap installedMap - , toolToPackages = \(Cabal.Dependency name _) -> + , toolToPackages = \name -> maybe Map.empty (Map.fromSet (const Cabal.anyVersion)) $ - Map.lookup (T.pack . packageNameString . fromCabalPackageName $ name) (toolMap lp) + Map.lookup name toolMap , ctxEnvConfig = econfig , callStack = [] , extraToBuild = extraToBuild0 @@ -234,8 +233,8 @@ constructPlan ls0 baseConfigOpts0 locals extraToBuild0 localDumpPkgs loadPackage , wanted = wantedLocalPackages locals <> extraToBuild0 , localNames = Set.fromList $ map (packageName . lpPackage) locals } - - toolMap = getToolMap ls0 + where + toolMap = getToolMap ls0 lp -- | State to be maintained during the calculation of local packages -- to unregister. @@ -795,58 +794,49 @@ packageDepsWithTools p = do ctx <- ask -- TODO: it would be cool to defer these warnings until there's an -- actual issue building the package. - let toEither (Cabal.Dependency (Cabal.unPackageName -> name) _) mp = + let toEither name mp = case Map.toList mp of - [] -> Left (NoToolFound name (packageName p)) + [] -> Left (ToolWarning name (packageName p) Nothing) [_] -> Right mp - xs -> Left (AmbiguousToolsFound name (packageName p) (map fst xs)) + ((x, _):(y, _):zs) -> + Left (ToolWarning name (packageName p) (Just (x, y, map fst zs))) (warnings0, toolDeps) = partitionEithers $ - map (\dep -> toEither dep (toolToPackages ctx dep)) (packageTools p) + map (\dep -> toEither dep (toolToPackages ctx dep)) (Map.keys (packageTools p)) -- Check whether the tool is on the PATH before warning about it. - warnings <- fmap catMaybes $ forM warnings0 $ \warning -> do - let toolName = case warning of - NoToolFound tool _ -> tool - AmbiguousToolsFound tool _ _ -> tool + warnings <- fmap catMaybes $ forM warnings0 $ \warning@(ToolWarning (ExeName toolName) _ _) -> do config <- view configL menv <- liftIO $ configEnvOverride config minimalEnvSettings { esIncludeLocals = True } - mfound <- findExecutable menv toolName + mfound <- findExecutable menv $ T.unpack toolName case mfound of Nothing -> return (Just warning) Just _ -> return Nothing tell mempty { wWarnings = (map toolWarningText warnings ++) } - when (any isNoToolFound warnings) $ do - let msg = T.unlines - [ "Missing build-tools may be caused by dependencies of the build-tool being overridden by extra-deps." - , "This should be fixed soon - see this issue https://github.com/commercialhaskell/stack/issues/595" - ] - tell mempty { wWarnings = (msg:) } return $ Map.unionsWith intersectVersionRanges $ packageDeps p : toolDeps -data ToolWarning - = NoToolFound String PackageName - | AmbiguousToolsFound String PackageName [PackageName] - -isNoToolFound :: ToolWarning -> Bool -isNoToolFound NoToolFound{} = True -isNoToolFound _ = False +-- | Warn about tools in the snapshot definition. States the tool name +-- expected, the package name using it, and found packages. If the +-- last value is Nothing, it means the tool was not found +-- anywhere. For a Just value, it was found in at least two packages. +data ToolWarning = ToolWarning ExeName PackageName (Maybe (PackageName, PackageName, [PackageName])) + deriving Show toolWarningText :: ToolWarning -> Text -toolWarningText (NoToolFound toolName pkgName) = +toolWarningText (ToolWarning (ExeName toolName) pkgName Nothing) = "No packages found in snapshot which provide a " <> T.pack (show toolName) <> " executable, which is a build-tool dependency of " <> T.pack (show (packageNameString pkgName)) -toolWarningText (AmbiguousToolsFound toolName pkgName options) = +toolWarningText (ToolWarning (ExeName toolName) pkgName (Just (option1, option2, options))) = "Multiple packages found in snapshot which provide a " <> T.pack (show toolName) <> " exeuctable, which is a build-tool dependency of " <> T.pack (show (packageNameString pkgName)) <> ", so none will be installed.\n" <> "Here's the list of packages which provide it: " <> - T.intercalate ", " (map packageNameText options) <> + T.intercalate ", " (map packageNameText (option1:option2:options)) <> "\nSince there's no good way to choose, you may need to install it manually." -- | Strip out anything from the @Plan@ intended for the local database diff --git a/src/Stack/BuildPlan.hs b/src/Stack/BuildPlan.hs index 7e44b5aab3..c3814a9f34 100644 --- a/src/Stack/BuildPlan.hs +++ b/src/Stack/BuildPlan.hs @@ -152,7 +152,7 @@ instance Show BuildPlanException where -- both snapshot and local packages (deps and project packages). getToolMap :: LoadedSnapshot -> LocalPackages - -> Map Text (Set PackageName) + -> Map ExeName (Set PackageName) getToolMap ls locals = {- We no longer do this, following discussion at: @@ -171,13 +171,13 @@ getToolMap ls locals = ] where goSnap (pname, lpi) = - map (flip Map.singleton (Set.singleton pname) . unExeName) + map (flip Map.singleton (Set.singleton pname)) $ Set.toList $ lpiProvidedExes lpi goLocalProj (pname, lpv) = map (flip Map.singleton (Set.singleton pname)) - [t | CExe t <- Set.toList (lpvComponents lpv)] + [ExeName t | CExe t <- Set.toList (lpvComponents lpv)] goLocalDep (pname, (gpd, _loc)) = map (flip Map.singleton (Set.singleton pname)) @@ -186,8 +186,8 @@ getToolMap ls locals = -- TODO consider doing buildable checking. Not a big deal though: -- worse case scenario is we build an extra package that wasn't -- strictly needed. - gpdExes :: GenericPackageDescription -> [Text] - gpdExes = map (T.pack . C.unUnqualComponentName . fst) . condExecutables + gpdExes :: GenericPackageDescription -> [ExeName] + gpdExes = map (ExeName . T.pack . C.unUnqualComponentName . fst) . condExecutables gpdPackages :: [GenericPackageDescription] -> Map PackageName Version gpdPackages gpds = Map.fromList $ diff --git a/src/Stack/Package.hs b/src/Stack/Package.hs index 4b841e6ba5..2e88ced7f5 100644 --- a/src/Stack/Package.hs +++ b/src/Stack/Package.hs @@ -65,7 +65,6 @@ import Distribution.Simple.Utils import Distribution.System (OS (..), Arch, Platform (..)) import qualified Distribution.Text as D import qualified Distribution.Types.CondTree as Cabal -import qualified Distribution.Types.Dependency as Cabal import qualified Distribution.Types.ExeDependency as Cabal import qualified Distribution.Types.LegacyExeDependency as Cabal import qualified Distribution.Types.UnqualComponentName as Cabal @@ -83,7 +82,7 @@ import Stack.Constants.Config import Stack.Prelude import Stack.PrettyPrint import Stack.Types.Build -import Stack.Types.BuildPlan (PackageLocationIndex (..), PackageLocation (..)) +import Stack.Types.BuildPlan (PackageLocationIndex (..), PackageLocation (..), ExeName (..)) import Stack.Types.Compiler import Stack.Types.Config import Stack.Types.FlagName @@ -222,9 +221,7 @@ packageFromPackageDescription packageConfig pkgFlags pkg = , packageLicense = license pkg , packageDeps = deps , packageFiles = pkgFiles - , packageTools = map - (\(Cabal.ExeDependency name' _ range) -> Cabal.Dependency name' range) - (packageDescTools pkg) + , packageTools = packageDescTools pkg , packageGhcOptions = packageConfigGhcOptions packageConfig , packageFlags = packageConfigFlags packageConfig , packageDefaultFlags = M.fromList @@ -544,8 +541,20 @@ packageToolDependencies = allBuildInfo -- | Get all dependencies of the package (buildable targets only). -packageDescTools :: PackageDescription -> [Cabal.ExeDependency] -packageDescTools = concatMap buildToolDepends . allBuildInfo +-- +-- This uses both the new 'buildToolDepends' and old 'buildTools' +-- information. +packageDescTools :: PackageDescription -> Map ExeName VersionRange +packageDescTools = + M.fromList . concatMap tools . allBuildInfo + where + tools bi = map go1 (buildTools bi) ++ map go2 (buildToolDepends bi) + + go1 :: Cabal.LegacyExeDependency -> (ExeName, VersionRange) + go1 (Cabal.LegacyExeDependency name range) = (ExeName $ T.pack name, range) + + go2 :: Cabal.ExeDependency -> (ExeName, VersionRange) + go2 (Cabal.ExeDependency _pkg name range) = (ExeName $ T.pack $ Cabal.unUnqualComponentName name, range) -- | Get all files referenced by the package. packageDescModulesAndFiles diff --git a/src/Stack/Types/Package.hs b/src/Stack/Types/Package.hs index ba52dd250f..50ec3c6adc 100644 --- a/src/Stack/Types/Package.hs +++ b/src/Stack/Types/Package.hs @@ -21,11 +21,10 @@ import Data.Text.Encoding (encodeUtf8, decodeUtf8) import Distribution.InstalledPackageInfo (PError) import Distribution.License (License) import Distribution.ModuleName (ModuleName) -import Distribution.Package hiding (Package,PackageName,packageName,packageVersion,PackageIdentifier) import Distribution.PackageDescription (TestSuiteInterface, BuildType) import Distribution.System (Platform (..)) import Path as FL -import Stack.Types.BuildPlan (PackageLocation, PackageLocationIndex (..)) +import Stack.Types.BuildPlan (PackageLocation, PackageLocationIndex (..), ExeName) import Stack.Types.Compiler import Stack.Types.Config import Stack.Types.FlagName @@ -77,7 +76,7 @@ data Package = ,packageLicense :: !License -- ^ The license the package was released under. ,packageFiles :: !GetPackageFiles -- ^ Get all files of the package. ,packageDeps :: !(Map PackageName VersionRange) -- ^ Packages that the package depends on. - ,packageTools :: ![Dependency] -- ^ A build tool name. + ,packageTools :: !(Map ExeName VersionRange) -- ^ A build tool name. ,packageAllDeps :: !(Set PackageName) -- ^ Original dependencies (not sieved). ,packageGhcOptions :: ![Text] -- ^ Ghc options used on package. ,packageFlags :: !(Map FlagName Bool) -- ^ Flags used on package. From 8f1917bfe27948bd8296d9664685c7412f3ef1cb Mon Sep 17 00:00:00 2001 From: Michael Snoyman Date: Thu, 17 Aug 2017 10:04:08 +0300 Subject: [PATCH 4/7] Remove redundant (and now incorrect) packageToolDependencies function --- src/Stack/Package.hs | 10 +--------- src/Stack/Snapshot.hs | 5 ++--- 2 files changed, 3 insertions(+), 12 deletions(-) diff --git a/src/Stack/Package.hs b/src/Stack/Package.hs index 2e88ced7f5..03068a4757 100644 --- a/src/Stack/Package.hs +++ b/src/Stack/Package.hs @@ -33,7 +33,7 @@ module Stack.Package ,buildLogPath ,PackageException (..) ,resolvePackageDescription - ,packageToolDependencies + ,packageDescTools ,packageDependencies ,autogenDir ,checkCabalFileName @@ -532,14 +532,6 @@ packageDependencies pkg = concatMap targetBuildDepends (allBuildInfo pkg) ++ maybe [] setupDepends (setupBuildInfo pkg) --- | Get all build tool dependencies of the package (buildable targets only). -packageToolDependencies :: PackageDescription -> Map Text VersionRange -packageToolDependencies = - M.fromList . - concatMap (fmap (\(Cabal.LegacyExeDependency name range) -> (T.pack name, range)) . - buildTools) . - allBuildInfo - -- | Get all dependencies of the package (buildable targets only). -- -- This uses both the new 'buildToolDepends' and old 'buildTools' diff --git a/src/Stack/Snapshot.hs b/src/Stack/Snapshot.hs index b599659893..a66e07db93 100644 --- a/src/Stack/Snapshot.hs +++ b/src/Stack/Snapshot.hs @@ -792,9 +792,8 @@ calculate gpd platform compilerVersion loc flags hide options = Set.fromList $ map (ExeName . T.pack . C.unUnqualComponentName . C.exeName) $ C.executables pd - , lpiNeededExes = Map.mapKeys ExeName - $ Map.map fromVersionRange - $ packageToolDependencies pd + , lpiNeededExes = Map.map fromVersionRange + $ packageDescTools pd , lpiExposedModules = maybe Set.empty (Set.fromList . map fromCabalModuleName . C.exposedModules) From f9a41d3885098f1cbfa76457f4938c7cdf2543da Mon Sep 17 00:00:00 2001 From: Michael Snoyman Date: Thu, 17 Aug 2017 10:22:44 +0300 Subject: [PATCH 5/7] Move getDefaultPackageConfig to where it is used --- src/Stack/Build/Source.hs | 15 --------------- src/Stack/SDist.hs | 16 +++++++++++++++- 2 files changed, 15 insertions(+), 16 deletions(-) diff --git a/src/Stack/Build/Source.hs b/src/Stack/Build/Source.hs index 5be820cc3a..8c59d67aaa 100644 --- a/src/Stack/Build/Source.hs +++ b/src/Stack/Build/Source.hs @@ -13,7 +13,6 @@ module Stack.Build.Source , getLocalFlags , getGhcOptions , addUnlistedToBuildCache - , getDefaultPackageConfig ) where import Stack.Prelude @@ -471,20 +470,6 @@ checkComponentsBuildable lps = , c <- Set.toList (lpUnbuildable lp) ] -getDefaultPackageConfig :: (MonadIO m, MonadReader env m, HasEnvConfig env) - => m PackageConfig -getDefaultPackageConfig = do - platform <- view platformL - compilerVersion <- view actualCompilerVersionL - return PackageConfig - { packageConfigEnableTests = False - , packageConfigEnableBenchmarks = False - , packageConfigFlags = M.empty - , packageConfigGhcOptions = [] - , packageConfigCompilerVersion = compilerVersion - , packageConfigPlatform = platform - } - -- | Get 'PackageConfig' for package given its name. getPackageConfig :: (MonadIO m, MonadReader env m, HasEnvConfig env) => BuildOptsCLI diff --git a/src/Stack/SDist.hs b/src/Stack/SDist.hs index f36c024d1b..6ec057f4a5 100644 --- a/src/Stack/SDist.hs +++ b/src/Stack/SDist.hs @@ -51,7 +51,7 @@ import Path.IO hiding (getModificationTime, getPermissions, withSystem import Stack.Build (mkBaseConfigOpts, build) import Stack.Build.Execute import Stack.Build.Installed -import Stack.Build.Source (loadSourceMap, getDefaultPackageConfig) +import Stack.Build.Source (loadSourceMap) import Stack.Build.Target hiding (PackageType (..)) import Stack.PackageLocation (resolveMultiPackageLocation) import Stack.Constants @@ -443,3 +443,17 @@ getModTime :: FilePath -> IO Tar.EpochTime getModTime path = do t <- getModificationTime path return . floor . utcTimeToPOSIXSeconds $ t + +getDefaultPackageConfig :: (MonadIO m, MonadReader env m, HasEnvConfig env) + => m PackageConfig +getDefaultPackageConfig = do + platform <- view platformL + compilerVersion <- view actualCompilerVersionL + return PackageConfig + { packageConfigEnableTests = False + , packageConfigEnableBenchmarks = False + , packageConfigFlags = mempty + , packageConfigGhcOptions = [] + , packageConfigCompilerVersion = compilerVersion + , packageConfigPlatform = platform + } From 66a9b1e271be368bdc06d2ee6a6bd724d799ad70 Mon Sep 17 00:00:00 2001 From: Michael Snoyman Date: Thu, 17 Aug 2017 11:17:32 +0300 Subject: [PATCH 6/7] Make tests and benchmarks run again See the comment added in this commit, further investigation is likely needed. --- src/Stack/Package.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/src/Stack/Package.hs b/src/Stack/Package.hs index 03068a4757..0faf4efa29 100644 --- a/src/Stack/Package.hs +++ b/src/Stack/Package.hs @@ -229,11 +229,17 @@ packageFromPackageDescription packageConfig pkgFlags pkg = , packageAllDeps = S.fromList (M.keys deps) , packageHasLibrary = maybe False (buildable . libBuildInfo) (library pkg) , packageTests = M.fromList - [(T.pack (Cabal.unUnqualComponentName $ testName t), testInterface t) | t <- testSuites pkg - , buildable (testBuildInfo t)] + [(T.pack (Cabal.unUnqualComponentName $ testName t), testInterface t) | t <- testSuites pkg] + -- FIXME: Previously, we only included buildable components + -- here. Since Cabal 2.0, this ended up disabling test running + -- in all cases. Need to investigate if that's a change in + -- Cabal behavior or how we're piping data through the system + -- in response to Cabal data type changes. A cleanup of the + -- PackageConfig datatype (which will probably happen for + -- componentized builds) will likely make all of this clearer. , packageBenchmarks = S.fromList - [T.pack (Cabal.unUnqualComponentName $ benchmarkName biBuildInfo) | biBuildInfo <- benchmarks pkg - , buildable (benchmarkBuildInfo biBuildInfo)] + [T.pack (Cabal.unUnqualComponentName $ benchmarkName biBuildInfo) | biBuildInfo <- benchmarks pkg] + -- Same comment about buildable applies here too. , packageExes = S.fromList [T.pack (Cabal.unUnqualComponentName $ exeName biBuildInfo) | biBuildInfo <- executables pkg From b1f9dcff43f2c0faff94e164a6bdd60e6a408696 Mon Sep 17 00:00:00 2001 From: Michael Snoyman Date: Thu, 17 Aug 2017 16:55:42 +0300 Subject: [PATCH 7/7] Fiddle with the buildable field correctly Looks like I totally outsmarted myself here working on the Cabal 2.0 migration. Please see the newly added comment in this commit. --- src/Stack/Package.hs | 55 +++++++++++++++++++++----------------------- 1 file changed, 26 insertions(+), 29 deletions(-) diff --git a/src/Stack/Package.hs b/src/Stack/Package.hs index 0faf4efa29..606d4ad00e 100644 --- a/src/Stack/Package.hs +++ b/src/Stack/Package.hs @@ -799,41 +799,38 @@ resolvePackageDescription packageConfig (GenericPackageDescription desc defaultF (packageConfigPlatform packageConfig) flags - -- Due to https://github.com/haskell/cabal/issues/1725, - -- versions of Cabal before 2.0 would always require that the - -- dependencies for all libraries and executables be present, - -- even if they were not buildable. To ensure that Stack is - -- compatible with those older Cabal libraries (which may be - -- in use depending on the snapshot chosen), we set buildable - -- to True for libraries and executables. updateLibDeps lib deps = lib {libBuildInfo = - (libBuildInfo lib) - { targetBuildDepends = deps - , buildable = True - } - } + (libBuildInfo lib) {targetBuildDepends = deps}} updateExeDeps exe deps = exe {buildInfo = - (buildInfo exe) - { targetBuildDepends = deps - , buildable = True - } - } + (buildInfo exe) {targetBuildDepends = deps}} + + -- Note that, prior to moving to Cabal 2.0, we would set + -- testEnabled/benchmarkEnabled here. These fields no longer + -- exist, so we modify buildable instead here. The only + -- wrinkle in the Cabal 2.0 story is + -- https://github.com/haskell/cabal/issues/1725, where older + -- versions of Cabal (which may be used for actually building + -- code) don't properly exclude build-depends for + -- non-buildable components. Testing indicates that everything + -- is working fine, and that this comment can be completely + -- ignored. I'm leaving the comment anyway in case something + -- breaks and you, poor reader, are investigating. updateTestDeps test deps = - test {testBuildInfo = - (testBuildInfo test) - { targetBuildDepends = deps - , buildable = packageConfigEnableTests packageConfig - } - } + let bi = testBuildInfo test + bi' = bi + { targetBuildDepends = deps + , buildable = buildable bi && packageConfigEnableTests packageConfig + } + in test { testBuildInfo = bi' } updateBenchmarkDeps benchmark deps = - benchmark {benchmarkBuildInfo = - (benchmarkBuildInfo benchmark) - { targetBuildDepends = deps - , buildable = packageConfigEnableBenchmarks packageConfig - } - } + let bi = benchmarkBuildInfo benchmark + bi' = bi + { targetBuildDepends = deps + , buildable = buildable bi && packageConfigEnableBenchmarks packageConfig + } + in benchmark { benchmarkBuildInfo = bi' } -- | Make a map from a list of flag specifications. --