Compare commits

..

1 Commits

Author SHA1 Message Date
8f7d937e26 Use predictable /tmp names for ghcup run, fixes #329 2022-03-14 00:38:57 +01:00
6 changed files with 160 additions and 88 deletions

View File

@@ -113,8 +113,8 @@ data Command
opts :: Parser Options opts :: Parser Options
opts = opts =
Options Options
<$> invertableSwitch "verbose" (Just 'v') False (help "Enable verbosity (default: disabled)") <$> invertableSwitch "verbose" 'v' False (help "Enable verbosity (default: disabled)")
<*> invertableSwitch "cache" (Just 'c') False (help "Cache downloads in ~/.ghcup/cache (default: disabled)") <*> invertableSwitch "cache" 'c' False (help "Cache downloads in ~/.ghcup/cache (default: disabled)")
<*> optional (option auto (long "metadata-caching" <> help "How long the yaml metadata caching interval is (in seconds), 0 to disable" <> internal)) <*> optional (option auto (long "metadata-caching" <> help "How long the yaml metadata caching interval is (in seconds), 0 to disable" <> internal))
<*> optional <*> optional
(option (option
@@ -127,7 +127,7 @@ opts =
<> completer fileUri <> completer fileUri
) )
) )
<*> (fmap . fmap) not (invertableSwitch "verify" (Just 'n') True (help "Disable tarball checksum verification (default: enabled)")) <*> (fmap . fmap) not (invertableSwitch "verify" 'n' True (help "Disable tarball checksum verification (default: enabled)"))
<*> optional (option <*> optional (option
(eitherReader keepOnParser) (eitherReader keepOnParser)
( long "keep" ( long "keep"
@@ -153,7 +153,7 @@ opts =
#endif #endif
<> hidden <> hidden
)) ))
<*> invertableSwitch "offline" (Just 'o') False (help "Don't do any network calls, trying cached assets and failing if missing.") <*> invertableSwitch "offline" 'o' False (help "Don't do any network calls, trying cached assets and failing if missing.")
<*> optional (option <*> optional (option
(eitherReader gpgParser) (eitherReader gpgParser)
( long "gpg" ( long "gpg"

View File

@@ -138,7 +138,7 @@ versionArgument criteria tool = argument (eitherReader tVersionEither) (metavar
-- the help is shown only for --no-recursive. -- the help is shown only for --no-recursive.
invertableSwitch invertableSwitch
:: String -- ^ long option :: String -- ^ long option
-> Maybe Char -- ^ short option for the non-default option -> Char -- ^ short option for the non-default option
-> Bool -- ^ is switch enabled by default? -> Bool -- ^ is switch enabled by default?
-> Mod FlagFields Bool -- ^ option modifier -> Mod FlagFields Bool -- ^ option modifier
-> Parser (Maybe Bool) -> Parser (Maybe Bool)
@@ -149,14 +149,14 @@ invertableSwitch longopt shortopt defv optmod = invertableSwitch' longopt shorto
-- | Allows providing option modifiers for both --foo and --no-foo. -- | Allows providing option modifiers for both --foo and --no-foo.
invertableSwitch' invertableSwitch'
:: String -- ^ long option (eg "foo") :: String -- ^ long option (eg "foo")
-> Maybe Char -- ^ short option for the non-default option -> Char -- ^ short option for the non-default option
-> Bool -- ^ is switch enabled by default? -> Bool -- ^ is switch enabled by default?
-> Mod FlagFields Bool -- ^ option modifier for --foo -> Mod FlagFields Bool -- ^ option modifier for --foo
-> Mod FlagFields Bool -- ^ option modifier for --no-foo -> Mod FlagFields Bool -- ^ option modifier for --no-foo
-> Parser (Maybe Bool) -> Parser (Maybe Bool)
invertableSwitch' longopt shortopt defv enmod dismod = optional invertableSwitch' longopt shortopt defv enmod dismod = optional
( flag' True ( enmod <> long longopt <> if defv then mempty else maybe mempty short shortopt) ( flag' True ( enmod <> long longopt <> if defv then mempty else short shortopt)
<|> flag' False (dismod <> long nolongopt <> if defv then maybe mempty short shortopt else mempty) <|> flag' False (dismod <> long nolongopt <> if defv then short shortopt else mempty)
) )
where where
nolongopt = "no-" ++ longopt nolongopt = "no-" ++ longopt

View File

@@ -234,7 +234,12 @@ ghcCompileOpts =
) )
) )
<*> many (argument str (metavar "CONFIGURE_ARGS" <> help "Additional arguments to configure, prefix with '-- ' (longopts)")) <*> many (argument str (metavar "CONFIGURE_ARGS" <> help "Additional arguments to configure, prefix with '-- ' (longopts)"))
<*> fmap (fromMaybe False) (invertableSwitch "set" Nothing False (help "Set as active version after install")) <*> flag
False
True
(long "set" <> help
"Set as active version after install"
)
<*> optional <*> optional
(option (option
(eitherReader (eitherReader
@@ -295,7 +300,12 @@ hlsCompileOpts =
<> (completer $ listCompleter $ fmap show ([1..12] :: [Int])) <> (completer $ listCompleter $ fmap show ([1..12] :: [Int]))
) )
) )
<*> fmap (fromMaybe True) (invertableSwitch "set" Nothing True (help "Don't set as active version after install")) <*> flag
False
True
(long "set" <> help
"Set as active version after install"
)
<*> optional <*> optional
(option (option
(eitherReader (eitherReader

View File

@@ -197,8 +197,12 @@ installOpts tool =
) )
<|> pure (Nothing, Nothing) <|> pure (Nothing, Nothing)
) )
<*> fmap (fromMaybe setDefault) (invertableSwitch "set" Nothing setDefault <*> flag
(help $ if not setDefault then "Set as active version after install" else "Don't set as active version after install")) False
True
(long "set" <> help
"Set as active version after install"
)
<*> optional <*> optional
(option (option
(eitherReader isolateParser) (eitherReader isolateParser)
@@ -211,11 +215,6 @@ installOpts tool =
) )
<*> switch <*> switch
(short 'f' <> long "force" <> help "Force install") (short 'f' <> long "force" <> help "Force install")
where
setDefault = case tool of
Nothing -> False
Just GHC -> False
Just _ -> True
@@ -398,7 +397,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
isolateDir isolateDir
forceInstall forceInstall
) )
$ when instSet $ when (isNothing isolateDir) $ void $ setGHC v SetGHCOnly Nothing $ when instSet $ void $ setGHC v SetGHCOnly Nothing
pure vi pure vi
Just uri -> do Just uri -> do
runInstGHC s'{ settings = settings {noVerify = True}} instPlatform $ do runInstGHC s'{ settings = settings {noVerify = True}} instPlatform $ do
@@ -409,7 +408,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
isolateDir isolateDir
forceInstall forceInstall
) )
$ when instSet $ when (isNothing isolateDir) $ void $ setGHC v SetGHCOnly Nothing $ when instSet $ void $ setGHC v SetGHCOnly Nothing
pure vi pure vi
) )
>>= \case >>= \case
@@ -469,7 +468,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
v v
isolateDir isolateDir
forceInstall forceInstall
) $ when instSet $ when (isNothing isolateDir) $ void $ setCabal v ) $ when instSet $ void $ setCabal v
pure vi pure vi
Just uri -> do Just uri -> do
runInstTool s'{ settings = settings { noVerify = True}} instPlatform $ do runInstTool s'{ settings = settings { noVerify = True}} instPlatform $ do
@@ -479,7 +478,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
v v
isolateDir isolateDir
forceInstall forceInstall
) $ when instSet $ when (isNothing isolateDir) $ void $ setCabal v ) $ when instSet $ void $ setCabal v
pure vi pure vi
) )
>>= \case >>= \case
@@ -520,7 +519,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
v v
isolateDir isolateDir
forceInstall forceInstall
) $ when instSet $ when (isNothing isolateDir) $ void $ setHLS v SetHLSOnly Nothing ) $ when instSet $ void $ setHLS v SetHLSOnly Nothing
pure vi pure vi
Just uri -> do Just uri -> do
runInstTool s'{ settings = settings { noVerify = True}} instPlatform $ do runInstTool s'{ settings = settings { noVerify = True}} instPlatform $ do
@@ -531,7 +530,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
v v
isolateDir isolateDir
forceInstall forceInstall
) $ when instSet $ when (isNothing isolateDir) $ void $ setHLS v SetHLSOnly Nothing ) $ when instSet $ void $ setHLS v SetHLSOnly Nothing
pure vi pure vi
) )
>>= \case >>= \case
@@ -580,7 +579,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
v v
isolateDir isolateDir
forceInstall forceInstall
) $ when instSet $ when (isNothing isolateDir) $ void $ setStack v ) $ when instSet $ void $ setStack v
pure vi pure vi
Just uri -> do Just uri -> do
runInstTool s'{ settings = settings { noVerify = True}} instPlatform $ do runInstTool s'{ settings = settings { noVerify = True}} instPlatform $ do
@@ -590,7 +589,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
v v
isolateDir isolateDir
forceInstall forceInstall
) $ when instSet $ when (isNothing isolateDir) $ void $ setStack v ) $ when instSet $ void $ setStack v
pure vi pure vi
) )
>>= \case >>= \case

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
}

