2022-02-09 17:57:59 +00:00
{- # LANGUAGE CPP # -}
{- # LANGUAGE QuasiQuotes # -}
{- # LANGUAGE TypeApplications # -}
{- # LANGUAGE DataKinds # -}
{- # LANGUAGE RankNTypes # -}
{- # LANGUAGE FlexibleContexts # -}
{- # LANGUAGE TypeFamilies # -}
2022-07-11 13:09:25 +00:00
{- # LANGUAGE ViewPatterns # -}
2022-02-09 17:57:59 +00:00
module GHCup.OptParse.Run where
import GHCup
import GHCup.Utils
import GHCup.OptParse.Common
import GHCup.Errors
import GHCup.Types
2022-03-17 23:42:48 +00:00
import GHCup.Types.Optics
2022-05-21 20:54:18 +00:00
import GHCup.Prelude
import GHCup.Prelude.File
# ifdef IS_WINDOWS
import GHCup.Prelude.Process
2022-06-06 21:02:21 +00:00
import GHCup.Prelude.Process.Windows ( execNoMinGW )
2022-05-21 20:54:18 +00:00
# endif
import GHCup.Prelude.Logger
import GHCup.Prelude.String.QQ
2022-02-09 17:57:59 +00:00
import Control.Exception.Safe ( MonadMask , MonadCatch )
# if ! MIN_VERSION_base ( 4 , 13 , 0 )
import Control.Monad.Fail ( MonadFail )
# endif
import Codec.Archive
import Control.Monad.Reader
import Control.Monad.Trans.Resource
import Data.Functor
import Data.Maybe ( isNothing )
import Data.List ( intercalate )
import Haskus.Utils.Variant.Excepts
import Options.Applicative hiding ( style )
import Prelude hiding ( appendFile )
import System.FilePath
import System.Environment
import System.Exit
import Text.PrettyPrint.HughesPJClass ( prettyShow )
import qualified Data.Map.Strict as Map
import qualified Data.Text as T
# ifndef IS_WINDOWS
import qualified System.Posix.Process as SPP
# endif
2022-07-11 14:05:39 +00:00
import Data.Versions ( prettyVer , Version )
2022-02-09 17:57:59 +00:00
---------------
--[ Options ]--
---------------
data RunOptions = RunOptions
{ runAppendPATH :: Bool
, runInstTool' :: Bool
2022-06-06 21:02:21 +00:00
, runMinGWPath :: Bool
2022-02-09 17:57:59 +00:00
, runGHCVer :: Maybe ToolVersion
, runCabalVer :: Maybe ToolVersion
, runHLSVer :: Maybe ToolVersion
, runStackVer :: Maybe ToolVersion
, runBinDir :: Maybe FilePath
2022-05-11 18:11:35 +00:00
, runQuick :: Bool
2022-02-09 17:57:59 +00:00
, runCOMMAND :: [ String ]
}
---------------
--[ Parsers ]--
---------------
2022-05-11 18:11:35 +00:00
2022-02-09 17:57:59 +00:00
runOpts :: Parser RunOptions
runOpts =
RunOptions
<$> switch
( short 'a' <> long " append " <> help " Append bin/ dir to PATH instead of prepending (this means that e.g. a system installation may take precedence) " )
<*> switch
( short 'i' <> long " install " <> help " Install the tool, if missing " )
2022-06-06 21:02:21 +00:00
<*> switch
( short 'm' <> long " mingw-path " <> help " On windows, add mingw64 PATHs to environment (does nothing on unix) " )
2022-02-09 17:57:59 +00:00
<*> optional
( option
2022-07-11 14:05:39 +00:00
( eitherReader ghcVersionTagEither )
2022-03-04 23:46:37 +00:00
( metavar " GHC_VERSION " <> long " ghc " <> help " The ghc version "
<> completer ( tagCompleter GHC [] )
<> ( completer $ versionCompleter Nothing GHC )
)
2022-02-09 17:57:59 +00:00
)
<*> optional
( option
2022-07-11 14:05:39 +00:00
( eitherReader toolVersionTagEither )
2022-03-04 23:46:37 +00:00
( metavar " CABAL_VERSION " <> long " cabal " <> help " The cabal version "
<> completer ( tagCompleter Cabal [] )
<> ( completer $ versionCompleter Nothing Cabal )
)
2022-02-09 17:57:59 +00:00
)
<*> optional
( option
2022-07-11 14:05:39 +00:00
( eitherReader toolVersionTagEither )
2022-03-04 23:46:37 +00:00
( metavar " HLS_VERSION " <> long " hls " <> help " The HLS version "
<> completer ( tagCompleter HLS [] )
<> ( completer $ versionCompleter Nothing HLS )
)
2022-02-09 17:57:59 +00:00
)
<*> optional
( option
2022-07-11 14:05:39 +00:00
( eitherReader toolVersionTagEither )
2022-03-04 23:46:37 +00:00
( metavar " STACK_VERSION " <> long " stack " <> help " The stack version "
<> completer ( tagCompleter Stack [] )
<> ( completer $ versionCompleter Nothing Stack )
)
2022-02-09 17:57:59 +00:00
)
<*> optional
( option
( eitherReader isolateParser )
( short 'b'
<> long " bindir "
<> metavar " DIR "
<> help " directory where to create the tool symlinks (default: newly created system temp dir) "
2022-03-04 23:46:37 +00:00
<> completer ( bashCompleter " directory " )
2022-02-09 17:57:59 +00:00
)
)
2022-05-11 18:11:35 +00:00
<*> switch
( short 'q' <> long " quick " <> help " Avoid any expensive work (such as downloads, version/tag resolution etc.). Disables --install. " )
2022-02-09 17:57:59 +00:00
<*> many ( argument str ( metavar " COMMAND " <> help " The command to run, with arguments (use longopts --). If omitted, just prints the created bin/ dir to stdout and exits. " ) )
--------------
--[ Footer ]--
--------------
runFooter :: String
runFooter = [ s | Discussion :
Adds the given tools to a dedicated bin / directory and adds them to PATH , exposing
the relevant binaries , then executes a command .
Examples :
# run VSCode with all latest toolchain exposed , installing missing versions if necessary
ghcup run --ghc latest --cabal latest --hls latest --stack latest --install -- code Setup.hs
# create a custom toolchain bin / dir with GHC and cabal that can be manually added to PATH
ghcup run --ghc 8.10.7 --cabal 3.2.0.0 --bindir $HOME/toolchain/bin
# run a specific ghc version
ghcup run --ghc 8.10.7 -- ghc --version|]
---------------------------
--[ Effect interpreters ]--
---------------------------
type RunEffects = ' [ A l r e a d y I n s t a l l e d
, UnknownArchive
, ArchiveResult
, FileDoesNotExistError
, CopyError
, NotInstalled
, DirNotEmpty
, NoDownload
, NotInstalled
, BuildFailed
, TagNotFound
, DigestError
, GPGError
, DownloadFailed
, TarDirDoesNotExist
, NextVerNotFound
, NoToolVersionSet
, FileAlreadyExistsError
, ProcessError
2022-05-12 15:58:40 +00:00
, UninstallFailed
2022-05-19 21:17:58 +00:00
, MergeFileTreeError
2022-02-09 17:57:59 +00:00
]
2022-02-10 18:29:32 +00:00
runLeanRUN :: ( MonadUnliftIO m , MonadIO m )
=> LeanAppState
-> Excepts RunEffects ( ReaderT LeanAppState m ) a
-> m ( VEither RunEffects a )
runLeanRUN leanAppstate =
-- Don't use runLeanAppState here, which is disabled on windows.
-- This is the only command on all platforms that doesn't need full appstate.
flip runReaderT leanAppstate
. runE
@ RunEffects
2022-02-09 17:57:59 +00:00
runRUN :: MonadUnliftIO m
2022-03-17 23:42:48 +00:00
=> IO AppState
2022-02-09 17:57:59 +00:00
-> Excepts RunEffects ( ResourceT ( ReaderT AppState m ) ) a
-> m ( VEither RunEffects a )
2022-03-17 23:42:48 +00:00
runRUN appState action' = do
s' <- liftIO appState
flip runReaderT s'
2022-02-09 17:57:59 +00:00
. runResourceT
. runE
@ RunEffects
2022-03-17 23:42:48 +00:00
$ action'
2022-02-09 17:57:59 +00:00
------------------
--[ Entrypoint ]--
------------------
2022-07-11 14:05:39 +00:00
run :: forall m .
2022-02-09 17:57:59 +00:00
( MonadFail m
, MonadMask m
, MonadCatch m
, MonadIO m
, MonadUnliftIO m
)
=> RunOptions
2022-03-17 23:42:48 +00:00
-> IO AppState
2022-02-10 18:29:32 +00:00
-> LeanAppState
2022-02-09 17:57:59 +00:00
-> ( ReaderT LeanAppState m () -> m () )
-> m ExitCode
2022-03-17 23:42:48 +00:00
run RunOptions { .. } runAppState leanAppstate runLogger = do
2022-05-11 18:11:35 +00:00
r <- if not runQuick
2022-03-17 23:42:48 +00:00
then runRUN runAppState $ do
toolchain <- liftE resolveToolchainFull
2022-07-11 13:09:25 +00:00
-- oh dear
r <- lift ask
tmp <- lift . lift . lift . flip runReaderT ( fromAppState r ) $ createTmpDir toolchain
2022-03-17 23:42:48 +00:00
liftE $ installToolChainFull toolchain tmp
pure tmp
else runLeanRUN leanAppstate $ do
toolchain <- resolveToolchain
2022-07-11 13:09:25 +00:00
tmp <- lift $ createTmpDir toolchain
2022-03-17 23:42:48 +00:00
liftE $ installToolChain toolchain tmp
pure tmp
case r of
VRight tmp -> do
case runCOMMAND of
[] -> do
liftIO $ putStr tmp
pure ExitSuccess
( cmd : args ) -> do
newEnv <- liftIO $ addToPath tmp
2022-02-10 17:35:25 +00:00
# ifndef IS_WINDOWS
2022-03-17 23:42:48 +00:00
void $ liftIO $ SPP . executeFile cmd True args ( Just newEnv )
pure ExitSuccess
2022-02-10 17:35:25 +00:00
# else
2022-06-06 21:02:21 +00:00
r' <- if runMinGWPath
then runLeanRUN leanAppstate $ liftE $ lEM @ _ @ '[ProcessError] $ exec cmd args Nothing ( Just newEnv )
else runLeanRUN leanAppstate $ liftE $ lEM @ _ @ '[ProcessError] $ execNoMinGW cmd args Nothing ( Just newEnv )
2022-03-17 23:42:48 +00:00
case r' of
VRight _ -> pure ExitSuccess
VLeft e -> do
runLogger $ logError $ T . pack $ prettyShow e
pure $ ExitFailure 28
2022-02-10 17:35:25 +00:00
# endif
2022-03-17 23:42:48 +00:00
VLeft e -> do
runLogger $ logError $ T . pack $ prettyShow e
pure $ ExitFailure 27
2022-02-09 17:57:59 +00:00
where
2022-03-17 23:42:48 +00:00
2022-02-09 17:57:59 +00:00
-- TODO: doesn't work for cross
2022-03-17 23:42:48 +00:00
resolveToolchainFull :: ( MonadFail m
, MonadThrow m
, MonadIO m
, MonadCatch m
)
=> Excepts
' [ T a g N o t F o u n d
, NextVerNotFound
, NoToolVersionSet
] ( ResourceT ( ReaderT AppState m ) ) Toolchain
resolveToolchainFull = do
2022-03-13 22:49:53 +00:00
ghcVer <- forM runGHCVer $ \ ver -> do
2022-02-10 18:29:32 +00:00
( v , _ ) <- liftE $ fromVersion ( Just ver ) GHC
2022-03-13 22:49:53 +00:00
pure v
cabalVer <- forM runCabalVer $ \ ver -> do
2022-02-10 18:29:32 +00:00
( v , _ ) <- liftE $ fromVersion ( Just ver ) Cabal
2022-07-11 14:05:39 +00:00
pure ( _tvVersion v )
2022-03-13 22:49:53 +00:00
hlsVer <- forM runHLSVer $ \ ver -> do
2022-02-10 18:29:32 +00:00
( v , _ ) <- liftE $ fromVersion ( Just ver ) HLS
2022-07-11 14:05:39 +00:00
pure ( _tvVersion v )
2022-03-13 22:49:53 +00:00
stackVer <- forM runStackVer $ \ ver -> do
2022-02-10 18:29:32 +00:00
( v , _ ) <- liftE $ fromVersion ( Just ver ) Stack
2022-07-11 14:05:39 +00:00
pure ( _tvVersion v )
2022-03-13 22:49:53 +00:00
pure Toolchain { .. }
2022-03-17 23:42:48 +00:00
resolveToolchain = do
2022-03-13 22:49:53 +00:00
ghcVer <- case runGHCVer of
2022-07-11 14:05:39 +00:00
Just ( GHCVersion v ) -> pure $ Just v
Just ( ToolVersion v ) -> pure $ Just ( mkTVer v )
2022-03-13 22:49:53 +00:00
Nothing -> pure Nothing
2022-02-10 18:29:32 +00:00
_ -> fail " Internal error "
2022-03-13 22:49:53 +00:00
cabalVer <- case runCabalVer of
2022-07-11 14:05:39 +00:00
Just ( GHCVersion v ) -> pure $ Just ( _tvVersion v )
2022-03-13 22:49:53 +00:00
Just ( ToolVersion v ) -> pure $ Just v
Nothing -> pure Nothing
2022-02-10 18:29:32 +00:00
_ -> fail " Internal error "
2022-03-13 22:49:53 +00:00
hlsVer <- case runHLSVer of
2022-07-11 14:05:39 +00:00
Just ( GHCVersion v ) -> pure $ Just ( _tvVersion v )
2022-03-13 22:49:53 +00:00
Just ( ToolVersion v ) -> pure $ Just v
Nothing -> pure Nothing
2022-02-10 18:29:32 +00:00
_ -> fail " Internal error "
2022-03-13 22:49:53 +00:00
stackVer <- case runStackVer of
2022-07-11 14:05:39 +00:00
Just ( GHCVersion v ) -> pure $ Just ( _tvVersion v )
2022-03-13 22:49:53 +00:00
Just ( ToolVersion v ) -> pure $ Just v
Nothing -> pure Nothing
2022-02-10 18:29:32 +00:00
_ -> fail " Internal error "
2022-03-13 22:49:53 +00:00
pure Toolchain { .. }
2022-02-10 18:29:32 +00:00
2022-03-17 23:42:48 +00:00
installToolChainFull :: ( MonadFail m
, MonadThrow m
, MonadIO m
, MonadCatch m
)
=> Toolchain
-> FilePath
-> Excepts
' [ T a g N o t F o u n d
, NextVerNotFound
, NoToolVersionSet
, UnknownArchive
, TarDirDoesNotExist
, ProcessError
, NotInstalled
, NoDownload
, GPGError
, DownloadFailed
, DirNotEmpty
, DigestError
, BuildFailed
, ArchiveResult
, AlreadyInstalled
, FileAlreadyExistsError
, CopyError
2022-05-12 15:58:40 +00:00
, UninstallFailed
2022-05-19 21:17:58 +00:00
, MergeFileTreeError
2022-03-17 23:42:48 +00:00
] ( ResourceT ( ReaderT AppState m ) ) ()
installToolChainFull Toolchain { .. } tmp = do
2022-07-11 14:05:39 +00:00
case ghcVer of
Just v -> do
isInstalled <- lift $ checkIfToolInstalled' GHC v
unless isInstalled $ when ( runInstTool' && isNothing ( _tvTarget v ) ) $ void $ liftE $ installGHCBin
( _tvVersion v )
GHCupInternal
False
[]
setGHC' v tmp
_ -> pure ()
case cabalVer of
Just v -> do
isInstalled <- lift $ checkIfToolInstalled' Cabal ( mkTVer v )
unless isInstalled $ when runInstTool' $ void $ liftE $ installCabalBin
v
GHCupInternal
False
setCabal' v tmp
_ -> pure ()
case stackVer of
Just v -> do
isInstalled <- lift $ checkIfToolInstalled' Stack ( mkTVer v )
unless isInstalled $ when runInstTool' $ void $ liftE $ installStackBin
v
GHCupInternal
False
setStack' v tmp
_ -> pure ()
case hlsVer of
Just v -> do
isInstalled <- lift $ checkIfToolInstalled' HLS ( mkTVer v )
unless isInstalled $ when runInstTool' $ void $ liftE $ installHLSBin
v
GHCupInternal
False
setHLS' v tmp
_ -> pure ()
2022-03-17 23:42:48 +00:00
installToolChain :: ( MonadFail m
, MonadThrow m
, MonadIO m
, MonadCatch m
)
=> Toolchain
-> FilePath
-> Excepts '[NotInstalled] ( ReaderT LeanAppState m ) ()
installToolChain Toolchain { .. } tmp = do
2022-07-11 14:05:39 +00:00
case ghcVer of
Just v -> setGHC' v tmp
_ -> pure ()
case cabalVer of
Just v -> setCabal' v tmp
_ -> pure ()
case stackVer of
Just v -> setStack' v tmp
_ -> pure ()
case hlsVer of
Just v -> setHLS' v tmp
_ -> pure ()
setGHC' v tmp = do
2022-02-10 18:29:32 +00:00
void $ liftE $ setGHC v SetGHC_XYZ ( Just tmp )
void $ liftE $ setGHC v SetGHCOnly ( Just tmp )
2022-07-11 14:05:39 +00:00
setCabal' v tmp = do
bin <- liftE $ whereIsTool Cabal ( mkTVer v )
2022-02-10 18:29:32 +00:00
cbin <- liftIO $ canonicalizePath bin
2022-02-10 20:49:19 +00:00
lift $ createLink ( relativeSymlink tmp cbin ) ( tmp </> ( " cabal " <.> exeExt ) )
2022-07-11 14:05:39 +00:00
setStack' v tmp = do
bin <- liftE $ whereIsTool Stack ( mkTVer v )
2022-02-10 18:29:32 +00:00
cbin <- liftIO $ canonicalizePath bin
2022-02-10 20:49:19 +00:00
lift $ createLink ( relativeSymlink tmp cbin ) ( tmp </> ( " stack " <.> exeExt ) )
2022-07-11 14:05:39 +00:00
setHLS' v tmp = do
2022-02-10 19:35:09 +00:00
Dirs { .. } <- getDirs
2022-07-11 14:05:39 +00:00
legacy <- isLegacyHLS v
2022-02-10 19:35:09 +00:00
if legacy
then do
-- TODO: factor this out
2022-07-11 14:05:39 +00:00
hlsWrapper <- liftE @ _ @ '[NotInstalled] $ hlsWrapperBinary v !? ( NotInstalled HLS ( mkTVer v ) )
2022-02-10 19:35:09 +00:00
cw <- liftIO $ canonicalizePath ( binDir </> hlsWrapper )
lift $ createLink ( relativeSymlink tmp cw ) ( tmp </> takeFileName cw )
2022-07-11 14:05:39 +00:00
hlsBins <- hlsServerBinaries v Nothing >>= liftIO . traverse ( canonicalizePath . ( binDir </> ) )
2022-02-10 19:35:09 +00:00
forM_ hlsBins $ \ bin ->
lift $ createLink ( relativeSymlink tmp bin ) ( tmp </> takeFileName bin )
2022-07-11 14:05:39 +00:00
liftE $ setHLS v SetHLSOnly ( Just tmp )
2022-02-10 19:35:09 +00:00
else do
2022-07-11 14:05:39 +00:00
liftE $ setHLS v SetHLS_XYZ ( Just tmp )
liftE $ setHLS v SetHLSOnly ( Just tmp )
2022-02-09 17:57:59 +00:00
addToPath path = do
cEnv <- Map . fromList <$> getEnvironment
let paths = [ " PATH " , " Path " ]
curPaths = ( \ x -> maybe [] splitSearchPath ( Map . lookup x cEnv ) ) =<< paths
newPath = intercalate [ searchPathSeparator ] ( if runAppendPATH then ( curPaths ++ [ path ] ) else ( path : curPaths ) )
envWithoutPath = foldr ( \ x y -> Map . delete x y ) cEnv paths
pathVar = if isWindows then " Path " else " PATH "
envWithNewPath = Map . toList $ Map . insert pathVar newPath envWithoutPath
liftIO $ setEnv pathVar newPath
return envWithNewPath
2022-03-13 22:49:53 +00:00
2022-07-11 13:09:25 +00:00
createTmpDir :: ( MonadUnliftIO m
, MonadCatch m
, MonadThrow m
, MonadMask m
, MonadIO m
)
=> Toolchain
-> ReaderT LeanAppState m FilePath
createTmpDir toolchain =
case runBinDir of
Just bindir -> do
liftIO $ createDirRecursive' bindir
liftIO $ canonicalizePath bindir
Nothing -> do
d <- predictableTmpDir toolchain
liftIO $ createDirRecursive' d
liftIO $ canonicalizePath d
predictableTmpDir :: Monad m
=> Toolchain
-> ReaderT LeanAppState m FilePath
predictableTmpDir ( Toolchain Nothing Nothing Nothing Nothing ) = do
Dirs { tmpDir } <- getDirs
pure ( fromGHCupPath tmpDir </> " ghcup-none " )
2022-03-13 22:49:53 +00:00
predictableTmpDir Toolchain { .. } = do
2022-07-11 13:09:25 +00:00
Dirs { tmpDir } <- getDirs
pure $ fromGHCupPath tmpDir
2022-03-16 22:15:09 +00:00
</> ( " ghcup- " <> intercalate " _ "
( maybe [] ( ( : [] ) . ( " ghc- " <> ) . T . unpack . tVerToText ) ghcVer
2022-07-11 14:05:39 +00:00
<> maybe [] ( ( : [] ) . ( " cabal- " <> ) . T . unpack . prettyVer ) cabalVer
<> maybe [] ( ( : [] ) . ( " hls- " <> ) . T . unpack . prettyVer ) hlsVer
<> maybe [] ( ( : [] ) . ( " stack- " <> ) . T . unpack . prettyVer ) stackVer
2022-03-16 22:15:09 +00:00
)
2022-03-13 22:49:53 +00:00
)
-------------------------
--[ Other local types ]--
-------------------------
data Toolchain = Toolchain
{ ghcVer :: Maybe GHCTargetVersion
2022-07-11 14:05:39 +00:00
, cabalVer :: Maybe Version
, hlsVer :: Maybe Version
, stackVer :: Maybe Version
2022-07-11 13:09:25 +00:00
} deriving Show