2021-10-15 20:24:23 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE TypeApplications #-}
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE DuplicateRecordFields #-}
|
2022-03-05 19:50:58 +00:00
|
|
|
{-# LANGUAGE ViewPatterns #-}
|
2022-05-23 21:32:58 +00:00
|
|
|
{-# LANGUAGE TypeOperators #-}
|
2021-10-15 20:24:23 +00:00
|
|
|
|
|
|
|
module GHCup.OptParse.Install where
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
import GHCup.OptParse.Common
|
|
|
|
|
|
|
|
import GHCup
|
|
|
|
import GHCup.Errors
|
|
|
|
import GHCup.Types
|
2022-05-13 19:35:34 +00:00
|
|
|
import GHCup.Utils.Dirs
|
2022-05-23 21:32:58 +00:00
|
|
|
import GHCup.Prelude
|
2022-05-21 20:54:18 +00:00
|
|
|
import GHCup.Prelude.Logger
|
|
|
|
import GHCup.Prelude.String.QQ
|
2021-10-15 20:24:23 +00:00
|
|
|
|
|
|
|
#if !MIN_VERSION_base(4,13,0)
|
|
|
|
import Control.Monad.Fail ( MonadFail )
|
|
|
|
#endif
|
|
|
|
import Control.Monad.Reader
|
|
|
|
import Control.Monad.Trans.Resource
|
|
|
|
import Data.Either
|
|
|
|
import Data.Functor
|
|
|
|
import Data.Maybe
|
|
|
|
import Haskus.Utils.Variant.Excepts
|
|
|
|
import Options.Applicative hiding ( style )
|
|
|
|
import Options.Applicative.Help.Pretty ( text )
|
|
|
|
import Prelude hiding ( appendFile )
|
|
|
|
import System.Exit
|
2021-11-12 18:05:13 +00:00
|
|
|
import URI.ByteString hiding ( uriParser )
|
2021-10-15 20:24:23 +00:00
|
|
|
|
|
|
|
import qualified Data.Text as T
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
----------------
|
|
|
|
--[ Commands ]--
|
|
|
|
----------------
|
|
|
|
|
|
|
|
|
2023-10-24 16:35:41 +00:00
|
|
|
data InstallCommand = InstallGHC InstallOptions
|
2021-10-15 20:24:23 +00:00
|
|
|
| InstallCabal InstallOptions
|
|
|
|
| InstallHLS InstallOptions
|
|
|
|
| InstallStack InstallOptions
|
2023-07-22 15:10:27 +00:00
|
|
|
deriving (Eq, Show)
|
2021-10-15 20:24:23 +00:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
---------------
|
|
|
|
--[ Options ]--
|
|
|
|
---------------
|
|
|
|
|
|
|
|
data InstallOptions = InstallOptions
|
|
|
|
{ instVer :: Maybe ToolVersion
|
|
|
|
, instBindist :: Maybe URI
|
|
|
|
, instSet :: Bool
|
|
|
|
, isolateDir :: Maybe FilePath
|
|
|
|
, forceInstall :: Bool
|
2022-06-09 12:42:01 +00:00
|
|
|
, addConfArgs :: [T.Text]
|
2023-07-22 15:10:27 +00:00
|
|
|
} deriving (Eq, Show)
|
2021-10-15 20:24:23 +00:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
---------------
|
|
|
|
--[ Footers ]--
|
|
|
|
---------------
|
|
|
|
|
|
|
|
installCabalFooter :: String
|
|
|
|
installCabalFooter = [s|Discussion:
|
|
|
|
Installs the specified cabal-install version (or a recommended default one)
|
|
|
|
into "~/.ghcup/bin", so it can be overwritten by later
|
|
|
|
"cabal install cabal-install", which installs into "~/.cabal/bin" by
|
|
|
|
default. Make sure to set up your PATH appropriately, so the cabal
|
|
|
|
installation takes precedence.|]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
---------------
|
|
|
|
--[ Parsers ]--
|
|
|
|
---------------
|
|
|
|
|
2023-10-24 16:35:41 +00:00
|
|
|
installParser :: Parser (Either InstallCommand InstallOptions)
|
2021-10-15 20:24:23 +00:00
|
|
|
installParser =
|
|
|
|
(Left <$> subparser
|
|
|
|
( command
|
|
|
|
"ghc"
|
|
|
|
( InstallGHC
|
|
|
|
<$> info
|
2023-10-24 16:35:41 +00:00
|
|
|
(installOpts (Just GHC) <**> helper)
|
2021-10-15 20:24:23 +00:00
|
|
|
( progDesc "Install GHC"
|
|
|
|
<> footerDoc (Just $ text installGHCFooter)
|
|
|
|
)
|
|
|
|
)
|
|
|
|
<> command
|
|
|
|
"cabal"
|
|
|
|
( InstallCabal
|
|
|
|
<$> info
|
|
|
|
(installOpts (Just Cabal) <**> helper)
|
|
|
|
( progDesc "Install Cabal"
|
|
|
|
<> footerDoc (Just $ text installCabalFooter)
|
|
|
|
)
|
|
|
|
)
|
|
|
|
<> command
|
|
|
|
"hls"
|
|
|
|
( InstallHLS
|
|
|
|
<$> info
|
|
|
|
(installOpts (Just HLS) <**> helper)
|
|
|
|
( progDesc "Install haskell-language-server"
|
|
|
|
<> footerDoc (Just $ text installHLSFooter)
|
|
|
|
)
|
|
|
|
)
|
|
|
|
<> command
|
|
|
|
"stack"
|
|
|
|
( InstallStack
|
|
|
|
<$> info
|
|
|
|
(installOpts (Just Stack) <**> helper)
|
|
|
|
( progDesc "Install stack"
|
|
|
|
<> footerDoc (Just $ text installStackFooter)
|
|
|
|
)
|
|
|
|
)
|
|
|
|
)
|
|
|
|
)
|
2023-10-24 16:35:41 +00:00
|
|
|
<|> (Right <$> installOpts (Just GHC))
|
2021-10-15 20:24:23 +00:00
|
|
|
where
|
|
|
|
installHLSFooter :: String
|
|
|
|
installHLSFooter = [s|Discussion:
|
|
|
|
Installs haskell-language-server binaries and wrapper
|
|
|
|
into "~/.ghcup/bin"
|
|
|
|
|
|
|
|
Examples:
|
|
|
|
# install recommended HLS
|
|
|
|
ghcup install hls|]
|
|
|
|
|
|
|
|
installStackFooter :: String
|
|
|
|
installStackFooter = [s|Discussion:
|
|
|
|
Installs stack binaries into "~/.ghcup/bin"
|
|
|
|
|
|
|
|
Examples:
|
|
|
|
# install recommended Stack
|
|
|
|
ghcup install stack|]
|
|
|
|
|
|
|
|
installGHCFooter :: String
|
|
|
|
installGHCFooter = [s|Discussion:
|
|
|
|
Installs the specified GHC version (or a recommended default one) into
|
|
|
|
a self-contained "~/.ghcup/ghc/<ghcver>" directory
|
|
|
|
and symlinks the ghc binaries to "~/.ghcup/bin/<binary>-<ghcver>".
|
|
|
|
|
|
|
|
Examples:
|
|
|
|
# install recommended GHC
|
|
|
|
ghcup install ghc
|
|
|
|
|
|
|
|
# install latest GHC
|
|
|
|
ghcup install ghc latest
|
|
|
|
|
|
|
|
# install GHC 8.10.2
|
|
|
|
ghcup install ghc 8.10.2
|
|
|
|
|
|
|
|
# install GHC head fedora bindist
|
2022-08-09 13:32:58 +00:00
|
|
|
ghcup install ghc -u 'https://gitlab.haskell.org/ghc/ghc/-/jobs/artifacts/master/raw/ghc-x86_64-linux-fedora33-release.tar.xz?job=x86_64-linux-fedora33-release' head|]
|
2021-10-15 20:24:23 +00:00
|
|
|
|
|
|
|
|
|
|
|
installOpts :: Maybe Tool -> Parser InstallOptions
|
|
|
|
installOpts tool =
|
2022-11-12 06:12:13 +00:00
|
|
|
(\(u, v) b is f -> InstallOptions v u b is f)
|
|
|
|
<$> ( ( (,)
|
2021-10-15 20:24:23 +00:00
|
|
|
<$> optional
|
|
|
|
(option
|
2021-11-12 18:05:13 +00:00
|
|
|
(eitherReader uriParser)
|
2021-10-15 20:24:23 +00:00
|
|
|
(short 'u' <> long "url" <> metavar "BINDIST_URL" <> help
|
|
|
|
"Install the specified version from this bindist"
|
2022-03-04 23:46:37 +00:00
|
|
|
<> completer (toolDlCompleter (fromMaybe GHC tool))
|
2021-10-15 20:24:23 +00:00
|
|
|
)
|
|
|
|
)
|
2023-05-01 09:46:27 +00:00
|
|
|
<*> (Just <$> toolVersionTagArgument [] tool)
|
2021-10-15 20:24:23 +00:00
|
|
|
)
|
|
|
|
<|> pure (Nothing, Nothing)
|
|
|
|
)
|
2022-03-13 21:48:45 +00:00
|
|
|
<*> fmap (fromMaybe setDefault) (invertableSwitch "set" Nothing setDefault
|
|
|
|
(help $ if not setDefault then "Set as active version after install" else "Don't set as active version after install"))
|
2021-10-15 20:24:23 +00:00
|
|
|
<*> optional
|
|
|
|
(option
|
|
|
|
(eitherReader isolateParser)
|
|
|
|
( short 'i'
|
|
|
|
<> long "isolate"
|
|
|
|
<> metavar "DIR"
|
2023-07-25 15:01:44 +00:00
|
|
|
<> help "install in an isolated absolute directory instead of the default one"
|
2022-03-04 23:46:37 +00:00
|
|
|
<> completer (bashCompleter "directory")
|
2021-10-15 20:24:23 +00:00
|
|
|
)
|
|
|
|
)
|
|
|
|
<*> switch
|
2022-05-12 11:28:09 +00:00
|
|
|
(short 'f' <> long "force" <> help "Force install (THIS IS UNSAFE, only use it in Dockerfiles or CI)")
|
2022-06-09 12:42:01 +00:00
|
|
|
<*> many (argument str (metavar "CONFIGURE_ARGS" <> help "Additional arguments to bindist configure, prefix with '-- ' (longopts)"))
|
2022-03-13 21:48:45 +00:00
|
|
|
where
|
|
|
|
setDefault = case tool of
|
|
|
|
Nothing -> False
|
|
|
|
Just GHC -> False
|
|
|
|
Just _ -> True
|
2022-05-11 13:47:08 +00:00
|
|
|
|
2021-10-15 20:24:23 +00:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
--------------
|
|
|
|
--[ Footer ]--
|
|
|
|
--------------
|
|
|
|
|
|
|
|
|
|
|
|
installToolFooter :: String
|
|
|
|
installToolFooter = [s|Discussion:
|
|
|
|
Installs GHC or cabal. When no command is given, installs GHC
|
|
|
|
with the specified version/tag.
|
|
|
|
It is recommended to always specify a subcommand (ghc/cabal/hls/stack).|]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
---------------------------
|
|
|
|
--[ Effect interpreters ]--
|
|
|
|
---------------------------
|
|
|
|
|
|
|
|
type InstallEffects = '[ AlreadyInstalled
|
|
|
|
, UnknownArchive
|
|
|
|
, ArchiveResult
|
|
|
|
, FileDoesNotExistError
|
|
|
|
, CopyError
|
|
|
|
, NotInstalled
|
|
|
|
, DirNotEmpty
|
|
|
|
, NoDownload
|
|
|
|
, NotInstalled
|
|
|
|
, BuildFailed
|
|
|
|
, TagNotFound
|
2023-05-01 09:46:27 +00:00
|
|
|
, DayNotFound
|
2021-10-15 20:24:23 +00:00
|
|
|
, DigestError
|
2022-12-21 16:31:41 +00:00
|
|
|
, ContentLengthError
|
2021-10-15 20:24:23 +00:00
|
|
|
, 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-05-23 21:32:58 +00:00
|
|
|
, InstallSetError
|
2021-10-15 20:24:23 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
|
|
|
|
runInstTool :: AppState
|
|
|
|
-> Excepts InstallEffects (ResourceT (ReaderT AppState IO)) a
|
|
|
|
-> IO (VEither InstallEffects a)
|
2022-11-12 06:12:13 +00:00
|
|
|
runInstTool appstate' =
|
|
|
|
flip runReaderT appstate'
|
2021-10-15 20:24:23 +00:00
|
|
|
. runResourceT
|
|
|
|
. runE
|
|
|
|
@InstallEffects
|
|
|
|
|
|
|
|
|
2022-05-23 21:32:58 +00:00
|
|
|
type InstallGHCEffects = '[ AlreadyInstalled
|
|
|
|
, ArchiveResult
|
2022-01-30 16:59:27 +00:00
|
|
|
, BuildFailed
|
2022-05-23 21:32:58 +00:00
|
|
|
, CopyError
|
|
|
|
, DigestError
|
2022-12-21 16:31:41 +00:00
|
|
|
, ContentLengthError
|
2022-01-30 16:59:27 +00:00
|
|
|
, DirNotEmpty
|
2022-05-23 21:32:58 +00:00
|
|
|
, DownloadFailed
|
|
|
|
, FileAlreadyExistsError
|
|
|
|
, FileDoesNotExistError
|
|
|
|
, GPGError
|
2022-05-19 21:17:58 +00:00
|
|
|
, MergeFileTreeError
|
2022-05-23 21:32:58 +00:00
|
|
|
, NextVerNotFound
|
|
|
|
, NoDownload
|
|
|
|
, NoToolVersionSet
|
|
|
|
, NotInstalled
|
|
|
|
, ProcessError
|
|
|
|
, TagNotFound
|
2023-05-01 09:46:27 +00:00
|
|
|
, DayNotFound
|
2022-05-23 21:32:58 +00:00
|
|
|
, TarDirDoesNotExist
|
|
|
|
, UninstallFailed
|
|
|
|
, UnknownArchive
|
|
|
|
, InstallSetError
|
2023-10-22 13:50:27 +00:00
|
|
|
, NoCompatiblePlatform
|
|
|
|
, GHCup.Errors.ParseError
|
|
|
|
, UnsupportedSetupCombo
|
|
|
|
, DistroNotFound
|
|
|
|
, NoCompatibleArch
|
2022-01-30 16:59:27 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
runInstGHC :: AppState
|
|
|
|
-> Excepts InstallGHCEffects (ResourceT (ReaderT AppState IO)) a
|
|
|
|
-> IO (VEither InstallGHCEffects a)
|
2022-11-12 06:12:13 +00:00
|
|
|
runInstGHC appstate' =
|
|
|
|
flip runReaderT appstate'
|
2022-01-30 16:59:27 +00:00
|
|
|
. runResourceT
|
|
|
|
. runE
|
|
|
|
@InstallGHCEffects
|
|
|
|
|
2021-10-15 20:24:23 +00:00
|
|
|
|
|
|
|
-------------------
|
|
|
|
--[ Entrypoints ]--
|
|
|
|
-------------------
|
|
|
|
|
|
|
|
|
2023-10-24 16:35:41 +00:00
|
|
|
install :: Either InstallCommand InstallOptions -> Settings -> IO AppState -> (ReaderT LeanAppState IO () -> IO ()) -> IO ExitCode
|
2021-10-15 20:24:23 +00:00
|
|
|
install installCommand settings getAppState' runLogger = case installCommand of
|
2023-10-22 13:50:27 +00:00
|
|
|
(Right iGHCopts) -> do
|
2021-10-15 20:24:23 +00:00
|
|
|
runLogger (logWarn "This is an old-style command for installing GHC. Use 'ghcup install ghc' instead.")
|
2023-10-22 13:50:27 +00:00
|
|
|
installGHC iGHCopts
|
|
|
|
(Left (InstallGHC iGHCopts)) -> installGHC iGHCopts
|
|
|
|
(Left (InstallCabal iopts)) -> installCabal iopts
|
|
|
|
(Left (InstallHLS iopts)) -> installHLS iopts
|
|
|
|
(Left (InstallStack iopts)) -> installStack iopts
|
2021-10-15 20:24:23 +00:00
|
|
|
where
|
2023-10-24 16:35:41 +00:00
|
|
|
installGHC :: InstallOptions -> IO ExitCode
|
|
|
|
installGHC InstallOptions{..} = do
|
2021-10-15 20:24:23 +00:00
|
|
|
s'@AppState{ dirs = Dirs{ .. } } <- liftIO getAppState'
|
|
|
|
(case instBindist of
|
2023-10-24 16:35:41 +00:00
|
|
|
Nothing -> runInstGHC s' $ do
|
2021-10-15 20:24:23 +00:00
|
|
|
(v, vi) <- liftE $ fromVersion instVer GHC
|
2022-05-23 21:32:58 +00:00
|
|
|
liftE $ runBothE' (installGHCBin
|
2023-07-07 08:41:58 +00:00
|
|
|
v
|
2022-05-11 13:47:08 +00:00
|
|
|
(maybe GHCupInternal IsolateDir isolateDir)
|
2021-10-15 20:24:23 +00:00
|
|
|
forceInstall
|
2022-06-09 12:42:01 +00:00
|
|
|
addConfArgs
|
2022-01-30 16:59:27 +00:00
|
|
|
)
|
2022-05-23 21:32:58 +00:00
|
|
|
$ when instSet $ when (isNothing isolateDir) $ liftE $ void $ setGHC v SetGHCOnly Nothing
|
2022-01-30 16:59:27 +00:00
|
|
|
pure vi
|
|
|
|
Just uri -> do
|
2022-11-12 06:12:13 +00:00
|
|
|
runInstGHC s'{ settings = settings {noVerify = True}} $ do
|
2022-01-30 16:59:27 +00:00
|
|
|
(v, vi) <- liftE $ fromVersion instVer GHC
|
2022-05-23 21:32:58 +00:00
|
|
|
liftE $ runBothE' (installGHCBindist
|
2023-05-14 11:33:04 +00:00
|
|
|
(DownloadInfo uri (Just $ RegexDir "ghc-.*") "" Nothing Nothing)
|
2023-07-07 08:41:58 +00:00
|
|
|
v
|
2022-05-11 13:47:08 +00:00
|
|
|
(maybe GHCupInternal IsolateDir isolateDir)
|
2022-01-30 16:59:27 +00:00
|
|
|
forceInstall
|
2022-06-09 12:42:01 +00:00
|
|
|
addConfArgs
|
2022-01-30 16:59:27 +00:00
|
|
|
)
|
2022-05-23 21:32:58 +00:00
|
|
|
$ when instSet $ when (isNothing isolateDir) $ liftE $ void $ setGHC v SetGHCOnly Nothing
|
2021-10-15 20:24:23 +00:00
|
|
|
pure vi
|
|
|
|
)
|
|
|
|
>>= \case
|
|
|
|
VRight vi -> do
|
|
|
|
runLogger $ logInfo "GHC installation successful"
|
|
|
|
forM_ (_viPostInstall =<< vi) $ \msg ->
|
|
|
|
runLogger $ logInfo msg
|
|
|
|
pure ExitSuccess
|
2022-01-30 16:59:27 +00:00
|
|
|
|
2022-05-23 21:49:43 +00:00
|
|
|
VLeft e@(V (AlreadyInstalled _ _)) -> do
|
2022-12-19 16:10:19 +00:00
|
|
|
runLogger $ logWarn $ T.pack $ prettyHFError e
|
2022-01-30 16:59:27 +00:00
|
|
|
pure ExitSuccess
|
2022-05-23 21:49:43 +00:00
|
|
|
VLeft e@(V (AlreadyInstalled _ _)) -> do
|
2022-12-19 16:10:19 +00:00
|
|
|
runLogger $ logWarn $ T.pack $ prettyHFError e
|
2021-10-15 20:24:23 +00:00
|
|
|
pure ExitSuccess
|
2022-01-30 16:59:27 +00:00
|
|
|
|
2021-10-15 20:24:23 +00:00
|
|
|
VLeft (V (DirNotEmpty fp)) -> do
|
2022-05-12 11:28:09 +00:00
|
|
|
runLogger $ logError $
|
|
|
|
"Install directory " <> T.pack fp <> " is not empty."
|
2021-10-15 20:24:23 +00:00
|
|
|
pure $ ExitFailure 3
|
2022-05-23 21:32:58 +00:00
|
|
|
VLeft (V (DirNotEmpty fp)) -> do
|
2022-05-12 11:28:09 +00:00
|
|
|
runLogger $ logError $
|
|
|
|
"Install directory " <> T.pack fp <> " is not empty."
|
2022-01-30 16:59:27 +00:00
|
|
|
pure $ ExitFailure 3
|
|
|
|
|
2021-10-15 20:24:23 +00:00
|
|
|
VLeft err@(V (BuildFailed tmpdir _)) -> do
|
|
|
|
case keepDirs settings of
|
2022-12-19 16:10:19 +00:00
|
|
|
Never -> runLogger (logError $ T.pack $ prettyHFError err)
|
|
|
|
_ -> runLogger (logError $ T.pack (prettyHFError err) <> "\n" <>
|
2022-05-13 19:35:34 +00:00
|
|
|
"Check the logs at " <> T.pack (fromGHCupPath logsDir) <> " and the build directory " <> T.pack tmpdir <> " for more clues." <> "\n" <>
|
2021-10-15 20:24:23 +00:00
|
|
|
"Make sure to clean up " <> T.pack tmpdir <> " afterwards.")
|
|
|
|
pure $ ExitFailure 3
|
2022-05-23 21:32:58 +00:00
|
|
|
VLeft err@(V (BuildFailed tmpdir _)) -> do
|
2022-01-30 16:59:27 +00:00
|
|
|
case keepDirs settings of
|
2022-12-19 16:10:19 +00:00
|
|
|
Never -> runLogger (logError $ T.pack $ prettyHFError err)
|
|
|
|
_ -> runLogger (logError $ T.pack (prettyHFError err) <> "\n" <>
|
2022-05-13 19:35:34 +00:00
|
|
|
"Check the logs at " <> T.pack (fromGHCupPath logsDir) <> " and the build directory " <> T.pack tmpdir <> " for more clues." <> "\n" <>
|
2022-01-30 16:59:27 +00:00
|
|
|
"Make sure to clean up " <> T.pack tmpdir <> " afterwards.")
|
|
|
|
pure $ ExitFailure 3
|
|
|
|
|
2021-10-15 20:24:23 +00:00
|
|
|
VLeft e -> do
|
|
|
|
runLogger $ do
|
2022-12-19 16:10:19 +00:00
|
|
|
logError $ T.pack $ prettyHFError e
|
2022-05-13 19:35:34 +00:00
|
|
|
logError $ "Also check the logs in " <> T.pack (fromGHCupPath logsDir)
|
2021-10-15 20:24:23 +00:00
|
|
|
pure $ ExitFailure 3
|
|
|
|
|
|
|
|
|
|
|
|
installCabal :: InstallOptions -> IO ExitCode
|
|
|
|
installCabal InstallOptions{..} = do
|
|
|
|
s'@AppState{ dirs = Dirs{ .. } } <- liftIO getAppState'
|
|
|
|
(case instBindist of
|
2022-11-12 06:12:13 +00:00
|
|
|
Nothing -> runInstTool s' $ do
|
2022-03-05 19:50:58 +00:00
|
|
|
(_tvVersion -> v, vi) <- liftE $ fromVersion instVer Cabal
|
2022-05-23 21:32:58 +00:00
|
|
|
liftE $ runBothE' (installCabalBin
|
2022-03-05 19:50:58 +00:00
|
|
|
v
|
2022-05-11 13:47:08 +00:00
|
|
|
(maybe GHCupInternal IsolateDir isolateDir)
|
2022-03-05 19:50:58 +00:00
|
|
|
forceInstall
|
2022-05-23 21:32:58 +00:00
|
|
|
) $ when instSet $ when (isNothing isolateDir) $ liftE $ setCabal v
|
2021-10-15 20:24:23 +00:00
|
|
|
pure vi
|
|
|
|
Just uri -> do
|
2022-11-12 06:12:13 +00:00
|
|
|
runInstTool s'{ settings = settings { noVerify = True}} $ do
|
2022-03-05 19:50:58 +00:00
|
|
|
(_tvVersion -> v, vi) <- liftE $ fromVersion instVer Cabal
|
2022-05-23 21:32:58 +00:00
|
|
|
liftE $ runBothE' (installCabalBindist
|
2023-05-14 11:33:04 +00:00
|
|
|
(DownloadInfo uri Nothing "" Nothing Nothing)
|
2022-03-05 19:50:58 +00:00
|
|
|
v
|
2022-05-11 13:47:08 +00:00
|
|
|
(maybe GHCupInternal IsolateDir isolateDir)
|
2022-03-05 19:50:58 +00:00
|
|
|
forceInstall
|
2022-05-23 21:32:58 +00:00
|
|
|
) $ when instSet $ when (isNothing isolateDir) $ liftE $ setCabal v
|
2021-10-15 20:24:23 +00:00
|
|
|
pure vi
|
|
|
|
)
|
|
|
|
>>= \case
|
|
|
|
VRight vi -> do
|
|
|
|
runLogger $ logInfo "Cabal installation successful"
|
|
|
|
forM_ (_viPostInstall =<< vi) $ \msg ->
|
|
|
|
runLogger $ logInfo msg
|
|
|
|
pure ExitSuccess
|
2022-05-23 21:49:43 +00:00
|
|
|
VLeft e@(V (AlreadyInstalled _ _)) -> do
|
2022-12-19 16:10:19 +00:00
|
|
|
runLogger $ logWarn $ T.pack $ prettyHFError e
|
2021-10-15 20:24:23 +00:00
|
|
|
pure ExitSuccess
|
|
|
|
VLeft (V (FileAlreadyExistsError fp)) -> do
|
|
|
|
runLogger $ logWarn $
|
|
|
|
"File " <> T.pack fp <> " already exists. Use 'ghcup install cabal --isolate " <> T.pack fp <> " --force ..." <> "' if you want to overwrite."
|
|
|
|
pure $ ExitFailure 3
|
2022-05-23 21:49:43 +00:00
|
|
|
VLeft e@(V (AlreadyInstalled _ _)) -> do
|
2022-12-19 16:10:19 +00:00
|
|
|
runLogger $ logWarn $ T.pack $ prettyHFError e
|
2022-03-05 19:50:58 +00:00
|
|
|
pure ExitSuccess
|
2022-05-23 21:32:58 +00:00
|
|
|
VLeft (V (FileAlreadyExistsError fp)) -> do
|
2022-03-05 19:50:58 +00:00
|
|
|
runLogger $ logWarn $
|
|
|
|
"File " <> T.pack fp <> " already exists. Use 'ghcup install cabal --isolate " <> T.pack fp <> " --force ..." <> "' if you want to overwrite."
|
|
|
|
pure $ ExitFailure 3
|
2021-10-15 20:24:23 +00:00
|
|
|
VLeft e -> do
|
|
|
|
runLogger $ do
|
2022-12-19 16:10:19 +00:00
|
|
|
logError $ T.pack $ prettyHFError e
|
2022-05-13 19:35:34 +00:00
|
|
|
logError $ "Also check the logs in " <> T.pack (fromGHCupPath logsDir)
|
2021-10-15 20:24:23 +00:00
|
|
|
pure $ ExitFailure 4
|
|
|
|
|
|
|
|
installHLS :: InstallOptions -> IO ExitCode
|
|
|
|
installHLS InstallOptions{..} = do
|
|
|
|
s'@AppState{ dirs = Dirs{ .. } } <- liftIO getAppState'
|
|
|
|
(case instBindist of
|
2022-11-12 06:12:13 +00:00
|
|
|
Nothing -> runInstTool s' $ do
|
2022-03-05 19:50:58 +00:00
|
|
|
(_tvVersion -> v, vi) <- liftE $ fromVersion instVer HLS
|
2022-05-23 21:32:58 +00:00
|
|
|
liftE $ runBothE' (installHLSBin
|
2022-03-05 19:50:58 +00:00
|
|
|
v
|
2022-05-11 13:47:08 +00:00
|
|
|
(maybe GHCupInternal IsolateDir isolateDir)
|
2022-03-05 19:50:58 +00:00
|
|
|
forceInstall
|
2022-05-23 21:32:58 +00:00
|
|
|
) $ when instSet $ when (isNothing isolateDir) $ liftE $ setHLS v SetHLSOnly Nothing
|
2021-10-15 20:24:23 +00:00
|
|
|
pure vi
|
|
|
|
Just uri -> do
|
2022-11-12 06:12:13 +00:00
|
|
|
runInstTool s'{ settings = settings { noVerify = True}} $ do
|
2022-03-05 19:50:58 +00:00
|
|
|
(_tvVersion -> v, vi) <- liftE $ fromVersion instVer HLS
|
2022-02-05 00:53:04 +00:00
|
|
|
-- TODO: support legacy
|
2022-05-23 21:32:58 +00:00
|
|
|
liftE $ runBothE' (installHLSBindist
|
2023-05-14 11:33:04 +00:00
|
|
|
(DownloadInfo uri (if isWindows then Nothing else Just (RegexDir "haskell-language-server-*")) "" Nothing Nothing)
|
2022-03-05 19:50:58 +00:00
|
|
|
v
|
2022-05-11 13:47:08 +00:00
|
|
|
(maybe GHCupInternal IsolateDir isolateDir)
|
2022-03-05 19:50:58 +00:00
|
|
|
forceInstall
|
2022-05-23 21:32:58 +00:00
|
|
|
) $ when instSet $ when (isNothing isolateDir) $ liftE $ setHLS v SetHLSOnly Nothing
|
2021-10-15 20:24:23 +00:00
|
|
|
pure vi
|
|
|
|
)
|
|
|
|
>>= \case
|
|
|
|
VRight vi -> do
|
|
|
|
runLogger $ logInfo "HLS installation successful"
|
|
|
|
forM_ (_viPostInstall =<< vi) $ \msg ->
|
|
|
|
runLogger $ logInfo msg
|
|
|
|
pure ExitSuccess
|
2022-05-23 21:49:43 +00:00
|
|
|
VLeft e@(V (AlreadyInstalled _ _)) -> do
|
2022-12-19 16:10:19 +00:00
|
|
|
runLogger $ logWarn $ T.pack $ prettyHFError e
|
2021-10-15 20:24:23 +00:00
|
|
|
pure ExitSuccess
|
|
|
|
VLeft (V (FileAlreadyExistsError fp)) -> do
|
|
|
|
runLogger $ logWarn $
|
|
|
|
"File " <> T.pack fp <> " already exists. Use 'ghcup install hls --isolate " <> T.pack fp <> " --force ..." <> "' if you want to overwrite."
|
|
|
|
pure $ ExitFailure 3
|
2022-05-23 21:49:43 +00:00
|
|
|
VLeft e@(V (AlreadyInstalled _ _)) -> do
|
2022-12-19 16:10:19 +00:00
|
|
|
runLogger $ logWarn $ T.pack $ prettyHFError e
|
2022-03-05 19:50:58 +00:00
|
|
|
pure ExitSuccess
|
2022-05-23 21:32:58 +00:00
|
|
|
VLeft (V (FileAlreadyExistsError fp)) -> do
|
2022-03-05 19:50:58 +00:00
|
|
|
runLogger $ logWarn $
|
|
|
|
"File " <> T.pack fp <> " already exists. Use 'ghcup install hls --isolate " <> T.pack fp <> " --force ..." <> "' if you want to overwrite."
|
|
|
|
pure $ ExitFailure 3
|
2021-10-15 20:24:23 +00:00
|
|
|
VLeft e -> do
|
|
|
|
runLogger $ do
|
2022-12-19 16:10:19 +00:00
|
|
|
logError $ T.pack $ prettyHFError e
|
2022-05-13 19:35:34 +00:00
|
|
|
logError $ "Also check the logs in " <> T.pack (fromGHCupPath logsDir)
|
2021-10-15 20:24:23 +00:00
|
|
|
pure $ ExitFailure 4
|
|
|
|
|
|
|
|
installStack :: InstallOptions -> IO ExitCode
|
|
|
|
installStack InstallOptions{..} = do
|
|
|
|
s'@AppState{ dirs = Dirs{ .. } } <- liftIO getAppState'
|
|
|
|
(case instBindist of
|
2022-11-12 06:12:13 +00:00
|
|
|
Nothing -> runInstTool s' $ do
|
2022-03-05 19:50:58 +00:00
|
|
|
(_tvVersion -> v, vi) <- liftE $ fromVersion instVer Stack
|
2022-05-23 21:32:58 +00:00
|
|
|
liftE $ runBothE' (installStackBin
|
2022-03-05 19:50:58 +00:00
|
|
|
v
|
2022-05-11 13:47:08 +00:00
|
|
|
(maybe GHCupInternal IsolateDir isolateDir)
|
2022-03-05 19:50:58 +00:00
|
|
|
forceInstall
|
2022-05-23 21:32:58 +00:00
|
|
|
) $ when instSet $ when (isNothing isolateDir) $ liftE $ setStack v
|
2021-10-15 20:24:23 +00:00
|
|
|
pure vi
|
|
|
|
Just uri -> do
|
2022-11-12 06:12:13 +00:00
|
|
|
runInstTool s'{ settings = settings { noVerify = True}} $ do
|
2022-03-05 19:50:58 +00:00
|
|
|
(_tvVersion -> v, vi) <- liftE $ fromVersion instVer Stack
|
2022-05-23 21:32:58 +00:00
|
|
|
liftE $ runBothE' (installStackBindist
|
2023-05-14 11:33:04 +00:00
|
|
|
(DownloadInfo uri Nothing "" Nothing Nothing)
|
2022-03-05 19:50:58 +00:00
|
|
|
v
|
2022-05-11 13:47:08 +00:00
|
|
|
(maybe GHCupInternal IsolateDir isolateDir)
|
2022-03-05 19:50:58 +00:00
|
|
|
forceInstall
|
2022-05-23 21:32:58 +00:00
|
|
|
) $ when instSet $ when (isNothing isolateDir) $ liftE $ setStack v
|
2021-10-15 20:24:23 +00:00
|
|
|
pure vi
|
|
|
|
)
|
|
|
|
>>= \case
|
|
|
|
VRight vi -> do
|
|
|
|
runLogger $ logInfo "Stack installation successful"
|
|
|
|
forM_ (_viPostInstall =<< vi) $ \msg ->
|
|
|
|
runLogger $ logInfo msg
|
|
|
|
pure ExitSuccess
|
2022-05-23 21:49:43 +00:00
|
|
|
VLeft e@(V (AlreadyInstalled _ _)) -> do
|
2022-12-19 16:10:19 +00:00
|
|
|
runLogger $ logWarn $ T.pack $ prettyHFError e
|
2021-10-15 20:24:23 +00:00
|
|
|
pure ExitSuccess
|
|
|
|
VLeft (V (FileAlreadyExistsError fp)) -> do
|
|
|
|
runLogger $ logWarn $
|
|
|
|
"File " <> T.pack fp <> " already exists. Use 'ghcup install stack --isolate " <> T.pack fp <> " --force ..." <> "' if you want to overwrite."
|
|
|
|
pure $ ExitFailure 3
|
2022-05-23 21:49:43 +00:00
|
|
|
VLeft e@(V (AlreadyInstalled _ _)) -> do
|
2022-12-19 16:10:19 +00:00
|
|
|
runLogger $ logWarn $ T.pack $ prettyHFError e
|
2022-03-05 19:50:58 +00:00
|
|
|
pure ExitSuccess
|
2022-05-23 21:32:58 +00:00
|
|
|
VLeft (V (FileAlreadyExistsError fp)) -> do
|
2022-03-05 19:50:58 +00:00
|
|
|
runLogger $ logWarn $
|
|
|
|
"File " <> T.pack fp <> " already exists. Use 'ghcup install stack --isolate " <> T.pack fp <> " --force ..." <> "' if you want to overwrite."
|
|
|
|
pure $ ExitFailure 3
|
2021-10-15 20:24:23 +00:00
|
|
|
VLeft e -> do
|
|
|
|
runLogger $ do
|
2022-12-19 16:10:19 +00:00
|
|
|
logError $ T.pack $ prettyHFError e
|
2022-05-13 19:35:34 +00:00
|
|
|
logError $ "Also check the logs in " <> T.pack (fromGHCupPath logsDir)
|
2021-10-15 20:24:23 +00:00
|
|
|
pure $ ExitFailure 4
|