View File

@@ -468,6 +468,10 @@ installCabalBindist dlinfo ver isoFilepath forceInstall = do
Nothing -> do -- regular install Nothing -> do -- regular install
liftE $ installCabalUnpacked workdir binDir (Just ver) forceInstall liftE $ installCabalUnpacked workdir binDir (Just ver) forceInstall
-- create symlink if this is the latest version for regular installs
cVers <- lift $ fmap rights getInstalledCabals
let lInstCabal = headMay . reverse . sort $ cVers
when (maybe True (ver >=) lInstCabal) $ liftE $ setCabal ver
-- | Install an unpacked cabal distribution.Symbol -- | Install an unpacked cabal distribution.Symbol
installCabalUnpacked :: (MonadCatch m, HasLog env, MonadIO m, MonadReader env m) installCabalUnpacked :: (MonadCatch m, HasLog env, MonadIO m, MonadReader env m)
@@ -622,6 +626,7 @@ installHLSBindist dlinfo ver isoFilepath forceInstall = do
liftE $ runBuildAction tmpUnpack Nothing $ installHLSUnpacked workdir inst ver liftE $ runBuildAction tmpUnpack Nothing $ installHLSUnpacked workdir inst ver
liftE $ setHLS ver SetHLS_XYZ Nothing liftE $ setHLS ver SetHLS_XYZ Nothing
liftE $ installHLSPostInst isoFilepath ver
isLegacyHLSBindist :: FilePath -- ^ Path to the unpacked hls bindist isLegacyHLSBindist :: FilePath -- ^ Path to the unpacked hls bindist
-> IO Bool -> IO Bool
@@ -691,6 +696,19 @@ installHLSUnpackedLegacy path inst mver' forceInstall = do
lift $ chmod_755 destWrapperPath lift $ chmod_755 destWrapperPath
installHLSPostInst :: (MonadReader env m, HasDirs env, HasLog env, MonadIO m, MonadCatch m, MonadMask m, MonadFail m, MonadUnliftIO m)
=> Maybe FilePath
-> Version
-> Excepts '[NotInstalled] m ()
installHLSPostInst isoFilepath ver =
case isoFilepath of
Just _ -> pure ()
Nothing -> do
-- create symlink if this is the latest version in a regular install
hlsVers <- lift $ fmap rights getInstalledHLSs
let lInstHLS = headMay . reverse . sort $ hlsVers
when (maybe True (ver >=) lInstHLS) $ liftE $ setHLS ver SetHLSOnly Nothing
-- | Installs hls binaries @haskell-language-server-\<ghcver\>@ -- | Installs hls binaries @haskell-language-server-\<ghcver\>@
-- into @~\/.ghcup\/bin/@, as well as @haskell-languager-server-wrapper@. -- into @~\/.ghcup\/bin/@, as well as @haskell-languager-server-wrapper@.
@@ -898,6 +916,8 @@ compileHLS targetHLS ghcs jobs ov isolateDir cabalProject cabalProjectLocal patc
liftE $ installHLSUnpackedLegacy installDir binDir (Just installVer) True liftE $ installHLSUnpackedLegacy installDir binDir (Just installVer) True
) )
liftE $ installHLSPostInst isolateDir installVer
pure installVer pure installVer
@@ -1014,6 +1034,11 @@ installStackBindist dlinfo ver isoFilepath forceInstall = do
Nothing -> do -- regular install Nothing -> do -- regular install
liftE $ installStackUnpacked workdir binDir (Just ver) forceInstall liftE $ installStackUnpacked workdir binDir (Just ver) forceInstall
-- create symlink if this is the latest version and a regular install
sVers <- lift $ fmap rights getInstalledStacks
let lInstStack = headMay . reverse . sort $ sVers
when (maybe True (ver >=) lInstStack) $ liftE $ setStack ver
-- | Install an unpacked stack distribution. -- | Install an unpacked stack distribution.
installStackUnpacked :: (MonadReader env m, HasLog env, MonadCatch m, MonadIO m) installStackUnpacked :: (MonadReader env m, HasLog env, MonadCatch m, MonadIO m)