Merge branch 'issue-329'

This commit is contained in:
Julian Ospald 2022-03-14 11:49:33 +01:00
commit c1e0baedd3
Signed by: hasufell
GPG Key ID: 3786C5262ECB4A3F
1 changed files with 101 additions and 63 deletions

View File

@ -35,7 +35,6 @@ import Prelude hiding ( appendFile )
import System.Directory import System.Directory
import System.FilePath import System.FilePath
import System.Environment import System.Environment
import System.IO.Temp
import System.Exit import System.Exit
import Text.PrettyPrint.HughesPJClass ( prettyShow ) import Text.PrettyPrint.HughesPJClass ( prettyShow )
@ -217,16 +216,20 @@ run :: forall m.
-> LeanAppState -> LeanAppState
-> (ReaderT LeanAppState m () -> m ()) -> (ReaderT LeanAppState m () -> m ())
-> m ExitCode -> m ExitCode
run RunOptions{..} runAppState leanAppstate runLogger = do run RunOptions{..} runAppState leanAppstate runLogger = runE @RunEffects ( do
toolchain <- Excepts resolveToolchain
tmp <- case runBinDir of tmp <- case runBinDir of
Just bdir -> do Just bindir -> do
liftIO $ createDirRecursive' bdir liftIO $ createDirRecursive' bindir
liftIO $ canonicalizePath bdir liftIO $ canonicalizePath bindir
Nothing -> liftIO (getTemporaryDirectory >>= \tmp -> createTempDirectory tmp "ghcup") Nothing -> do
r <- do d <- liftIO $ predictableTmpDir toolchain
addToolsToDir tmp liftIO $ createDirRecursive' d
case r of liftIO $ canonicalizePath d
VRight _ -> do Excepts $ installToolChain toolchain tmp
pure tmp
) >>= \case
VRight tmp -> do
case runCOMMAND of case runCOMMAND of
[] -> do [] -> do
liftIO $ putStr tmp liftIO $ putStr tmp
@ -253,70 +256,78 @@ run RunOptions{..} runAppState leanAppstate runLogger = do
isToolTag _ = False isToolTag _ = False
-- TODO: doesn't work for cross -- TODO: doesn't work for cross
addToolsToDir tmp resolveToolchain
| or (fmap (maybe False isToolTag) [runGHCVer, runCabalVer, runHLSVer, runStackVer]) || runInstTool' = runRUN runAppState $ do | or (fmap (maybe False isToolTag) [runGHCVer, runCabalVer, runHLSVer, runStackVer]) || runInstTool' = runRUN runAppState $ do
forM_ runGHCVer $ \ver -> do ghcVer <- forM runGHCVer $ \ver -> do
(v, _) <- liftE $ fromVersion (Just ver) GHC (v, _) <- liftE $ fromVersion (Just ver) GHC
installTool GHC v pure v
setTool GHC v tmp cabalVer <- forM runCabalVer $ \ver -> do
forM_ runCabalVer $ \ver -> do
(v, _) <- liftE $ fromVersion (Just ver) Cabal (v, _) <- liftE $ fromVersion (Just ver) Cabal
installTool Cabal v pure v
setTool Cabal v tmp hlsVer <- forM runHLSVer $ \ver -> do
forM_ runHLSVer $ \ver -> do
(v, _) <- liftE $ fromVersion (Just ver) HLS (v, _) <- liftE $ fromVersion (Just ver) HLS
installTool HLS v pure v
setTool HLS v tmp stackVer <- forM runStackVer $ \ver -> do
forM_ runStackVer $ \ver -> do
(v, _) <- liftE $ fromVersion (Just ver) Stack (v, _) <- liftE $ fromVersion (Just ver) Stack
installTool Stack v pure v
setTool Stack v tmp pure Toolchain{..}
| otherwise = runLeanRUN leanAppstate $ do | otherwise = runLeanRUN leanAppstate $ do
case runGHCVer of ghcVer <- case runGHCVer of
Just (ToolVersion v) -> Just (ToolVersion v) -> pure $ Just v
setTool GHC v tmp Nothing -> pure Nothing
Nothing -> pure ()
_ -> fail "Internal error" _ -> fail "Internal error"
case runCabalVer of cabalVer <- case runCabalVer of
Just (ToolVersion v) -> Just (ToolVersion v) -> pure $ Just v
setTool Cabal v tmp Nothing -> pure Nothing
Nothing -> pure ()
_ -> fail "Internal error" _ -> fail "Internal error"
case runHLSVer of hlsVer <- case runHLSVer of
Just (ToolVersion v) -> Just (ToolVersion v) -> pure $ Just v
setTool HLS v tmp Nothing -> pure Nothing
Nothing -> pure ()
_ -> fail "Internal error" _ -> fail "Internal error"
case runStackVer of stackVer <- case runStackVer of
Just (ToolVersion v) -> Just (ToolVersion v) -> pure $ Just v
setTool Stack v tmp Nothing -> pure Nothing
Nothing -> pure ()
_ -> fail "Internal error" _ -> fail "Internal error"
pure Toolchain{..}
installTool tool v = do installToolChain Toolchain{..} tmp
isInstalled <- checkIfToolInstalled' tool v | or (fmap (maybe False isToolTag) [runGHCVer, runCabalVer, runHLSVer, runStackVer]) || runInstTool' = runRUN runAppState $ do
case tool of forM_ [(GHC,) <$> ghcVer, (Cabal,) <$> cabalVer, (HLS,) <$> hlsVer, (Stack,) <$> stackVer] $ \mt -> do
GHC -> do isInstalled <- maybe (pure False) (\(tool, v) -> lift $ checkIfToolInstalled' tool v) mt
unless isInstalled $ when (runInstTool' && isNothing (_tvTarget v)) $ void $ liftE $ installGHCBin case mt of
(_tvVersion v) Just (GHC, v) -> do
Nothing unless isInstalled $ when (runInstTool' && isNothing (_tvTarget v)) $ void $ liftE $ installGHCBin
False (_tvVersion v)
Cabal -> do Nothing
unless isInstalled $ when runInstTool' $ void $ liftE $ installCabalBin False
(_tvVersion v) setTool GHC v tmp
Nothing Just (Cabal, v) -> do
False unless isInstalled $ when runInstTool' $ void $ liftE $ installCabalBin
Stack -> do (_tvVersion v)
unless isInstalled $ when runInstTool' $ void $ liftE $ installStackBin Nothing
(_tvVersion v) False
Nothing setTool Cabal v tmp
False Just (Stack, v) -> do
HLS -> do unless isInstalled $ when runInstTool' $ void $ liftE $ installStackBin
unless isInstalled $ when runInstTool' $ void $ liftE $ installHLSBin (_tvVersion v)
(_tvVersion v) Nothing
Nothing False
False setTool Stack v tmp
GHCup -> pure () Just (HLS, v) -> do
unless isInstalled $ when runInstTool' $ void $ liftE $ installHLSBin
(_tvVersion v)
Nothing
False
setTool HLS v tmp
_ -> pure ()
| otherwise = runLeanRUN leanAppstate $ do
forM_ [(GHC,) <$> ghcVer, (Cabal,) <$> cabalVer, (HLS,) <$> hlsVer, (Stack,) <$> stackVer] $ \mt -> do
case mt of
Just (GHC, v) -> setTool GHC v tmp
Just (Cabal, v) -> setTool Cabal v tmp
Just (Stack, v) -> setTool Stack v tmp
Just (HLS, v) -> setTool HLS v tmp
_ -> pure ()
setTool tool v tmp = setTool tool v tmp =
case tool of case tool of
@ -360,3 +371,30 @@ run RunOptions{..} runAppState leanAppstate runLogger = do
envWithNewPath = Map.toList $ Map.insert pathVar newPath envWithoutPath envWithNewPath = Map.toList $ Map.insert pathVar newPath envWithoutPath
liftIO $ setEnv pathVar newPath liftIO $ setEnv pathVar newPath
return envWithNewPath return envWithNewPath
predictableTmpDir (Toolchain Nothing Nothing Nothing Nothing) =
liftIO (getTemporaryDirectory >>= \tmp -> pure (tmp </> "ghcup-none"))
predictableTmpDir Toolchain{..} = do
tmp <- getTemporaryDirectory
pure $ tmp
</> ("ghcup"
<> maybe "" (("_ghc-" <>) . T.unpack . tVerToText) ghcVer
<> maybe "" (("_cabal-" <>) . T.unpack . tVerToText) cabalVer
<> maybe "" (("_hls-" <>) . T.unpack . tVerToText) hlsVer
<> maybe "" (("_stack-" <>) . T.unpack . tVerToText) stackVer
)
-------------------------
--[ Other local types ]--
-------------------------
data Toolchain = Toolchain
{ ghcVer :: Maybe GHCTargetVersion
, cabalVer :: Maybe GHCTargetVersion
, hlsVer :: Maybe GHCTargetVersion
, stackVer :: Maybe GHCTargetVersion
}