diff --git a/package.yaml b/package.yaml index 55009842b4..fe77864aec 100644 --- a/package.yaml +++ b/package.yaml @@ -240,14 +240,12 @@ library: - Stack.Types.Config - Stack.Types.Config.Build - Stack.Types.Docker - - Stack.Types.FlagName - Stack.Types.GhcPkgId - Stack.Types.Image - Stack.Types.NamedComponent - Stack.Types.Nix - Stack.Types.Package - Stack.Types.PackageDump - - Stack.Types.PackageIdentifier - Stack.Types.PackageName - Stack.Types.PrettyPrint - Stack.Types.Resolver diff --git a/src/Stack/Build.hs b/src/Stack/Build.hs index 40a8f88acb..9d569729c2 100644 --- a/src/Stack/Build.hs +++ b/src/Stack/Build.hs @@ -36,6 +36,7 @@ import qualified Data.Text.IO as TIO import Data.Text.Read (decimal) import qualified Data.Vector as V import qualified Data.Yaml as Yaml +import Distribution.Version (mkVersion) import Path (parent) import Stack.Build.ConstructPlan import Stack.Build.Execute @@ -48,7 +49,6 @@ import Stack.Types.Build import Stack.Types.Config import Stack.Types.NamedComponent import Stack.Types.Package -import Stack.Types.Version import Stack.Types.Compiler (compilerVersionText #ifdef WINDOWS @@ -152,7 +152,7 @@ checkCabalVersion = do allowNewer <- view $ configL.to configAllowNewer cabalVer <- view cabalVersionL -- https://github.com/haskell/cabal/issues/2023 - when (allowNewer && cabalVer < $(mkVersion "1.22")) $ throwM $ + when (allowNewer && cabalVer < mkVersion [1, 22]) $ throwM $ CabalVersionException $ "Error: --allow-newer requires at least Cabal version 1.22, but version " ++ versionString cabalVer ++ @@ -293,7 +293,7 @@ fixCodePage :: HasEnvConfig env => RIO env a -> RIO env a fixCodePage inner = do mcp <- view $ configL.to configModifyCodePage ghcVersion <- view $ actualCompilerVersionL.to getGhcVersion - if mcp && ghcVersion < $(mkVersion "7.10.3") + if mcp && ghcVersion < mkVersion [7, 10, 3] then fixCodePage' -- GHC >=7.10.3 doesn't need this code page hack. else inner diff --git a/src/Stack/Build/ConstructPlan.hs b/src/Stack/Build/ConstructPlan.hs index 5efddb2d0a..2e878e4a63 100644 --- a/src/Stack/Build/ConstructPlan.hs +++ b/src/Stack/Build/ConstructPlan.hs @@ -32,6 +32,8 @@ import Data.Text.Encoding.Error (lenientDecode) import qualified Distribution.Text as Cabal import qualified Distribution.Version as Cabal import Distribution.Types.BuildType (BuildType (Configure)) +import Distribution.Types.PackageName (mkPackageName) +import Distribution.Version (mkVersion) import Generics.Deriving.Monoid (memptydefault, mappenddefault) import Path (parent) import qualified RIO @@ -50,7 +52,6 @@ import Stack.Types.Config import Stack.Types.GhcPkgId import Stack.Types.NamedComponent import Stack.Types.Package -import Stack.Types.PackageName import Stack.Types.Runner import Stack.Types.Version import System.IO (putStrLn) @@ -225,7 +226,7 @@ constructPlan ls0 baseConfigOpts0 locals extraToBuild0 localDumpPkgs loadPackage throwM $ ConstructPlanFailed "Plan construction failed." where hasBaseInDeps bconfig = - $(mkPackageName "base") `elem` + mkPackageName "base" `elem` [n | (PLImmutable (PLIHackage (PackageIdentifierRevision n _ _) _)) <- bcDependencies bconfig] mkCtx econfig = Ctx @@ -956,7 +957,7 @@ pprintExceptions exceptions stackYaml stackRoot parentMap wanted = addExtraDepsRecommendations | Map.null extras = [] - | (Just _) <- Map.lookup $(mkPackageName "base") extras = + | (Just _) <- Map.lookup (mkPackageName "base") extras = [ " *" <+> align (flow "Build requires unattainable version of base. Since base is a part of GHC, you most likely need to use a different GHC version with the matching base.") , line ] @@ -1097,7 +1098,7 @@ getShortestDepsPath (MonoidMap parentsMap) wanted name = -- search of dependencies. findShortest :: Int -> Map PackageName DepsPath -> [PackageIdentifier] findShortest fuel _ | fuel <= 0 = - [PackageIdentifier $(mkPackageName "stack-ran-out-of-jet-fuel") $(mkVersion "0")] + [PackageIdentifier (mkPackageName "stack-ran-out-of-jet-fuel") (mkVersion [0])] findShortest _ paths | M.null paths = [] findShortest fuel paths = case targets of diff --git a/src/Stack/Build/Execute.hs b/src/Stack/Build/Execute.hs index df1419854d..a6133f4880 100644 --- a/src/Stack/Build/Execute.hs +++ b/src/Stack/Build/Execute.hs @@ -58,6 +58,8 @@ import qualified Distribution.Simple.Build.Macros as C import Distribution.System (OS (Windows), Platform (Platform)) import qualified Distribution.Text as C +import Distribution.Types.PackageName (mkPackageName) +import Distribution.Version (mkVersion) import Path import Path.CheckInstall import Path.Extra (toFilePathNoTrailingSep, rejectMissingFile) @@ -82,7 +84,6 @@ import Stack.Types.Config import Stack.Types.GhcPkgId import Stack.Types.NamedComponent import Stack.Types.Package -import Stack.Types.PackageName import Stack.Types.Runner import Stack.Types.Version import qualified System.Directory as D @@ -838,7 +839,7 @@ ensureConfig newConfigCache pkgDir ExecuteEnv {..} announce cabal cabalfp task = deleteCaches pkgDir announce let programNames = - if eeCabalPkgVer < $(mkVersion "1.22") + if eeCabalPkgVer < mkVersion [1, 22] then ["ghc", "ghc-pkg"] else ["ghc", "ghc-pkg", "ghcjs", "ghcjs-pkg"] exes <- forM programNames $ \name -> do @@ -1024,7 +1025,7 @@ withSingleContext ActionContext {..} ExecuteEnv {..} task@Task {..} mdeps msuffi -- Omit cabal package dependency when building -- Cabal. See -- https://github.com/commercialhaskell/stack/issues/1356 - | packageName package == $(mkPackageName "Cabal") = [] + | packageName package == mkPackageName "Cabal" = [] | otherwise = ["-package=" ++ packageIdentifierString (PackageIdentifier cabalPackageName @@ -1059,7 +1060,7 @@ withSingleContext ActionContext {..} ExecuteEnv {..} task@Task {..} mdeps msuffi -- explicit list of dependencies, and we -- should simply use all of them. (Just customSetupDeps, _) -> do - unless (Map.member $(mkPackageName "Cabal") customSetupDeps) $ + unless (Map.member (mkPackageName "Cabal") customSetupDeps) $ prettyWarnL [ fromString $ packageNameString $ packageName package , "has a setup-depends field, but it does not mention a Cabal dependency. This is likely to cause build errors." @@ -1525,7 +1526,7 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap let quickjump = case actualCompiler of ACGhc ghcVer - | ghcVer >= $(mkVersion "8.4") -> ["--haddock-option=--quickjump"] + | ghcVer >= mkVersion [8, 4] -> ["--haddock-option=--quickjump"] _ -> [] cabal KeepTHLoading $ concat @@ -1928,7 +1929,7 @@ mungeBuildOutput excludeTHLoading makeAbsolute pkgDir compilerVer = void $ filterLinkerWarnings -- Check for ghc 7.8 since it's the only one prone to producing -- linker warnings on Windows x64 - | getGhcVersion compilerVer >= $(mkVersion "7.8") = doNothing + | getGhcVersion compilerVer >= mkVersion [7, 8] = doNothing | otherwise = CL.filter (not . isLinkerWarning) isLinkerWarning :: Text -> Bool @@ -2101,7 +2102,7 @@ addGlobalPackages deps globals0 = ---------------------------------- -- Is the given package identifier for any version of Cabal - isCabal (PackageIdentifier name _) = name == $(mkPackageName "Cabal") + isCabal (PackageIdentifier name _) = name == mkPackageName "Cabal" -- Is the given package name provided by the package dependencies? isDep dp = pkgName (dpPackageIdent dp) `Set.member` depNames diff --git a/src/Stack/Config.hs b/src/Stack/Config.hs index 2305b409ac..8d8bc09521 100644 --- a/src/Stack/Config.hs +++ b/src/Stack/Config.hs @@ -86,7 +86,6 @@ import Stack.Snapshot import Stack.Types.Config import Stack.Types.Docker import Stack.Types.Nix -import Stack.Types.PackageName (PackageName) import Stack.Types.Resolver import Stack.Types.Runner import Stack.Types.Urls diff --git a/src/Stack/Constants.hs b/src/Stack/Constants.hs index ad821840f9..4a4fc6a026 100644 --- a/src/Stack/Constants.hs +++ b/src/Stack/Constants.hs @@ -40,10 +40,10 @@ module Stack.Constants import Data.Char (toUpper) import qualified Data.Set as Set +import Distribution.Package (mkPackageName) import Path as FL import Stack.Prelude import Stack.Types.Compiler -import Stack.Types.PackageName -- | Extensions used for Haskell modules. Excludes preprocessor ones. haskellFileExts :: [Text] @@ -164,7 +164,7 @@ ghcjsBootPackages = -- | Just to avoid repetition and magic strings. cabalPackageName :: PackageName cabalPackageName = - $(mkPackageName "Cabal") + mkPackageName "Cabal" -- | Deprecated implicit global project directory used when outside of a project. implicitGlobalProjectDirDeprecated :: Path Abs Dir -- ^ Stack root. diff --git a/src/Stack/Coverage.hs b/src/Stack/Coverage.hs index 76c0ab0a6d..7c2cb5167f 100644 --- a/src/Stack/Coverage.hs +++ b/src/Stack/Coverage.hs @@ -29,6 +29,7 @@ import qualified Data.Set as Set import qualified Data.Text as T import qualified Data.Text.IO as T import qualified Data.Text.Lazy as LT +import Distribution.Version (mkVersion) import Path import Path.Extra (toFilePathNoTrailingSep) import Path.IO @@ -42,7 +43,6 @@ import Stack.Types.Config import Stack.Types.NamedComponent import Stack.Types.Package import Stack.Types.Runner -import Stack.Types.Version import System.FilePath (isPathSeparator) import qualified RIO import RIO.Process @@ -110,7 +110,7 @@ generateHpcReport pkgDir package tests = do internalLibs = packageInternalLibraries package eincludeName <- -- Pre-7.8 uses plain PKG-version in tix files. - if ghcVersion < $(mkVersion "7.10") then return $ Right $ Just [pkgId] + if ghcVersion < mkVersion [7, 10] then return $ Right $ Just [pkgId] -- We don't expect to find a package key if there is no library. else if not hasLibrary && Set.null internalLibs then return $ Right Nothing -- Look in the inplace DB for the package key. @@ -118,7 +118,7 @@ generateHpcReport pkgDir package tests = do else do -- GHC 8.0 uses package id instead of package key. -- See https://github.com/commercialhaskell/stack/issues/2424 - let hpcNameField = if ghcVersion >= $(mkVersion "8.0") then "id" else "key" + let hpcNameField = if ghcVersion >= mkVersion [8, 0] then "id" else "key" eincludeName <- findPackageFieldForBuiltPackage pkgDir (packageIdentifier package) internalLibs hpcNameField case eincludeName of Left err -> do @@ -440,7 +440,7 @@ findPackageFieldForBuiltPackage pkgDir pkgId internalLibs field = do Just result -> return $ Right result Nothing -> notFoundErr cabalVer <- view cabalVersionL - if cabalVer < $(mkVersion "1.24") + if cabalVer < mkVersion [1, 24] then do -- here we don't need to handle internal libs path <- liftM (inplaceDir ) $ parseRelFile (pkgIdStr ++ "-inplace.conf") diff --git a/src/Stack/Docker.hs b/src/Stack/Docker.hs index 40e67791b7..db80f83bbe 100644 --- a/src/Stack/Docker.hs +++ b/src/Stack/Docker.hs @@ -41,6 +41,7 @@ import qualified Data.Text as T import qualified Data.Text.Encoding as T import Data.Time (UTCTime,LocalTime(..),diffDays,utcToLocalTime,getZonedTime,ZonedTime(..)) import Data.Version (showVersion) +import Distribution.Version (mkVersion) import GHC.Exts (sortWith) import Path import Path.Extra (toFilePathNoTrailingSep) @@ -706,7 +707,7 @@ checkDockerVersion docker = return () _ -> throwIO InvalidVersionOutputException _ -> throwIO InvalidVersionOutputException - where minimumDockerVersion = $(mkVersion "1.6.0") + where minimumDockerVersion = mkVersion [1, 6, 0] prohibitedDockerVersions = [] stripVersion v = takeWhile (/= '-') (dropWhileEnd (not . isDigit) v) diff --git a/src/Stack/Dot.hs b/src/Stack/Dot.hs index 9d9936697c..29f1aed855 100644 --- a/src/Stack/Dot.hs +++ b/src/Stack/Dot.hs @@ -24,6 +24,7 @@ import qualified Data.Traversable as T import Distribution.Text (display) import qualified Distribution.SPDX.License as SPDX import Distribution.License (License(BSD3), licenseFromSPDX) +import Distribution.Types.PackageName (mkPackageName) import Stack.Build (loadPackage) import Stack.Build.Installed (getInstalled, GetInstalledOpts(..)) import Stack.Build.Source @@ -38,7 +39,6 @@ import Stack.Types.Build import Stack.Types.Config import Stack.Types.GhcPkgId import Stack.Types.Package -import Stack.Types.PackageName -- | Options record for @stack dot@ data DotOpts = DotOpts @@ -123,7 +123,7 @@ createDependencyGraph dotOpts = do loadPackageDeps name version loc flags ghcOptions -- Skip packages that can't be loaded - see -- https://github.com/commercialhaskell/stack/issues/2967 - | name `elem` [$(mkPackageName "rts"), $(mkPackageName "ghc")] = + | name `elem` [mkPackageName "rts", mkPackageName "ghc"] = return (Set.empty, DotPayload (Just version) (Just $ Right BSD3)) | otherwise = fmap (packageAllDeps &&& makePayload) (loadPackage loc flags ghcOptions) resolveDependencies (dotDependencyDepth dotOpts) graph depLoader diff --git a/src/Stack/GhcPkg.hs b/src/Stack/GhcPkg.hs index 99f3129d20..67c93c891d 100644 --- a/src/Stack/GhcPkg.hs +++ b/src/Stack/GhcPkg.hs @@ -27,6 +27,7 @@ import qualified Data.ByteString.Lazy as BL import Data.List import qualified Data.Text as T import qualified Data.Text.Encoding as T +import Distribution.Version (mkVersion) import Path (parent, mkRelFile, ()) import Path.Extra (toFilePathNoTrailingSep) import Path.IO @@ -34,7 +35,6 @@ import Stack.Constants import Stack.Types.Build import Stack.Types.GhcPkgId import Stack.Types.Compiler -import Stack.Types.Version import System.FilePath (searchPathSeparator) import RIO.Process @@ -167,7 +167,7 @@ unregisterGhcPkgId wc cv pkgDb gid ident = do -- TODO ideally we'd tell ghc-pkg a GhcPkgId instead args = "unregister" : "--user" : "--force" : (case cv of - ACGhc v | v < $(mkVersion "7.9") -> + ACGhc v | v < mkVersion [7, 9] -> [packageIdentifierString ident] _ -> ["--ipid", ghcPkgIdString gid]) diff --git a/src/Stack/Hoogle.hs b/src/Stack/Hoogle.hs index dd83b3b694..3dff10d5c5 100644 --- a/src/Stack/Hoogle.hs +++ b/src/Stack/Hoogle.hs @@ -12,13 +12,13 @@ import Stack.Prelude import qualified Data.ByteString.Lazy.Char8 as BL8 import Data.Char (isSpace) import qualified Data.Text as T +import Distribution.Types.PackageName (mkPackageName) +import Distribution.Version (mkVersion) import Path (parseAbsFile) import Path.IO hiding (findExecutable) import qualified Stack.Build import Stack.Runners import Stack.Types.Config -import Stack.Types.PackageName -import Stack.Types.Version import System.Exit import RIO.Process @@ -74,8 +74,8 @@ hoogleCmd (args,setup,rebuild,startServer) go = withBuildConfig go $ do defaultBuildOptsCLI)) (\(_ :: ExitCode) -> return ())) - hooglePackageName = $(mkPackageName "hoogle") - hoogleMinVersion = $(mkVersion "5.0") + hooglePackageName = mkPackageName "hoogle" + hoogleMinVersion = mkVersion [5, 0] hoogleMinIdent = PackageIdentifier hooglePackageName hoogleMinVersion installHoogle :: RIO EnvConfig () diff --git a/src/Stack/Package.hs b/src/Stack/Package.hs index 1eb48b2cf9..d2573cebba 100644 --- a/src/Stack/Package.hs +++ b/src/Stack/Package.hs @@ -58,6 +58,7 @@ import qualified Distribution.Types.LegacyExeDependency as Cabal import Distribution.Types.MungedPackageName import qualified Distribution.Types.UnqualComponentName as Cabal import qualified Distribution.Verbosity as D +import Distribution.Version (mkVersion) import Lens.Micro (lens) import qualified Hpack.Config as Hpack import Path as FL @@ -498,7 +499,7 @@ makeObjectFilePathFromC cabalDir namedComponent distDir cFilePath = do -- | Make the global autogen dir if Cabal version is new enough. packageAutogenDir :: Version -> Path Abs Dir -> Maybe (Path Abs Dir) packageAutogenDir cabalVer distDir - | cabalVer < $(mkVersion "2.0") = Nothing + | cabalVer < mkVersion [2, 0] = Nothing | otherwise = Just $ buildDir distDir $(mkRelDir "global-autogen") -- | Make the autogen dir. @@ -509,7 +510,7 @@ componentAutogenDir cabalVer component distDir = -- | See 'Distribution.Simple.LocalBuildInfo.componentBuildDir' componentBuildDir :: Version -> NamedComponent -> Path Abs Dir -> Path Abs Dir componentBuildDir cabalVer component distDir - | cabalVer < $(mkVersion "2.0") = buildDir distDir + | cabalVer < mkVersion [2, 0] = buildDir distDir | otherwise = case component of CLib -> buildDir distDir @@ -562,7 +563,7 @@ packageDependencies pkgConfig pkg' = maybe [] setupDepends (setupBuildInfo pkg) where pkg - | getGhcVersion (packageConfigCompilerVersion pkgConfig) >= $(mkVersion "8.0") = pkg' + | getGhcVersion (packageConfigCompilerVersion pkgConfig) >= mkVersion [8, 0] = pkg' -- Set all components to buildable. Only need to worry about -- library, exe, test, and bench, since others didn't exist in -- older Cabal versions diff --git a/src/Stack/SDist.hs b/src/Stack/SDist.hs index bc7c24885f..440de2fd53 100644 --- a/src/Stack/SDist.hs +++ b/src/Stack/SDist.hs @@ -43,7 +43,6 @@ import qualified Distribution.PackageDescription.Check as Check import qualified Distribution.PackageDescription.Parsec as Cabal import Distribution.PackageDescription.PrettyPrint (showGenericPackageDescription) import qualified Distribution.Types.UnqualComponentName as Cabal -import qualified Distribution.Text as Cabal import Distribution.Version (simplifyVersionRange, orLaterVersion, earlierVersion, hasUpperBound, hasLowerBound) import Lens.Micro (set) import Path @@ -59,7 +58,6 @@ import Stack.Package import Stack.Types.Build import Stack.Types.Config import Stack.Types.Package -import Stack.Types.PackageIdentifier import Stack.Types.Runner import Stack.Types.Version import System.Directory (getModificationTime, getPermissions) @@ -195,7 +193,7 @@ getCabalLbs pvpBounds mrev cabalfp = do $ Cabal.packageDescription gpd' } } - ident <- parsePackageIdentifierThrowing $ Cabal.display $ Cabal.package $ Cabal.packageDescription gpd'' + ident = Cabal.package $ Cabal.packageDescription gpd'' -- Sanity rendering and reparsing the input, to ensure there are no -- cabal bugs, since there have been bugs here before, and currently -- are at the time of writing: diff --git a/src/Stack/Script.hs b/src/Stack/Script.hs index b3857d3361..1d12c66373 100644 --- a/src/Stack/Script.hs +++ b/src/Stack/Script.hs @@ -13,6 +13,7 @@ import qualified Data.Conduit.List as CL import Data.List.Split (splitWhen) import qualified Data.Map.Strict as Map import qualified Data.Set as Set +import Distribution.Types.PackageName (mkPackageName) import Path import Path.IO import qualified Stack.Build @@ -163,48 +164,48 @@ getPackagesFromModuleInfo mi scriptFP = do -- packages that should never be auto-parsed in. blacklist :: Set PackageName blacklist = Set.fromList - [ $(mkPackageName "async-dejafu") - , $(mkPackageName "monads-tf") - , $(mkPackageName "crypto-api") - , $(mkPackageName "fay-base") - , $(mkPackageName "hashmap") - , $(mkPackageName "hxt-unicode") - , $(mkPackageName "hledger-web") - , $(mkPackageName "plot-gtk3") - , $(mkPackageName "gtk3") - , $(mkPackageName "regex-pcre-builtin") - , $(mkPackageName "regex-compat-tdfa") - , $(mkPackageName "log") - , $(mkPackageName "zip") - , $(mkPackageName "monad-extras") - , $(mkPackageName "control-monad-free") - , $(mkPackageName "prompt") - , $(mkPackageName "kawhi") - , $(mkPackageName "language-c") - , $(mkPackageName "gl") - , $(mkPackageName "svg-tree") - , $(mkPackageName "Glob") - , $(mkPackageName "nanospec") - , $(mkPackageName "HTF") - , $(mkPackageName "courier") - , $(mkPackageName "newtype-generics") - , $(mkPackageName "objective") - , $(mkPackageName "binary-ieee754") - , $(mkPackageName "rerebase") - , $(mkPackageName "cipher-aes") - , $(mkPackageName "cipher-blowfish") - , $(mkPackageName "cipher-camellia") - , $(mkPackageName "cipher-des") - , $(mkPackageName "cipher-rc4") - , $(mkPackageName "crypto-cipher-types") - , $(mkPackageName "crypto-numbers") - , $(mkPackageName "crypto-pubkey") - , $(mkPackageName "crypto-random") - , $(mkPackageName "cryptohash") - , $(mkPackageName "cryptohash-conduit") - , $(mkPackageName "cryptohash-md5") - , $(mkPackageName "cryptohash-sha1") - , $(mkPackageName "cryptohash-sha256") + [ mkPackageName "async-dejafu" + , mkPackageName "monads-tf" + , mkPackageName "crypto-api" + , mkPackageName "fay-base" + , mkPackageName "hashmap" + , mkPackageName "hxt-unicode" + , mkPackageName "hledger-web" + , mkPackageName "plot-gtk3" + , mkPackageName "gtk3" + , mkPackageName "regex-pcre-builtin" + , mkPackageName "regex-compat-tdfa" + , mkPackageName "log" + , mkPackageName "zip" + , mkPackageName "monad-extras" + , mkPackageName "control-monad-free" + , mkPackageName "prompt" + , mkPackageName "kawhi" + , mkPackageName "language-c" + , mkPackageName "gl" + , mkPackageName "svg-tree" + , mkPackageName "Glob" + , mkPackageName "nanospec" + , mkPackageName "HTF" + , mkPackageName "courier" + , mkPackageName "newtype-generics" + , mkPackageName "objective" + , mkPackageName "binary-ieee754" + , mkPackageName "rerebase" + , mkPackageName "cipher-aes" + , mkPackageName "cipher-blowfish" + , mkPackageName "cipher-camellia" + , mkPackageName "cipher-des" + , mkPackageName "cipher-rc4" + , mkPackageName "crypto-cipher-types" + , mkPackageName "crypto-numbers" + , mkPackageName "crypto-pubkey" + , mkPackageName "crypto-random" + , mkPackageName "cryptohash" + , mkPackageName "cryptohash-conduit" + , mkPackageName "cryptohash-md5" + , mkPackageName "cryptohash-sha1" + , mkPackageName "cryptohash-sha256" ] toModuleInfo :: LoadedSnapshot -> ModuleInfo diff --git a/src/Stack/Setup.hs b/src/Stack/Setup.hs index 1b27a5bb40..707f998e53 100644 --- a/src/Stack/Setup.hs +++ b/src/Stack/Setup.hs @@ -63,6 +63,8 @@ import qualified Data.Yaml as Yaml import Distribution.System (OS, Arch (..), Platform (..)) import qualified Distribution.System as Cabal import Distribution.Text (simpleParse) +import Distribution.Types.PackageName (mkPackageName) +import Distribution.Version (mkVersion) import Lens.Micro (set) import Network.HTTP.StackClient (getResponseBody, getResponseStatusCode) import Network.HTTP.Download @@ -377,7 +379,7 @@ ensureCompiler :: (HasConfig env, HasGHCVariant env) -> RIO env (Maybe ExtraDirs, CompilerBuild, Bool) ensureCompiler sopts = do let wc = whichCompiler (wantedToActual (soptsWantedCompiler sopts)) - when (getGhcVersion (wantedToActual (soptsWantedCompiler sopts)) < $(mkVersion "7.8")) $ do + when (getGhcVersion (wantedToActual (soptsWantedCompiler sopts)) < mkVersion [7, 8]) $ do logWarn "Stack will almost certainly fail with GHC below version 7.8" logWarn "Valiantly attempting to run anyway, but I know this is doomed" logWarn "For more information, see: https://github.com/commercialhaskell/stack/issues/648" @@ -407,7 +409,7 @@ ensureCompiler sopts = do case platform of Platform _ Cabal.Windows | not (soptsSkipMsys sopts) -> - case getInstalledTool installed $(mkPackageName "msys2") (const True) of + case getInstalledTool installed (mkPackageName "msys2") (const True) of Just tool -> return (Just tool) Nothing | soptsInstallIfMissing sopts -> do @@ -418,7 +420,7 @@ ensureCompiler sopts = do case Map.lookup osKey $ siMsys2 si of Just x -> return x Nothing -> throwString $ "MSYS2 not found for " ++ T.unpack osKey - let tool = Tool (PackageIdentifier $(mkPackageName "msys2") version) + let tool = Tool (PackageIdentifier (mkPackageName "msys2") version) Just <$> downloadAndInstallTool (configLocalPrograms config) si info tool (installMsys2Windows osKey) | otherwise -> do logWarn "Continuing despite missing tool: msys2" @@ -661,7 +663,7 @@ ensureDockerStackExe containerPlatform = do config <- view configL containerPlatformDir <- runReaderT platformOnlyRelDir (containerPlatform,PlatformVariantNone) let programsPath = configLocalProgramsBase config containerPlatformDir - tool = Tool (PackageIdentifier $(mkPackageName "stack") stackVersion) + tool = Tool (PackageIdentifier (mkPackageName "stack") stackVersion) stackExeDir <- installDir programsPath tool let stackExePath = stackExeDir $(mkRelFile "stack") stackExeExists <- doesFileExist stackExePath @@ -683,7 +685,7 @@ upgradeCabal :: (HasConfig env, HasGHCVariant env) upgradeCabal wc upgradeTo = do logWarn "Using deprecated --upgrade-cabal feature, this is not recommended" logWarn "Manipulating the global Cabal is only for debugging purposes" - let name = $(mkPackageName "Cabal") + let name = mkPackageName "Cabal" installed <- getCabalPkgVer wc case upgradeTo of Specific wantedVersion -> do @@ -715,7 +717,7 @@ doCabalInstall :: (HasConfig env, HasGHCVariant env) -> Version -> RIO env () doCabalInstall wc installed wantedVersion = do - when (wantedVersion >= $(mkVersion "2.2")) $ do + when (wantedVersion >= mkVersion [2, 2]) $ do logWarn "--upgrade-cabal will almost certainly fail for Cabal 2.2 or later" logWarn "See: https://github.com/commercialhaskell/stack/issues/4070" logWarn "Valiantly attempting to build it anyway, but I know this is doomed" @@ -725,7 +727,7 @@ doCabalInstall wc installed wantedVersion = do fromString (versionString wantedVersion) <> " to replace " <> fromString (versionString installed) - let name = $(mkPackageName "Cabal") + let name = mkPackageName "Cabal" suffix <- parseRelDir $ "Cabal-" ++ versionString wantedVersion let dir = tmpdir suffix unpackPackageLocation dir $ PLIHackage @@ -1267,20 +1269,20 @@ bootGhcjs ghcjsVersion stackYaml destDir bootOpts = logInfo "No cabal-install binary found for use with GHCJS." return True Just v - | v < $(mkVersion "1.22.4") -> do + | v < mkVersion [1, 22, 4] -> do logInfo $ "The cabal-install found on PATH is too old to be used for booting GHCJS (version " <> fromString (versionString v) <> ")." return True - | v >= $(mkVersion "1.23") -> do + | v >= mkVersion [1, 23] -> do logWarn $ "The cabal-install found on PATH is a version stack doesn't know about, version " <> fromString (versionString v) <> ". This may or may not work.\n" <> "See this issue: https://github.com/ghcjs/ghcjs/issues/470" return False - | ghcjsVersion >= $(mkVersion "0.2.0.20160413") && v >= $(mkVersion "1.22.8") -> do + | ghcjsVersion >= mkVersion [0, 2, 0, 20160413] && v >= mkVersion [1, 22, 8] -> do logWarn $ "The cabal-install found on PATH, version " <> fromString (versionString v) <> @@ -1315,7 +1317,7 @@ bootGhcjs ghcjsVersion stackYaml destDir bootOpts = Nothing -> do logError "Failed to get cabal-install version after installing it." failedToFindErr - Just v | v >= $(mkVersion "1.22.8") && v < $(mkVersion "1.23") -> + Just v | v >= mkVersion [1, 22, 8] && v < mkVersion [1, 23] -> logWarn $ "Installed version of cabal-install is in a version range which may not work.\n" <> "See this issue: https://github.com/ghcjs/ghcjs/issues/470\n" <> @@ -1680,7 +1682,7 @@ getUtf8EnvVars => ActualCompiler -> RIO env (Map Text Text) getUtf8EnvVars compilerVer = - if getGhcVersion compilerVer >= $(mkVersion "7.10.3") + if getGhcVersion compilerVer >= mkVersion [7, 10, 3] -- GHC_CHARENC supported by GHC >=7.10.3 then return $ Map.singleton "GHC_CHARENC" "UTF-8" else legacyLocale diff --git a/src/Stack/Solver.hs b/src/Stack/Solver.hs index 526ce2e360..f8af7256ca 100644 --- a/src/Stack/Solver.hs +++ b/src/Stack/Solver.hs @@ -39,6 +39,7 @@ import qualified Data.Yaml as Yaml import qualified Distribution.Package as C import qualified Distribution.PackageDescription as C import qualified Distribution.Text as C +import Distribution.Version (mkVersion) import Path import Path.Find (findFiles) import Path.IO hiding (findExecutable, findFiles, withSystemTempDir) @@ -55,9 +56,6 @@ import Stack.Types.Build import Stack.Types.BuildPlan import Stack.Types.Compiler import Stack.Types.Config -import Stack.Types.FlagName -import Stack.Types.PackageIdentifier -import Stack.Types.Version import qualified System.Directory as D import qualified System.FilePath as FP import RIO.Process @@ -207,9 +205,8 @@ parseCabalOutputLine t0 = maybe (Left t0) Right . join . match re $ t0 mk :: String -> [Maybe (Bool, String)] -> Maybe (PackageName, (Version, Map FlagName Bool)) mk ident fl = do - PackageIdentifier name version <- - parsePackageIdentifierThrowing ident - fl' <- (traverse . traverse) parseFlagNameThrowing $ catMaybes fl + PackageIdentifier name version <- parsePackageIdentifier ident + fl' <- (traverse . traverse) parseFlagName $ catMaybes fl return (name, (version, Map.fromList $ map swap fl')) lexeme r = some (psym isSpace) *> r @@ -298,12 +295,12 @@ setupCabalEnv compiler inner = do case mcabal of Nothing -> throwM SolverMissingCabalInstall Just version - | version < $(mkVersion "1.24") -> prettyWarn $ + | version < mkVersion [1, 24] -> prettyWarn $ "Installed version of cabal-install (" <> fromString (versionString version) <> ") doesn't support custom-setup clause, and so may not yield correct results." <> line <> "To resolve this, install a newer version via 'stack install cabal-install'." <> line - | version >= $(mkVersion "1.25") -> prettyWarn $ + | version >= mkVersion [1, 25] -> prettyWarn $ "Installed version of cabal-install (" <> fromString (versionString version) <> ") is newer than stack has been tested with. If you run into difficulties, consider downgrading." <> line diff --git a/src/Stack/Types/Build.hs b/src/Stack/Types/Build.hs index c01d8153c7..6987292012 100644 --- a/src/Stack/Types/Build.hs +++ b/src/Stack/Types/Build.hs @@ -64,6 +64,7 @@ import Data.Time.Clock import Distribution.PackageDescription (TestSuiteInterface) import Distribution.System (Arch) import qualified Distribution.Text as C +import Distribution.Version (mkVersion) import Path (mkRelDir, parseRelDir, (), parent) import Path.Extra (toFilePathNoTrailingSep) import Stack.Constants @@ -610,7 +611,7 @@ configureOptsNoDir econfig bco deps isLocal package = concat -- earlier. Cabal also might do less work then. useExactConf = configAllowNewer config - newerCabal = view cabalVersionL econfig >= $(mkVersion "1.22") + newerCabal = view cabalVersionL econfig >= mkVersion [1, 22] -- Unioning atop defaults is needed so that all flags are specified -- with --exact-configuration. diff --git a/src/Stack/Types/Config.hs b/src/Stack/Types/Config.hs index fbd7ba9e65..659a9ed81b 100644 --- a/src/Stack/Types/Config.hs +++ b/src/Stack/Types/Config.hs @@ -199,7 +199,7 @@ import qualified Distribution.PackageDescription as C import Distribution.System (Platform) import qualified Distribution.Text import qualified Distribution.Types.UnqualComponentName as C -import Distribution.Version (anyVersion, mkVersion') +import Distribution.Version (anyVersion, mkVersion', mkVersion) import Generics.Deriving.Monoid (memptydefault, mappenddefault) import Lens.Micro (Lens', lens, _1, _2, to) import Options.Applicative (ReadM) @@ -216,7 +216,6 @@ import Stack.Types.Docker import Stack.Types.Image import Stack.Types.NamedComponent import Stack.Types.Nix -import Stack.Types.PackageName import Stack.Types.Resolver import Stack.Types.Runner import Stack.Types.StylesUpdate (StylesUpdate, @@ -867,9 +866,9 @@ parseConfigMonoidObject rootDir obj = do name <- if name' == "*" then return Nothing - else case parsePackageNameThrowing $ T.unpack name' of - Left e -> fail $ show e - Right x -> return $ Just x + else case parsePackageName $ T.unpack name' of + Nothing -> fail $ "Invalid package name: " ++ show name' + Just x -> return $ Just x return (name, b) configMonoidWorkDirName :: Text @@ -1753,9 +1752,9 @@ instance FromJSONKey GhcOptionKey where "$locals" -> return GOKLocals "$targets" -> return GOKTargets _ -> - case parsePackageNameThrowing $ T.unpack t of - Left e -> fail $ show e - Right x -> return $ GOKPackage x + case parsePackageName $ T.unpack t of + Nothing -> fail $ "Invalid package name: " ++ show t + Just x -> return $ GOKPackage x fromJSONKeyList = FromJSONKeyTextParser $ \_ -> fail "GhcOptionKey.fromJSONKeyList" newtype GhcOptions = GhcOptions { unGhcOptions :: [Text] } @@ -1969,7 +1968,7 @@ envOverrideSettingsL = configL.lens shouldForceGhcColorFlag :: (HasRunner env, HasEnvConfig env) => RIO env Bool shouldForceGhcColorFlag = do - canDoColor <- (>= $(mkVersion "8.2.1")) . getGhcVersion + canDoColor <- (>= mkVersion [8, 2, 1]) . getGhcVersion <$> view actualCompilerVersionL shouldDoColor <- view useColorL return $ canDoColor && shouldDoColor diff --git a/src/Stack/Types/FlagName.hs b/src/Stack/Types/FlagName.hs deleted file mode 100644 index 0f984e190c..0000000000 --- a/src/Stack/Types/FlagName.hs +++ /dev/null @@ -1,60 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE BangPatterns #-} -{-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE DeriveDataTypeable #-} -{-# LANGUAGE TupleSections #-} - --- | Names for flags. - -module Stack.Types.FlagName - (FlagName - ,FlagNameParseFail(..) - ,parseFlagName - ,parseFlagNameThrowing - ,mkFlagName) - where - -import Stack.Prelude -import qualified Data.Text as T -import qualified Distribution.PackageDescription as Cabal -import Distribution.PackageDescription (FlagName) -import Language.Haskell.TH -import Language.Haskell.TH.Syntax - --- | A parse fail. -newtype FlagNameParseFail = FlagNameParseFail Text - deriving (Typeable) -instance Exception FlagNameParseFail -instance Show FlagNameParseFail where - show (FlagNameParseFail bs) = "Invalid flag name: " ++ show bs - - {- -instance FromJSON FlagName where - parseJSON j = - do s <- parseJSON j - case parseFlagNameFromString s of - Nothing -> - fail ("Couldn't parse flag name: " ++ s) - Just ver -> return ver - -instance FromJSONKey FlagName where - fromJSONKey = FromJSONKeyTextParser $ \k -> - either (fail . show) return $ parseFlagName k - -} - --- | Make a flag name. -mkFlagName :: String -> Q Exp -mkFlagName s = - case parseFlagName s of - Nothing -> qRunIO $ throwString ("Invalid flag name: " ++ show s) - Just _ -> [|Cabal.mkFlagName s|] - --- | Convenience function for parsing from a 'String' -parseFlagNameThrowing :: MonadThrow m => String -> m FlagName -parseFlagNameThrowing str = - case parseFlagName str of - Nothing -> throwM $ FlagNameParseFail $ T.pack str - Just fn -> pure fn diff --git a/src/Stack/Types/PackageIdentifier.hs b/src/Stack/Types/PackageIdentifier.hs deleted file mode 100644 index 097a932137..0000000000 --- a/src/Stack/Types/PackageIdentifier.hs +++ /dev/null @@ -1,31 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE DeriveDataTypeable #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# OPTIONS -fno-warn-unused-do-bind #-} - --- | Package identifier (name-version). - -module Stack.Types.PackageIdentifier - ( parsePackageIdentifier - , parsePackageIdentifierThrowing - ) where - -import Stack.Prelude -import qualified Data.Text as T - --- | A parse fail. -newtype PackageIdentifierParseFail - = PackageIdentifierParseFail Text - deriving (Typeable) -instance Show PackageIdentifierParseFail where - show (PackageIdentifierParseFail bs) = "Invalid package identifier: " ++ show bs -instance Exception PackageIdentifierParseFail - --- | Convenience function for parsing from a 'String'. -parsePackageIdentifierThrowing :: MonadThrow m => String -> m PackageIdentifier -parsePackageIdentifierThrowing str = - case parsePackageIdentifier str of - Nothing -> throwM $ PackageIdentifierParseFail $ T.pack str - Just ident -> pure ident diff --git a/src/Stack/Types/PackageName.hs b/src/Stack/Types/PackageName.hs index 989673ad3f..8dadb647d8 100644 --- a/src/Stack/Types/PackageName.hs +++ b/src/Stack/Types/PackageName.hs @@ -10,20 +10,13 @@ -- | Names for packages. module Stack.Types.PackageName - (PackageName - ,PackageNameParseFail(..) - ,parsePackageName - ,parsePackageNameThrowing + (parsePackageNameThrowing ,parsePackageNameFromFilePath - ,mkPackageName ,packageNameArgument) where import Stack.Prelude import qualified Data.Text as T -import qualified Distribution.Package as Cabal -import Language.Haskell.TH -import Language.Haskell.TH.Syntax import qualified Options.Applicative as O import Path @@ -39,13 +32,6 @@ instance Show PackageNameParseFail where show (CabalFileNameParseFail fp) = "Invalid file path for cabal file, must have a .cabal extension: " ++ fp show (CabalFileNameInvalidPackageName fp) = "cabal file names must use valid package names followed by a .cabal extension, the following is invalid: " ++ fp --- | Make a package name. -mkPackageName :: String -> Q Exp -mkPackageName s = - case parsePackageName s of - Nothing -> qRunIO $ throwIO (PackageNameParseFail $ T.pack s) - Just _ -> [|Cabal.mkPackageName s|] - -- | Parse a package name from a 'String'. parsePackageNameThrowing :: MonadThrow m => String -> m PackageName parsePackageNameThrowing str = diff --git a/src/Stack/Types/Version.hs b/src/Stack/Types/Version.hs index c57e119115..9bc4f285a1 100644 --- a/src/Stack/Types/Version.hs +++ b/src/Stack/Types/Version.hs @@ -15,9 +15,7 @@ module Stack.Types.Version ,Cabal.VersionRange -- TODO in the future should have a newtype wrapper ,IntersectingVersionRange(..) ,VersionCheck(..) - ,parseVersion ,parseVersionThrowing - ,mkVersion ,versionRangeText ,withinRange ,Stack.Types.Version.intersectVersionRanges @@ -39,8 +37,6 @@ import qualified Data.Text as T import Distribution.Text (disp) import qualified Distribution.Version as Cabal import Distribution.Version (Version, versionNumbers, withinRange) -import Language.Haskell.TH -import Language.Haskell.TH.Syntax import qualified Paths_stack as Meta import Text.PrettyPrint (render) @@ -73,13 +69,6 @@ parseVersionThrowing str = Nothing -> throwM $ VersionParseFail $ T.pack str Just v -> pure v --- | Make a package version. -mkVersion :: String -> Q Exp -mkVersion s = - case parseVersion s of - Nothing -> qRunIO $ throwIO (VersionParseFail $ T.pack s) - Just (versionNumbers -> vs) -> [|Cabal.mkVersion vs|] - -- | Display a version range versionRangeText :: Cabal.VersionRange -> Text versionRangeText = T.pack . render . disp diff --git a/src/test/Stack/Build/TargetSpec.hs b/src/test/Stack/Build/TargetSpec.hs index 3c12b48acd..ffd210a233 100644 --- a/src/test/Stack/Build/TargetSpec.hs +++ b/src/test/Stack/Build/TargetSpec.hs @@ -4,11 +4,11 @@ module Stack.Build.TargetSpec (main, spec) where import qualified Data.Text as T +import Distribution.Types.PackageName (mkPackageName) +import Distribution.Version (mkVersion) import Stack.Build.Target import Stack.Prelude import Stack.Types.NamedComponent -import Stack.Types.PackageName -import Stack.Types.Version import Test.Hspec main :: IO () @@ -18,13 +18,13 @@ spec :: Spec spec = do describe "parseRawTarget" $ do let test s e = it s $ parseRawTarget (T.pack s) `shouldBe` e - test "foobar" $ Just $ RTPackage $(mkPackageName "foobar") + test "foobar" $ Just $ RTPackage (mkPackageName "foobar") test "foobar-1.2.3" $ Just $ RTPackageIdentifier $ PackageIdentifier - $(mkPackageName "foobar") $(mkVersion "1.2.3") + (mkPackageName "foobar") (mkVersion [1, 2, 3]) test "./foobar" Nothing test "foobar/" Nothing test "/foobar" Nothing test ":some-exe" $ Just $ RTComponent "some-exe" - test "foobar:some-exe" $ Just $ RTPackageComponent $(mkPackageName "foobar") $ UnresolvedComponent "some-exe" - test "foobar:exe:some-exe" $ Just $ RTPackageComponent $(mkPackageName "foobar") + test "foobar:some-exe" $ Just $ RTPackageComponent (mkPackageName "foobar") $ UnresolvedComponent "some-exe" + test "foobar:exe:some-exe" $ Just $ RTPackageComponent (mkPackageName "foobar") $ ResolvedComponent $ CExe "some-exe" diff --git a/src/test/Stack/PackageDumpSpec.hs b/src/test/Stack/PackageDumpSpec.hs index f59172968d..2c8f205670 100644 --- a/src/test/Stack/PackageDumpSpec.hs +++ b/src/test/Stack/PackageDumpSpec.hs @@ -10,13 +10,12 @@ import Data.Conduit.Text (decodeUtf8) import qualified Data.Map as Map import qualified Data.Set as Set import Distribution.License (License(..)) +import Distribution.Types.PackageName (mkPackageName) +import Distribution.Version (mkVersion) import Stack.PackageDump import Stack.Prelude import Stack.Types.Compiler import Stack.Types.GhcPkgId -import Stack.Types.PackageIdentifier -import Stack.Types.PackageName -import Stack.Types.Version import RIO.Process import Test.Hspec import Test.Hspec.QuickCheck @@ -72,7 +71,8 @@ spec = do .| conduitDumpPackage .| CL.consume ghcPkgId <- parseGhcPkgId "haskell2010-1.1.2.0-05c8dd51009e08c6371c82972d40f55a" - packageIdent <- parsePackageIdentifierThrowing "haskell2010-1.1.2.0" + packageIdent <- maybe (fail "Not parsable package id") return $ + parsePackageIdentifier "haskell2010-1.1.2.0" depends <- mapM parseGhcPkgId [ "array-0.5.0.0-470385a50d2b78598af85cfe9d988e1b" , "base-4.7.0.2-bfd89587617e381ae01b8dd7b6c7f1c1" @@ -105,7 +105,8 @@ spec = do .| conduitDumpPackage .| CL.consume ghcPkgId <- parseGhcPkgId "ghc-7.10.1-325809317787a897b7a97d646ceaa3a3" - pkgIdent <- parsePackageIdentifierThrowing "ghc-7.10.1" + pkgIdent <- maybe (fail "Not parsable package id") return $ + parsePackageIdentifier "ghc-7.10.1" depends <- mapM parseGhcPkgId [ "array-0.5.1.0-e29cdbe82692341ebb7ce6e2798294f9" , "base-4.8.0.0-1b689eb8d72c4d4cc88f445839c1f01a" @@ -148,7 +149,8 @@ spec = do .| conduitDumpPackage .| CL.consume ghcPkgId <- parseGhcPkgId "hmatrix-0.16.1.5-12d5d21f26aa98774cdd8edbc343fbfe" - pkgId <- parsePackageIdentifierThrowing"hmatrix-0.16.1.5" + pkgId <- maybe (fail "Not parsable package id") return $ + parsePackageIdentifier "hmatrix-0.16.1.5" depends <- mapM parseGhcPkgId [ "array-0.5.0.0-470385a50d2b78598af85cfe9d988e1b" , "base-4.7.0.2-918c7ac27f65a87103264a9f51652d63" @@ -189,7 +191,8 @@ spec = do .| conduitDumpPackage .| CL.consume ghcPkgId <- parseGhcPkgId "ghc-boot-0.0.0.0" - pkgId <- parsePackageIdentifierThrowing"ghc-boot-0.0.0.0" + pkgId <- maybe (fail "Not parsable package id") return $ + parsePackageIdentifier "ghc-boot-0.0.0.0" depends <- mapM parseGhcPkgId [ "base-4.9.0.0" , "binary-0.7.5.0" @@ -233,13 +236,13 @@ spec = do .| addProfiling icache .| addHaddock icache .| fakeAddSymbols - .| sinkMatching False False False (Map.singleton $(mkPackageName "transformers") $(mkVersion "0.0.0.0.0.0.1")) - case Map.lookup $(mkPackageName "base") m of + .| sinkMatching False False False (Map.singleton (mkPackageName "transformers") (mkVersion [0, 0, 0, 0, 0, 0, 1])) + case Map.lookup (mkPackageName "base") m of Nothing -> error "base not present" Just _ -> return () liftIO $ do - Map.lookup $(mkPackageName "transformers") m `shouldBe` Nothing - Map.lookup $(mkPackageName "ghc") m `shouldBe` Nothing + Map.lookup (mkPackageName "transformers") m `shouldBe` Nothing + Map.lookup (mkPackageName "ghc") m `shouldBe` Nothing describe "pruneDeps" $ do it "sanity check" $ do diff --git a/src/test/Stack/SnapshotSpec.hs b/src/test/Stack/SnapshotSpec.hs index a9b3842b13..d938aee22d 100644 --- a/src/test/Stack/SnapshotSpec.hs +++ b/src/test/Stack/SnapshotSpec.hs @@ -3,11 +3,11 @@ {-# LANGUAGE TemplateHaskell #-} module Stack.SnapshotSpec (spec) where +import Distribution.Types.PackageName (mkPackageName) +import Distribution.Version (mkVersion) import Stack.Prelude import Stack.Snapshot (loadGlobalHints) -import Stack.Types.PackageName import Stack.Types.Runner (withRunner, ColorWhen (ColorNever)) -import Stack.Types.Version import Test.Hspec import qualified RIO.Map as Map import RIO.ByteString (hPut) @@ -23,23 +23,23 @@ spec = do withRunner LevelError False False ColorNever mempty Nothing False $ \runner -> runRIO runner $ inner abs' it' "unknown compiler" $ \fp -> do - mmap <- loadGlobalHints fp $ WCGhc $(mkVersion "0.0.0.0.0.0.0") + mmap <- loadGlobalHints fp $ WCGhc (mkVersion [0, 0, 0, 0, 0, 0, 0]) liftIO $ mmap `shouldBe` Nothing it' "known compiler" $ \fp -> do - mmap <- loadGlobalHints fp $ WCGhc $(mkVersion "8.4.3") + mmap <- loadGlobalHints fp $ WCGhc (mkVersion [8, 4, 3]) case mmap of Nothing -> error "not found" Just m -> liftIO $ do - Map.lookup $(mkPackageName "ghc") m `shouldBe` Just $(mkVersion "8.4.3") - Map.lookup $(mkPackageName "base") m `shouldBe` Just $(mkVersion "4.11.1.0") - Map.lookup $(mkPackageName "bytestring") m `shouldBe` Just $(mkVersion "0.10.8.2") - Map.lookup $(mkPackageName "acme-missiles") m `shouldBe` Nothing + Map.lookup (mkPackageName "ghc") m `shouldBe` Just (mkVersion [8, 4, 3]) + Map.lookup (mkPackageName "base") m `shouldBe` Just (mkVersion [4, 11, 1, 0]) + Map.lookup (mkPackageName "bytestring") m `shouldBe` Just (mkVersion [0, 10, 8, 2]) + Map.lookup (mkPackageName "acme-missiles") m `shouldBe` Nothing it' "older known compiler" $ \fp -> do - mmap <- loadGlobalHints fp $ WCGhc $(mkVersion "7.8.4") + mmap <- loadGlobalHints fp $ WCGhc (mkVersion [7, 8, 4]) case mmap of Nothing -> error "not found" Just m -> liftIO $ do - Map.lookup $(mkPackageName "ghc") m `shouldBe` Just $(mkVersion "7.8.4") - Map.lookup $(mkPackageName "base") m `shouldBe` Just $(mkVersion "4.7.0.2") - Map.lookup $(mkPackageName "Cabal") m `shouldBe` Just $(mkVersion "1.18.1.5") - Map.lookup $(mkPackageName "acme-missiles") m `shouldBe` Nothing + Map.lookup (mkPackageName "ghc") m `shouldBe` Just (mkVersion [7, 8, 4]) + Map.lookup (mkPackageName "base") m `shouldBe` Just (mkVersion [4, 7, 0, 2]) + Map.lookup (mkPackageName "Cabal") m `shouldBe` Just (mkVersion [1, 18, 1, 5]) + Map.lookup (mkPackageName "acme-missiles") m `shouldBe` Nothing diff --git a/src/test/Stack/SolverSpec.hs b/src/test/Stack/SolverSpec.hs index c15473bcdf..ed298dc55a 100644 --- a/src/test/Stack/SolverSpec.hs +++ b/src/test/Stack/SolverSpec.hs @@ -5,10 +5,10 @@ module Stack.SolverSpec where import Data.Text (unpack) +import Distribution.PackageDescription (mkFlagName) +import Distribution.Types.PackageName (mkPackageName) +import Distribution.Version (mkVersion) import Stack.Prelude -import Stack.Types.FlagName -import Stack.Types.PackageName -import Stack.Types.Version import Test.Hspec import qualified Data.Map as Map @@ -19,26 +19,26 @@ spec = describe "Stack.Solver" $ do successfulExample "text-1.2.1.1 (latest: 1.2.2.0) -integer-simple (via: parsec-3.1.9) (new package)" - $(mkPackageName "text") - $(mkVersion "1.2.1.1") - [ ($(mkFlagName "integer-simple"), False) + (mkPackageName "text") + (mkVersion [1, 2, 1, 1]) + [ (mkFlagName "integer-simple", False) ] successfulExample "hspec-snap-1.0.0.0 *test (via: servant-snap-0.5) (new package)" - $(mkPackageName "hspec-snap") - $(mkVersion "1.0.0.0") + (mkPackageName "hspec-snap") + (mkVersion [1, 0, 0, 0]) [] successfulExample "time-locale-compat-0.1.1.1 -old-locale (via: http-api-data-0.2.2) (new package)" - $(mkPackageName "time-locale-compat") - $(mkVersion "0.1.1.1") - [ ($(mkFlagName "old-locale"), False) + (mkPackageName "time-locale-compat") + (mkVersion [0, 1, 1, 1]) + [ (mkFlagName "old-locale", False) ] successfulExample "flowdock-rest-0.2.0.0 -aeson-compat *test (via: haxl-fxtra-0.0.0.0) (new package)" - $(mkPackageName "flowdock-rest") - $(mkVersion "0.2.0.0") - [ ($(mkFlagName "aeson-compat"), False) + (mkPackageName "flowdock-rest") + (mkVersion [0, 2, 0, 0]) + [ (mkFlagName "aeson-compat", False) ] where successfulExample input pkgName' pkgVersion' flags =