{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}

module Path.CheckInstall
  ( warnInstallSearchPathIssues
  ) where

import           Control.Monad.Extra ( anyM, (&&^) )
import qualified Data.Text as T
import           Stack.Prelude
import           Stack.Types.Config
import qualified System.Directory as D
import qualified System.FilePath as FP

-- | Checks if the installed executable will be available on the user's

-- PATH. This doesn't use @envSearchPath menv@ because it includes paths

-- only visible when running in the Stack environment.

warnInstallSearchPathIssues :: HasConfig env => FilePath -> [Text] -> RIO env ()
warnInstallSearchPathIssues :: forall env. HasConfig env => FilePath -> [Text] -> RIO env ()
warnInstallSearchPathIssues FilePath
destDir [Text]
installed = do
  [FilePath]
searchPath <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [FilePath]
FP.getSearchPath
  Bool
destDirIsInPATH <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *) a. Monad m => (a -> m Bool) -> [a] -> m Bool
anyM (\FilePath
dir -> FilePath -> IO Bool
D.doesDirectoryExist FilePath
dir forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
&&^ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> FilePath -> Bool
FP.equalFilePath FilePath
destDir) (FilePath -> IO FilePath
D.canonicalizePath FilePath
dir)) [FilePath]
searchPath
  if Bool
destDirIsInPATH
    then forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Text]
installed forall a b. (a -> b) -> a -> b
$ \Text
exe -> do
      Maybe FilePath
mexePath <- (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO (Maybe FilePath)
D.findExecutable forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack) Text
exe
      case Maybe FilePath
mexePath of
        Just FilePath
exePath -> do
          FilePath
exeDir <- (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> FilePath
FP.takeDirectory forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
D.canonicalizePath) FilePath
exePath
          forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FilePath
exeDir FilePath -> FilePath -> Bool
`FP.equalFilePath` FilePath
destDir) forall a b. (a -> b) -> a -> b
$ do
            forall env (m :: * -> *).
(HasCallStack, HasTerm env, MonadReader env m, MonadIO m) =>
[StyleDoc] -> m ()
prettyWarnL
              [ FilePath -> StyleDoc
flow FilePath
"The"
              , Style -> StyleDoc -> StyleDoc
style Style
File forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => FilePath -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack forall a b. (a -> b) -> a -> b
$ Text
exe
              , FilePath -> StyleDoc
flow FilePath
"executable found on the PATH environment variable is"
              , Style -> StyleDoc -> StyleDoc
style Style
File forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => FilePath -> a
fromString forall a b. (a -> b) -> a -> b
$ FilePath
exePath
              , FilePath -> StyleDoc
flow FilePath
"and not the version that was just installed."
              , FilePath -> StyleDoc
flow FilePath
"This means that"
              , Style -> StyleDoc -> StyleDoc
style Style
File forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => FilePath -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack forall a b. (a -> b) -> a -> b
$ Text
exe
              , StyleDoc
"calls on the command line will not use this version."
              ]
        Maybe FilePath
Nothing -> do
          forall env (m :: * -> *).
(HasCallStack, HasTerm env, MonadReader env m, MonadIO m) =>
[StyleDoc] -> m ()
prettyWarnL
            [ FilePath -> StyleDoc
flow FilePath
"Installation path"
            , Style -> StyleDoc -> StyleDoc
style Style
Dir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => FilePath -> a
fromString forall a b. (a -> b) -> a -> b
$ FilePath
destDir
            , FilePath -> StyleDoc
flow FilePath
"is on the PATH but the"
            , Style -> StyleDoc -> StyleDoc
style Style
File forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => FilePath -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack forall a b. (a -> b) -> a -> b
$ Text
exe
            , FilePath -> StyleDoc
flow FilePath
"executable that was just installed could not be found on the PATH."
            ]
    else do
      forall env (m :: * -> *).
(HasCallStack, HasTerm env, MonadReader env m, MonadIO m) =>
[StyleDoc] -> m ()
prettyWarnL
        [ FilePath -> StyleDoc
flow FilePath
"Installation path "
        , Style -> StyleDoc -> StyleDoc
style Style
Dir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => FilePath -> a
fromString forall a b. (a -> b) -> a -> b
$ FilePath
destDir
        , StyleDoc
"not found on the PATH environment variable."
        ]