Skip to content

Commit b338401

Browse files
committed
Ignore stack patchlevel for doc links and docker exe dl
1 parent 5cddf28 commit b338401

File tree

5 files changed

+23
-16
lines changed

5 files changed

+23
-16
lines changed

src/Stack/Options/BuildParser.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,17 +4,16 @@
44
module Stack.Options.BuildParser where
55

66
import qualified Data.Map as Map
7-
import Data.Version (showVersion)
87
import Options.Applicative
98
import Options.Applicative.Args
109
import Options.Applicative.Builder.Extra
11-
import Paths_stack as Meta
1210
import Stack.Options.Completion
1311
import Stack.Options.PackageParser (readFlag)
1412
import Stack.Prelude
1513
import Stack.Types.Config
1614
import Stack.Types.FlagName
1715
import Stack.Types.PackageName
16+
import Stack.Types.Version
1817

1918
-- | Parser for CLI-only build arguments
2019
buildOptsParser :: BuildCommand
@@ -92,7 +91,7 @@ targetsParser =
9291
completer targetCompleter <>
9392
help ("If none specified, use all local packages. " <>
9493
"See https://docs.haskellstack.org/en/v" <>
95-
showVersion Meta.version <>
94+
versionString stackMinorVersion <>
9695
"/build_command/#target-syntax for details.")))
9796

9897
flagsParser :: Parser (Map.Map (Maybe PackageName) (Map.Map FlagName Bool))

src/Stack/Options/GhciParser.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,15 @@
11
{-# LANGUAGE NoImplicitPrelude #-}
22
module Stack.Options.GhciParser where
33

4-
import Data.Version (showVersion)
54
import Options.Applicative
65
import Options.Applicative.Args
76
import Options.Applicative.Builder.Extra
8-
import Paths_stack as Meta
97
import Stack.Config (packagesParser)
108
import Stack.Ghci (GhciOpts (..))
119
import Stack.Options.BuildParser (flagsParser)
1210
import Stack.Options.Completion
1311
import Stack.Prelude
12+
import Stack.Types.Version
1413

1514
-- | Parser for GHCI options
1615
ghciOptsParser :: Parser GhciOpts
@@ -21,7 +20,7 @@ ghciOptsParser = GhciOpts
2120
completer (targetCompleter <> fileExtCompleter [".hs", ".lhs"]) <>
2221
help ("If none specified, use all local packages. " <>
2322
"See https://docs.haskellstack.org/en/v" <>
24-
showVersion Meta.version <>
23+
versionString stackMinorVersion <>
2524
"/build_command/#target-syntax for details. " <>
2625
"If a path to a .hs or .lhs file is specified, it will be loaded.")))
2726
<*> fmap concat (many (argsOption (long "ghci-options" <>

src/Stack/Setup.hs

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -61,15 +61,13 @@ import qualified Data.Yaml as Yaml
6161
import Distribution.System (OS, Arch (..), Platform (..))
6262
import qualified Distribution.System as Cabal
6363
import Distribution.Text (simpleParse)
64-
import Distribution.Version (mkVersion')
6564
import Lens.Micro (set)
6665
import Network.HTTP.Simple (getResponseBody, httpLBS, withResponse, getResponseStatusCode)
6766
import Network.HTTP.Download
6867
import Path
6968
import Path.CheckInstall (warnInstallSearchPathIssues)
7069
import Path.Extra (toFilePathNoTrailingSep)
7170
import Path.IO hiding (findExecutable, withSystemTempDir)
72-
import qualified Paths_stack as Meta
7371
import Prelude (getLine, putStr, putStrLn, until)
7472
import Stack.Build (build)
7573
import Stack.Config (loadConfig)
@@ -661,7 +659,7 @@ ensureDockerStackExe containerPlatform = do
661659
stackExeExists <- doesFileExist stackExePath
662660
unless stackExeExists $ do
663661
logInfo $ mconcat ["Downloading Docker-compatible ", T.pack stackProgName, " executable"]
664-
sri <- downloadStackReleaseInfo Nothing Nothing (Just (versionString stackVersion))
662+
sri <- downloadStackReleaseInfo Nothing Nothing (Just (versionString stackMinorVersion))
665663
platforms <- runReaderT preferredPlatforms (containerPlatform, PlatformVariantNone)
666664
downloadStackExe platforms sri stackExeDir False (const $ return ())
667665
return stackExePath
@@ -1983,6 +1981,3 @@ getDownloadVersion (StackReleaseInfo val) = do
19831981
String rawName <- HashMap.lookup "name" o
19841982
-- drop the "v" at the beginning of the name
19851983
parseVersion $ T.drop 1 rawName
1986-
1987-
stackVersion :: Version
1988-
stackVersion = fromCabalVersion (mkVersion' Meta.version)

src/Stack/Types/Build.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -62,13 +62,11 @@ import Data.Text.Encoding (decodeUtf8With)
6262
import Data.Text.Encoding.Error (lenientDecode)
6363
import Data.Time.Calendar
6464
import Data.Time.Clock
65-
import Data.Version (showVersion)
6665
import Distribution.PackageDescription (TestSuiteInterface)
6766
import Distribution.System (Arch)
6867
import qualified Distribution.Text as C
6968
import Path (mkRelDir, parseRelDir, (</>))
7069
import Path.Extra (toFilePathNoTrailingSep)
71-
import Paths_stack as Meta
7270
import Stack.Constants
7371
import Stack.Types.BuildPlan
7472
import Stack.Types.Compiler
@@ -187,7 +185,7 @@ instance Show StackBuildException where
187185
"The following target packages were not found: " ++
188186
intercalate ", " (map packageNameString $ Set.toList noKnown) ++
189187
"\nSee https://docs.haskellstack.org/en/v"
190-
<> showVersion Meta.version <>
188+
<> versionString stackMinorVersion <>
191189
"/build_command/#target-syntax for details."
192190
notInSnapshot'
193191
| Map.null notInSnapshot = []

src/Stack/Types/Version.hs

Lines changed: 17 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,10 @@ module Stack.Types.Version
2929
,latestApplicableVersion
3030
,checkVersion
3131
,nextMajorVersion
32-
,UpgradeTo(..))
32+
,UpgradeTo(..)
33+
,minorVersion
34+
,stackVersion
35+
,stackMinorVersion)
3336
where
3437

3538
import Stack.Prelude hiding (Vector)
@@ -45,6 +48,7 @@ import Distribution.Text (disp)
4548
import qualified Distribution.Version as Cabal
4649
import Language.Haskell.TH
4750
import Language.Haskell.TH.Syntax
51+
import qualified Paths_stack as Meta
4852
import Text.PrettyPrint (render)
4953

5054
-- | A parse fail.
@@ -219,3 +223,15 @@ checkVersion check (Version wanted) (Version actual) =
219223
(Nothing, _) -> True
220224
(Just _, Nothing) -> False
221225
(Just w, Just a) -> a >= w
226+
227+
-- | Get minor version (excludes any patchlevel)
228+
minorVersion :: Version -> Version
229+
minorVersion (Version v) = Version (V.take 3 v)
230+
231+
-- | Current Stack version
232+
stackVersion :: Version
233+
stackVersion = fromCabalVersion (Cabal.mkVersion' Meta.version)
234+
235+
-- | Current Stack minor version (excludes patchlevel)
236+
stackMinorVersion :: Version
237+
stackMinorVersion = minorVersion stackVersion

0 commit comments

Comments
 (0)