Skip to content

Commit 7c08f52

Browse files
committed
Warn when binary installed by "stack upgrade" isn't visible on PATH
1 parent a8f8239 commit 7c08f52

File tree

4 files changed

+68
-40
lines changed

4 files changed

+68
-40
lines changed

ChangeLog.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -174,6 +174,8 @@ Other enhancements:
174174
* Upgraded `http-client-tls` version, which now offers support for the
175175
`socks5://` and `socks5h://` values in the `http_proxy` and `https_proxy`
176176
environment variables.
177+
* Binary "stack upgrade" will now warn if the installed executable is not
178+
on the PATH or shadowed by another entry.
177179

178180
Bug fixes:
179181

src/Path/CheckInstall.hs

Lines changed: 60 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,60 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE TemplateHaskell #-}
3+
{-# LANGUAGE OverloadedStrings #-}
4+
5+
module Path.CheckInstall where
6+
7+
import Control.Monad (unless)
8+
import Control.Monad.Extra (anyM, (&&^))
9+
import Control.Monad.IO.Class
10+
import Control.Monad.Logger
11+
import Data.Foldable (forM_)
12+
import Data.Text (Text)
13+
import qualified Data.Text as T
14+
import qualified System.Directory as D
15+
import qualified System.FilePath as FP
16+
17+
-- | Checks if the installed executable will be available on the user's
18+
-- PATH. This doesn't use @envSearchPath menv@ because it includes paths
19+
-- only visible when running in the stack environment.
20+
warnInstallSearchPathIssues :: (MonadIO m, MonadLogger m) => FilePath -> [Text] -> m ()
21+
warnInstallSearchPathIssues destDir installed = do
22+
searchPath <- liftIO FP.getSearchPath
23+
destDirIsInPATH <- liftIO $
24+
anyM (\dir -> D.doesDirectoryExist dir &&^ fmap (FP.equalFilePath destDir) (D.canonicalizePath dir)) searchPath
25+
if destDirIsInPATH
26+
then forM_ installed $ \exe -> do
27+
mexePath <- (liftIO . D.findExecutable . T.unpack) exe
28+
case mexePath of
29+
Just exePath -> do
30+
exeDir <- (liftIO . fmap FP.takeDirectory . D.canonicalizePath) exePath
31+
unless (exeDir `FP.equalFilePath` destDir) $ do
32+
$logWarn ""
33+
$logWarn $ T.concat
34+
[ "WARNING: The \""
35+
, exe
36+
, "\" executable found on the PATH environment variable is "
37+
, T.pack exePath
38+
, ", and not the version that was just installed."
39+
]
40+
$logWarn $ T.concat
41+
[ "This means that \""
42+
, exe
43+
, "\" calls on the command line will not use this version."
44+
]
45+
Nothing -> do
46+
$logWarn ""
47+
$logWarn $ T.concat
48+
[ "WARNING: Installation path "
49+
, T.pack destDir
50+
, " is on the PATH but the \""
51+
, exe
52+
, "\" executable that was just installed could not be found on the PATH."
53+
]
54+
else do
55+
$logWarn ""
56+
$logWarn $ T.concat
57+
[ "WARNING: Installation path "
58+
, T.pack destDir
59+
, " not found on the PATH environment variable"
60+
]

src/Stack/Build/Execute.hs

Lines changed: 2 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,6 @@ import Control.Exception.Safe (catchIO)
2929
import Control.Exception.Lifted
3030
import Control.Monad (liftM, when, unless, void)
3131
import Control.Monad.Catch (MonadCatch)
32-
import Control.Monad.Extra (anyM, (&&^))
3332
import Control.Monad.IO.Class
3433
import Control.Monad.Logger
3534
import Control.Monad.Trans.Control (liftBaseWith)
@@ -74,6 +73,7 @@ import Distribution.System (OS (Windows),
7473
import qualified Distribution.Text as C
7574
import Language.Haskell.TH as TH (location)
7675
import Path
76+
import Path.CheckInstall
7777
import Path.Extra (toFilePathNoTrailingSep, rejectMissingFile)
7878
import Path.IO hiding (findExecutable, makeAbsolute)
7979
import Prelude hiding (FilePath, writeFile, any)
@@ -551,46 +551,8 @@ copyExecutables exes = do
551551
, T.pack destDir'
552552
, ":"]
553553
forM_ installed $ \exe -> $logInfo ("- " <> exe)
554+
warnInstallSearchPathIssues destDir' installed
554555

555-
searchPath <- liftIO FP.getSearchPath
556-
destDirIsInPATH <- liftIO $
557-
anyM (\dir -> D.doesDirectoryExist dir &&^ fmap (FP.equalFilePath destDir') (D.canonicalizePath dir)) searchPath
558-
if destDirIsInPATH
559-
then forM_ installed $ \exe -> do
560-
mexePath <- (liftIO . D.findExecutable . T.unpack) exe
561-
case mexePath of
562-
Just exePath -> do
563-
exeDir <- (liftIO . fmap FP.takeDirectory . D.canonicalizePath) exePath
564-
unless (exeDir `FP.equalFilePath` destDir') $ do
565-
$logWarn ""
566-
$logWarn $ T.concat
567-
[ "WARNING: The \""
568-
, exe
569-
, "\" executable found on the PATH environment variable is "
570-
, T.pack exePath
571-
, ", and not the version that was just installed."
572-
]
573-
$logWarn $ T.concat
574-
[ "This means that \""
575-
, exe
576-
, "\" calls on the command line will not use this version."
577-
]
578-
Nothing -> do
579-
$logWarn ""
580-
$logWarn $ T.concat
581-
[ "WARNING: Installation path "
582-
, T.pack destDir'
583-
, " is on the PATH but the \""
584-
, exe
585-
, "\" executable that was just installed could not be found on the PATH."
586-
]
587-
else do
588-
$logWarn ""
589-
$logWarn $ T.concat
590-
[ "WARNING: Installation path "
591-
, T.pack destDir'
592-
, " not found on the PATH environment variable"
593-
]
594556

595557
-- | Windows can't write over the current executable. Instead, we rename the
596558
-- current executable to something else and then do the copy.

src/Stack/Setup.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,7 @@ import Lens.Micro (set)
8181
import Network.HTTP.Simple (getResponseBody, httpLBS, withResponse, getResponseStatusCode)
8282
import Network.HTTP.Download
8383
import Path
84+
import Path.CheckInstall (warnInstallSearchPathIssues)
8485
import Path.Extra (toFilePathNoTrailingSep)
8586
import Path.IO hiding (findExecutable)
8687
import qualified Paths_stack as Meta
@@ -1765,6 +1766,9 @@ downloadStackExe platforms0 archiveInfo destDir testExe = do
17651766
renameFile tmpFile destFile
17661767
_ -> renameFile tmpFile destFile
17671768

1769+
destDir' <- liftIO . D.canonicalizePath . toFilePath $ destDir
1770+
warnInstallSearchPathIssues destDir' ["stack"]
1771+
17681772
$logInfo $ T.pack $ "New stack executable available at " ++ toFilePath destFile
17691773
where
17701774

0 commit comments

Comments
 (0)