Avoid metadata download when possible

This commit is contained in:
Julian Ospald 2022-02-10 19:29:32 +01:00
parent 09a8a0bda0
commit 5186d959bc
Signed by: hasufell
GPG Key ID: 3786C5262ECB4A3F
2 changed files with 114 additions and 59 deletions

View File

@ -161,6 +161,16 @@ type RunEffects = '[ AlreadyInstalled
, ProcessError , ProcessError
] ]
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
runRUN :: MonadUnliftIO m runRUN :: MonadUnliftIO m
=> (ReaderT AppState m (VEither RunEffects a) -> m (VEither RunEffects a)) => (ReaderT AppState m (VEither RunEffects a) -> m (VEither RunEffects a))
@ -189,75 +199,120 @@ run :: forall m.
) )
=> RunOptions => RunOptions
-> (forall a. ReaderT AppState m (VEither RunEffects a) -> m (VEither RunEffects a)) -> (forall a. ReaderT AppState m (VEither RunEffects a) -> m (VEither RunEffects a))
-> LeanAppState
-> (ReaderT LeanAppState m () -> m ()) -> (ReaderT LeanAppState m () -> m ())
-> m ExitCode -> m ExitCode
run RunOptions{..} runAppState runLogger = runRUN runAppState (do run RunOptions{..} runAppState leanAppstate runLogger = do
tmp <- case runBinDir of tmp <- case runBinDir of
Just bdir -> do Just bdir -> do
liftIO $ createDirRecursive' bdir liftIO $ createDirRecursive' bdir
liftIO $ canonicalizePath bdir liftIO $ canonicalizePath bdir
Nothing -> liftIO (getTemporaryDirectory >>= \tmp -> createTempDirectory tmp "ghcup") Nothing -> liftIO (getTemporaryDirectory >>= \tmp -> createTempDirectory tmp "ghcup")
forM_ runGHCVer $ addToolToDir tmp GHC r <- addToolsToDir tmp
forM_ runCabalVer $ addToolToDir tmp Cabal case r of
forM_ runHLSVer $ addToolToDir tmp HLS VRight _ -> do
forM_ runStackVer $ addToolToDir tmp Stack case runCOMMAND of
case runCOMMAND of [] -> liftIO $ putStr tmp
[] -> liftIO $ putStr tmp (cmd:args) -> do
(cmd:args) -> do newEnv <- liftIO $ addToPath tmp
newEnv <- liftIO $ addToPath tmp
#ifndef IS_WINDOWS #ifndef IS_WINDOWS
liftIO $ SPP.executeFile cmd True args (Just newEnv) liftIO $ SPP.executeFile cmd True args (Just newEnv)
#else #else
liftE $ lEM @_ @'[ProcessError] $ exec cmd args Nothing (Just newEnv) liftE $ lEM @_ @'[ProcessError] $ exec cmd args Nothing (Just newEnv)
#endif #endif
pure () pure ExitSuccess
) >>= \case VLeft e -> do
VRight _ -> do runLogger $ logError $ T.pack $ prettyShow e
pure ExitSuccess pure $ ExitFailure 27
VLeft e -> do
runLogger $ logError $ T.pack $ prettyShow e
pure $ ExitFailure 27
where where
isToolTag :: ToolVersion -> Bool
isToolTag (ToolTag _) = True
isToolTag _ = False
-- TODO: doesn't work for cross -- TODO: doesn't work for cross
addToolToDir tmp tool ver = do addToolsToDir tmp
(v, _) <- liftE $ fromVersion (Just ver) tool | or (fmap (maybe False isToolTag) [runGHCVer, runCabalVer, runHLSVer, runStackVer]) || runInstTool' = runRUN runAppState $ do
isInstalled <- checkIfToolInstalled' tool v forM_ runGHCVer $ \ver -> do
case tool of (v, _) <- liftE $ fromVersion (Just ver) GHC
GHC -> do installTool GHC v
unless isInstalled $ when (runInstTool' && isNothing (_tvTarget v)) $ void $ liftE $ installGHCBin setTool GHC v tmp
(_tvVersion v) forM_ runCabalVer $ \ver -> do
Nothing (v, _) <- liftE $ fromVersion (Just ver) Cabal
False installTool Cabal v
void $ liftE $ setGHC v SetGHC_XYZ (Just tmp) setTool Cabal v tmp
void $ liftE $ setGHC v SetGHCOnly (Just tmp) forM_ runHLSVer $ \ver -> do
pure () (v, _) <- liftE $ fromVersion (Just ver) HLS
Cabal -> do installTool HLS v
unless isInstalled $ when runInstTool' $ void $ liftE $ installCabalBin setTool HLS v tmp
(_tvVersion v) forM_ runStackVer $ \ver -> do
Nothing (v, _) <- liftE $ fromVersion (Just ver) Stack
False installTool Stack v
bin <- liftE $ whereIsTool Cabal v setTool Stack v tmp
cbin <- liftIO $ canonicalizePath bin | otherwise = runLeanRUN leanAppstate $ do
lift $ createLink (relativeSymlink tmp cbin) (tmp </> "cabal") case runGHCVer of
pure () Just (ToolVersion v) ->
Stack -> do setTool GHC v tmp
unless isInstalled $ when runInstTool' $ void $ liftE $ installStackBin Nothing -> pure ()
(_tvVersion v) _ -> fail "Internal error"
Nothing case runCabalVer of
False Just (ToolVersion v) ->
bin <- liftE $ whereIsTool Stack v setTool Cabal v tmp
cbin <- liftIO $ canonicalizePath bin Nothing -> pure ()
lift $ createLink (relativeSymlink tmp cbin) (tmp </> "stack") _ -> fail "Internal error"
pure () case runHLSVer of
HLS -> do Just (ToolVersion v) ->
unless isInstalled $ when runInstTool' $ void $ liftE $ installHLSBin setTool HLS v tmp
(_tvVersion v) Nothing -> pure ()
Nothing _ -> fail "Internal error"
False case runStackVer of
liftE $ setHLS (_tvVersion v) SetHLS_XYZ (Just tmp) Just (ToolVersion v) ->
liftE $ setHLS (_tvVersion v) SetHLSOnly (Just tmp) setTool Stack v tmp
pure () Nothing -> pure ()
GHCup -> pure () _ -> fail "Internal error"
installTool tool v = do
isInstalled <- checkIfToolInstalled' tool v
case tool of
GHC -> do
unless isInstalled $ when (runInstTool' && isNothing (_tvTarget v)) $ void $ liftE $ installGHCBin
(_tvVersion v)
Nothing
False
Cabal -> do
unless isInstalled $ when runInstTool' $ void $ liftE $ installCabalBin
(_tvVersion v)
Nothing
False
Stack -> do
unless isInstalled $ when runInstTool' $ void $ liftE $ installStackBin
(_tvVersion v)
Nothing
False
HLS -> do
unless isInstalled $ when runInstTool' $ void $ liftE $ installHLSBin
(_tvVersion v)
Nothing
False
GHCup -> pure ()
setTool tool v tmp =
case tool of
GHC -> do
void $ liftE $ setGHC v SetGHC_XYZ (Just tmp)
void $ liftE $ setGHC v SetGHCOnly (Just tmp)
Cabal -> do
bin <- liftE $ whereIsTool Cabal v
cbin <- liftIO $ canonicalizePath bin
lift $ createLink (relativeSymlink tmp cbin) (tmp </> "cabal")
Stack -> do
bin <- liftE $ whereIsTool Stack v
cbin <- liftIO $ canonicalizePath bin
lift $ createLink (relativeSymlink tmp cbin) (tmp </> "stack")
HLS -> do
liftE $ setHLS (_tvVersion v) SetHLS_XYZ (Just tmp)
liftE $ setHLS (_tvVersion v) SetHLSOnly (Just tmp)
GHCup -> pure ()
addToPath path = do addToPath path = do
cEnv <- Map.fromList <$> getEnvironment cEnv <- Map.fromList <$> getEnvironment
let paths = ["PATH", "Path"] let paths = ["PATH", "Path"]

View File

@ -313,7 +313,7 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
Nuke -> nuke appState runLogger Nuke -> nuke appState runLogger
Prefetch pfCom -> prefetch pfCom runAppState runLogger Prefetch pfCom -> prefetch pfCom runAppState runLogger
GC gcOpts -> gc gcOpts runAppState runLogger GC gcOpts -> gc gcOpts runAppState runLogger
Run runCommand -> run runCommand runAppState runLogger Run runCommand -> run runCommand runAppState leanAppstate runLogger
case res of case res of
ExitSuccess -> pure () ExitSuccess -> pure ()