2021-10-15 20:24:23 +00:00
{- # LANGUAGE CPP # -}
{- # LANGUAGE DataKinds # -}
{- # LANGUAGE TypeApplications # -}
{- # LANGUAGE FlexibleContexts # -}
{- # LANGUAGE OverloadedStrings # -}
{- # LANGUAGE TemplateHaskell # -}
{- # LANGUAGE QuasiQuotes # -}
{- # LANGUAGE DuplicateRecordFields # -}
{- # LANGUAGE RankNTypes # -}
module GHCup.OptParse.Compile where
import GHCup
2022-07-09 21:12:00 +00:00
import qualified GHCup.GHC as GHC
import qualified GHCup.HLS as HLS
2021-10-15 20:24:23 +00:00
import GHCup.Errors
import GHCup.Types
import GHCup.Types.Optics
import GHCup.Utils
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
import GHCup.OptParse.Common
# if ! MIN_VERSION_base ( 4 , 13 , 0 )
import Control.Monad.Fail ( MonadFail )
# endif
import Control.Concurrent ( threadDelay )
import Control.Monad.Reader
import Control.Monad.Trans.Resource
import Data.Bifunctor
import Data.Functor
import Data.Maybe
2022-07-11 22:05:08 +00:00
import Data.Versions ( Version , prettyVer , version , pvp )
import qualified Data.Versions as V
2021-10-15 20:24:23 +00:00
import Data.Text ( Text )
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
2022-07-11 22:05:08 +00:00
import Control.Exception.Safe ( MonadMask , displayException )
2021-10-15 20:24:23 +00:00
import System.FilePath ( isPathSeparator )
import Text.Read ( readEither )
----------------
--[ Commands ]--
----------------
data CompileCommand = CompileGHC GHCCompileOptions
| CompileHLS HLSCompileOptions
2023-07-24 15:04:18 +00:00
deriving ( Eq , Show )
2021-10-15 20:24:23 +00:00
---------------
--[ Options ]--
---------------
data GHCCompileOptions = GHCCompileOptions
2023-07-04 14:06:03 +00:00
{ targetGhc :: GHC . GHCVer
2021-10-15 20:24:23 +00:00
, bootstrapGhc :: Either Version FilePath
, jobs :: Maybe Int
, buildConfig :: Maybe FilePath
2021-11-12 18:52:00 +00:00
, patches :: Maybe ( Either FilePath [ URI ] )
2021-10-15 20:24:23 +00:00
, crossTarget :: Maybe Text
, addConfArgs :: [ Text ]
, setCompile :: Bool
, ovewrwiteVer :: Maybe Version
, buildFlavour :: Maybe String
2023-07-15 11:07:21 +00:00
, buildSystem :: Maybe BuildSystem
2021-10-15 20:24:23 +00:00
, isolateDir :: Maybe FilePath
2023-07-24 15:04:18 +00:00
} deriving ( Eq , Show )
2021-10-15 20:24:23 +00:00
2022-07-09 18:27:55 +00:00
2021-10-15 20:24:23 +00:00
data HLSCompileOptions = HLSCompileOptions
2022-07-09 21:12:00 +00:00
{ targetHLS :: HLS . HLSVer
2021-10-15 20:24:23 +00:00
, jobs :: Maybe Int
, setCompile :: Bool
2022-07-09 21:50:20 +00:00
, updateCabal :: Bool
2022-07-06 20:49:11 +00:00
, ovewrwiteVer :: Either Bool Version
2021-10-15 20:24:23 +00:00
, isolateDir :: Maybe FilePath
2021-11-12 18:05:13 +00:00
, cabalProject :: Maybe ( Either FilePath URI )
, cabalProjectLocal :: Maybe URI
2021-11-12 18:52:00 +00:00
, patches :: Maybe ( Either FilePath [ URI ] )
2021-10-15 20:24:23 +00:00
, targetGHCs :: [ ToolVersion ]
2021-11-12 00:13:57 +00:00
, cabalArgs :: [ Text ]
2023-07-24 15:04:18 +00:00
} deriving ( Eq , Show )
2021-10-15 20:24:23 +00:00
---------------
--[ Parsers ]--
---------------
2022-05-12 11:28:09 +00:00
2021-10-15 20:24:23 +00:00
compileP :: Parser CompileCommand
compileP = subparser
( command
" ghc "
( CompileGHC
<$> info
( ghcCompileOpts <**> helper )
( progDesc " Compile GHC from source "
<> footerDoc ( Just $ text compileFooter )
)
)
<> command
" hls "
( CompileHLS
<$> info
( hlsCompileOpts <**> helper )
( progDesc " Compile HLS from source "
<> footerDoc ( Just $ text compileHLSFooter )
)
)
)
where
compileFooter = [ s | Discussion :
Compiles and installs the specified GHC version into
a self - contained " ~/.ghcup/ghc/<ghcver> " directory
and symlinks the ghc binaries to " ~/.ghcup/bin/<binary>-<ghcver> " .
This also allows building a cross - compiler . Consult the documentation
first : < https :// gitlab . haskell . org / ghc / ghc /-/ wikis / building / cross - compiling # configuring - the - build >
ENV variables :
Various toolchain variables will be passed onto the ghc build system ,
such as : CC , LD , OBJDUMP , NM , AR , RANLIB .
Examples :
# compile from known version
ghcup compile ghc - j 4 - v 8.4 . 2 - b 8.2 . 2
# compile from git commit / reference
ghcup compile ghc - j 4 - g master - b 8.2 . 2
# specify path to bootstrap ghc
ghcup compile ghc - j 4 - v 8.4 . 2 - b / usr / bin / ghc - 8.2 . 2
# build cross compiler
ghcup compile ghc - j 4 - v 8.4 . 2 - b 8.2 . 2 - x armv7 - unknown - linux - gnueabihf --config $(pwd)/build.mk -- --enable-unregisterised|]
compileHLSFooter = [ s | Discussion :
Compiles and installs the specified HLS version .
2022-07-06 20:49:11 +00:00
The --ghc arguments are necessary to specify which GHC version to build for/against.
2021-10-15 20:24:23 +00:00
These need to be available in PATH prior to compilation .
Examples :
2022-07-09 21:50:20 +00:00
# compile 1.7 . 0.0 from hackage for 8.10 . 7 , running 'cabal update' before the build
2022-07-10 19:58:03 +00:00
ghcup compile hls --version 1.7.0.0 --ghc 8.10.7 --cabal-update
2022-07-09 18:27:55 +00:00
# compile from master for ghc 9.2 . 3 using 'git describe' to name the binary and ignore the pinned index state
ghcup compile hls - g master --git-describe-version --ghc 9.2.3 -- --index-state=@(date '+%s')
2023-11-30 09:12:46 +00:00
# compile a specific commit for ghc 9.2 . 3 and set a specific version for the binary name
2022-07-06 20:49:11 +00:00
ghcup compile hls - g a32db0b - o 1.7 . 0.0 - p1 --ghc 9.2.3|]
2021-10-15 20:24:23 +00:00
ghcCompileOpts :: Parser GHCCompileOptions
ghcCompileOpts =
GHCCompileOptions
2022-07-09 21:12:00 +00:00
<$> ( ( GHC . SourceDist <$> option
2021-10-15 20:24:23 +00:00
( eitherReader
( first ( const " Not a valid version " ) . version . T . pack )
)
( short 'v' <> long " version " <> metavar " VERSION " <> help
" The tool version to compile "
2023-05-01 09:46:27 +00:00
<> ( completer $ versionCompleter [] GHC )
2021-10-15 20:24:23 +00:00
)
) <|>
2022-07-09 21:12:00 +00:00
( GHC . GitDist <$> ( GitBranch <$> option
2021-10-15 20:24:23 +00:00
str
( short 'g' <> long " git-ref " <> metavar " GIT_REFERENCE " <> help
" The git commit/branch/ref to build from "
) <*>
2022-03-07 21:23:39 +00:00
optional ( option str (
short 'r' <> long " repository " <> metavar " GIT_REPOSITORY " <> help " The git repository to build from (defaults to GHC upstream) "
<> completer ( gitFileUri [ " https://gitlab.haskell.org/ghc/ghc.git " ] )
) )
2022-07-09 21:12:00 +00:00
) )
<|>
(
GHC . RemoteDist <$> ( option
( eitherReader uriParser )
( long " remote-source-dist " <> metavar " URI " <> help
" URI (https/http/file) to a GHC source distribution "
<> completer fileUri
)
)
)
)
2021-10-15 20:24:23 +00:00
<*> option
( eitherReader
( \ x ->
( bimap ( const " Not a valid version " ) Left . version . T . pack $ x ) <|> ( if isPathSeparator ( head x ) then pure $ Right x else Left " Not an absolute Path " )
)
)
( short 'b'
<> long " bootstrap-ghc "
<> metavar " BOOTSTRAP_GHC "
<> help
" The GHC version (or full path) to bootstrap with (must be installed) "
2023-05-01 09:46:27 +00:00
<> ( completer $ versionCompleter [] GHC )
2021-10-15 20:24:23 +00:00
)
<*> optional
( option
( eitherReader ( readEither @ Int ) )
( short 'j' <> long " jobs " <> metavar " JOBS " <> help
" How many jobs to use for make "
2022-03-04 23:46:37 +00:00
<> ( completer $ listCompleter $ fmap show ( [ 1 .. 12 ] :: [ Int ] ) )
2021-10-15 20:24:23 +00:00
)
)
<*> optional
( option
str
( short 'c' <> long " config " <> metavar " CONFIG " <> help
" Absolute path to build config file "
2022-03-04 23:46:37 +00:00
<> completer ( bashCompleter " file " )
2021-10-15 20:24:23 +00:00
)
)
2021-11-12 18:52:00 +00:00
<*> ( optional
(
( fmap Right $ many $ option
( eitherReader uriParser )
( long " patch " <> metavar " PATCH_URI " <> help
" URI to a patch (https/http/file) "
2022-03-04 23:46:37 +00:00
<> completer fileUri
2021-11-12 18:52:00 +00:00
)
)
<|>
( fmap Left $ option
str
( short 'p' <> long " patchdir " <> metavar " PATCH_DIR " <> help
2022-01-12 09:06:38 +00:00
" Absolute path to patch directory (applies all .patch and .diff files in order using -p1. This order is determined by a quilt series file if it exists, or the patches are lexicographically ordered) "
2022-03-04 23:46:37 +00:00
<> completer ( bashCompleter " directory " )
2021-11-12 18:52:00 +00:00
)
2021-10-15 20:24:23 +00:00
)
)
2021-11-12 18:52:00 +00:00
)
2021-10-15 20:24:23 +00:00
<*> optional
( option
str
( short 'x' <> long " cross-target " <> metavar " CROSS_TARGET " <> help
" Build cross-compiler for this platform "
)
)
2022-06-09 12:42:01 +00:00
<*> many ( argument str ( metavar " CONFIGURE_ARGS " <> help " Additional arguments to compile configure, prefix with '-- ' (longopts) " ) )
2022-03-13 21:48:45 +00:00
<*> fmap ( fromMaybe False ) ( invertableSwitch " set " Nothing False ( help " Set as active version after install " ) )
2021-10-15 20:24:23 +00:00
<*> optional
( option
( eitherReader
( first ( const " Not a valid version " ) . version . T . pack )
)
( short 'o' <> long " overwrite-version " <> metavar " OVERWRITE_VERSION " <> help
" Allows to overwrite the finally installed VERSION with a different one, e.g. when you build 8.10.4 with your own patches, you might want to set this to '8.10.4-p1' "
2023-05-01 09:46:27 +00:00
<> ( completer $ versionCompleter [] GHC )
2021-10-15 20:24:23 +00:00
)
)
<*> optional
( option
str
( short 'f' <> long " flavour " <> metavar " BUILD_FLAVOUR " <> help
" Set the compile build flavour (this value depends on the build system type: 'make' vs 'hadrian') "
)
)
2023-07-15 11:07:21 +00:00
<*> (
( \ b -> if b then Just Hadrian else Nothing ) <$> switch
( long " hadrian " <> help " Use the hadrian build system instead of make. Tries to detect by default. "
2021-10-15 20:24:23 +00:00
)
2023-07-15 11:07:21 +00:00
<|>
( \ b -> if b then Just Make else Nothing ) <$> switch
( long " make " <> help " Use the make build system instead of hadrian. Tries to detect by default. "
)
)
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, no symlinks to this installation will be made "
2022-03-04 23:46:37 +00:00
<> completer ( bashCompleter " directory " )
2021-10-15 20:24:23 +00:00
)
)
hlsCompileOpts :: Parser HLSCompileOptions
hlsCompileOpts =
HLSCompileOptions
2022-07-10 19:58:03 +00:00
<$> ( ( HLS . HackageDist <$> option
2021-10-15 20:24:23 +00:00
( eitherReader
2022-07-11 22:05:08 +00:00
( ( >>= first displayException . V . version . V . prettyPVP ) . first ( const " Not a valid PVP version " ) . pvp . T . pack )
2021-10-15 20:24:23 +00:00
)
( short 'v' <> long " version " <> metavar " VERSION " <> help
2022-07-10 19:58:03 +00:00
" The version to compile (pulled from hackage) "
2023-05-01 09:46:27 +00:00
<> ( completer $ versionCompleter' [] HLS ( either ( const False ) ( const True ) . V . pvp . V . prettyVer ) )
2021-10-15 20:24:23 +00:00
)
2022-07-09 18:27:55 +00:00
)
<|>
2022-07-09 21:12:00 +00:00
( HLS . GitDist <$> ( GitBranch <$> option
2021-10-15 20:24:23 +00:00
str
( short 'g' <> long " git-ref " <> metavar " GIT_REFERENCE " <> help
2022-07-06 20:49:11 +00:00
" The git commit/branch/ref to build from (accepts anything 'git checkout' accepts) "
2021-10-15 20:24:23 +00:00
) <*>
2022-05-01 15:12:39 +00:00
optional ( option str ( short 'r' <> long " repository " <> metavar " GIT_REPOSITORY " <> help " The git repository to build from (defaults to HLS upstream) "
2022-03-07 21:23:39 +00:00
<> completer ( gitFileUri [ " https://github.com/haskell/haskell-language-server.git " ] )
) )
2022-07-09 18:27:55 +00:00
) )
<|>
2022-07-10 19:58:03 +00:00
( HLS . SourceDist <$> ( option
2022-07-09 18:27:55 +00:00
( eitherReader
( first ( const " Not a valid version " ) . version . T . pack )
)
2022-07-10 19:58:03 +00:00
( long " source-dist " <> metavar " VERSION " <> help
" The version to compile (pulled from packaged git sources) "
2023-05-01 09:46:27 +00:00
<> ( completer $ versionCompleter [] HLS )
2022-07-09 18:27:55 +00:00
)
) )
<|>
(
2022-07-09 21:12:00 +00:00
HLS . RemoteDist <$> ( option
2022-07-09 18:27:55 +00:00
( eitherReader uriParser )
( long " remote-source-dist " <> metavar " URI " <> help
" URI (https/http/file) to a HLS source distribution "
<> completer fileUri
)
)
)
)
2021-10-15 20:24:23 +00:00
<*> optional
( option
( eitherReader ( readEither @ Int ) )
( short 'j' <> long " jobs " <> metavar " JOBS " <> help
" How many jobs to use for make "
2022-03-04 23:46:37 +00:00
<> ( completer $ listCompleter $ fmap show ( [ 1 .. 12 ] :: [ Int ] ) )
2021-10-15 20:24:23 +00:00
)
)
2022-03-13 21:48:45 +00:00
<*> fmap ( fromMaybe True ) ( invertableSwitch " set " Nothing True ( help " Don't set as active version after install " ) )
2022-07-09 21:50:20 +00:00
<*> switch ( long " cabal-update " <> help " Run 'cabal update' before the build " )
2022-07-06 20:49:11 +00:00
<*>
(
( Right <$> option
2021-10-15 20:24:23 +00:00
( eitherReader
( first ( const " Not a valid version " ) . version . T . pack )
)
( short 'o' <> long " overwrite-version " <> metavar " OVERWRITE_VERSION " <> help
" Allows to overwrite the finally installed VERSION with a different one, e.g. when you build 8.10.4 with your own patches, you might want to set this to '8.10.4-p1' "
2023-05-01 09:46:27 +00:00
<> ( completer $ versionCompleter [] HLS )
2021-10-15 20:24:23 +00:00
)
)
2022-07-06 20:49:11 +00:00
<|>
( Left <$> ( switch
( long " git-describe-version "
<> help " Use the output of 'git describe' (if building from git) as the VERSION component of the installed binary. "
)
)
)
)
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, no symlinks to this installation will be made "
2022-03-04 23:46:37 +00:00
<> completer ( bashCompleter " directory " )
2021-10-15 20:24:23 +00:00
)
)
<*> optional
( option
2021-11-12 18:05:13 +00:00
( ( fmap Right $ eitherReader uriParser ) <|> ( fmap Left str ) )
2021-10-15 20:24:23 +00:00
( long " cabal-project " <> metavar " CABAL_PROJECT " <> help
2021-11-12 18:05:13 +00:00
" If relative filepath, specifies the path to cabal.project inside the unpacked HLS tarball/checkout. Otherwise expects a full URI with https/http/file scheme. "
2022-03-04 23:46:37 +00:00
<> completer fileUri
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
( long " cabal-project-local " <> metavar " CABAL_PROJECT_LOCAL " <> help
2021-11-12 18:05:13 +00:00
" URI (https/http/file) to a cabal.project.local to be used for the build. Will be copied over. "
2022-03-04 23:46:37 +00:00
<> completer fileUri
2021-10-15 20:24:23 +00:00
)
)
2021-11-12 18:52:00 +00:00
<*> ( optional
(
( fmap Right $ many $ option
( eitherReader uriParser )
( long " patch " <> metavar " PATCH_URI " <> help
" URI to a patch (https/http/file) "
2022-03-04 23:46:37 +00:00
<> completer fileUri
2021-11-12 18:52:00 +00:00
)
)
<|>
( fmap Left $ option
str
( short 'p' <> long " patchdir " <> metavar " PATCH_DIR " <> help
" Absolute path to patch directory (applies all .patch and .diff files in order using -p1) "
2022-03-04 23:46:37 +00:00
<> completer ( bashCompleter " directory " )
2021-11-12 18:52:00 +00:00
)
2021-10-15 20:24:23 +00:00
)
)
2021-11-12 18:52:00 +00:00
)
2022-01-29 19:02:33 +00:00
<*> some (
2022-07-11 14:05:39 +00:00
option ( eitherReader ghcVersionTagEither )
2022-01-29 19:02:33 +00:00
( long " ghc " <> metavar " GHC_VERSION|TAG " <> help " For which GHC version to compile for (can be specified multiple times) "
<> completer ( tagCompleter GHC [] )
2023-05-01 09:46:27 +00:00
<> completer ( versionCompleter [] GHC ) )
2022-01-29 19:02:33 +00:00
)
2021-11-12 00:13:57 +00:00
<*> many ( argument str ( metavar " CABAL_ARGS " <> help " Additional arguments to cabal install, prefix with '-- ' (longopts) " ) )
2021-10-15 20:24:23 +00:00
---------------------------
--[ Effect interpreters ]--
---------------------------
type GHCEffects = ' [ A l r e a d y I n s t a l l e d
, BuildFailed
, DigestError
2022-12-21 16:31:41 +00:00
, ContentLengthError
2021-10-15 20:24:23 +00:00
, GPGError
, DownloadFailed
, GHCupSetError
, NoDownload
, NotFoundInPATH
, PatchFailed
, UnknownArchive
, TarDirDoesNotExist
, NotInstalled
, DirNotEmpty
, ArchiveResult
, FileDoesNotExistError
, HadrianNotFound
, InvalidBuildConfig
, ProcessError
, CopyError
, BuildFailed
2022-05-12 15:58:40 +00:00
, UninstallFailed
2022-05-19 21:17:58 +00:00
, MergeFileTreeError
2021-10-15 20:24:23 +00:00
]
type HLSEffects = ' [ A l r e a d y I n s t a l l e d
, BuildFailed
, DigestError
2022-12-21 16:31:41 +00:00
, ContentLengthError
2021-10-15 20:24:23 +00:00
, GPGError
, DownloadFailed
, GHCupSetError
, NoDownload
, NotFoundInPATH
, PatchFailed
, UnknownArchive
, TarDirDoesNotExist
, TagNotFound
2023-05-01 09:46:27 +00:00
, DayNotFound
2021-10-15 20:24:23 +00:00
, NextVerNotFound
, NoToolVersionSet
, NotInstalled
, DirNotEmpty
, ArchiveResult
2022-05-12 15:58:40 +00:00
, UninstallFailed
2022-05-19 21:17:58 +00:00
, MergeFileTreeError
2021-10-15 20:24:23 +00:00
]
runCompileGHC :: ( MonadUnliftIO m , MonadIO m )
=> ( ReaderT AppState m ( VEither GHCEffects a ) -> m ( VEither GHCEffects a ) )
-> Excepts GHCEffects ( ResourceT ( ReaderT AppState m ) ) a
-> m ( VEither GHCEffects a )
runCompileGHC runAppState =
runAppState
. runResourceT
. runE
@ GHCEffects
runCompileHLS :: ( MonadUnliftIO m , MonadIO m )
=> ( ReaderT AppState m ( VEither HLSEffects a ) -> m ( VEither HLSEffects a ) )
-> Excepts HLSEffects ( ResourceT ( ReaderT AppState m ) ) a
-> m ( VEither HLSEffects a )
runCompileHLS runAppState =
runAppState
. runResourceT
. runE
@ HLSEffects
------------------
--[ Entrypoint ]--
------------------
compile :: ( Monad m
, MonadMask m
, MonadUnliftIO m
, MonadFail m
)
=> CompileCommand
-> Settings
2021-11-13 21:50:15 +00:00
-> Dirs
2021-10-15 20:24:23 +00:00
-> ( forall eff a . ReaderT AppState m ( VEither eff a ) -> m ( VEither eff a ) )
-> ( ReaderT LeanAppState m () -> m () )
-> m ExitCode
2021-11-13 21:50:15 +00:00
compile compileCommand settings Dirs { .. } runAppState runLogger = do
2021-10-15 20:24:23 +00:00
case compileCommand of
( CompileHLS HLSCompileOptions { .. } ) -> do
runCompileHLS runAppState ( do
case targetHLS of
2022-07-09 21:12:00 +00:00
HLS . SourceDist targetVer -> do
2021-10-15 20:24:23 +00:00
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
2023-07-07 08:41:58 +00:00
let vi = getVersionInfo ( mkTVer targetVer ) HLS dls
2021-10-15 20:24:23 +00:00
forM_ ( _viPreCompile =<< vi ) $ \ msg -> do
lift $ logInfo msg
lift $ logInfo
" ...waiting for 5 seconds, you can still abort... "
liftIO $ threadDelay 5000000 -- for compilation, give the user a sec to intervene
2022-07-09 18:27:55 +00:00
_ -> pure ()
2021-10-15 20:24:23 +00:00
ghcs <- liftE $ forM targetGHCs ( \ ghc -> fmap ( _tvVersion . fst ) . fromVersion ( Just ghc ) $ GHC )
targetVer <- liftE $ compileHLS
targetHLS
ghcs
jobs
ovewrwiteVer
2022-05-11 13:47:08 +00:00
( maybe GHCupInternal IsolateDir isolateDir )
2021-10-15 20:24:23 +00:00
cabalProject
cabalProjectLocal
2022-07-09 21:50:20 +00:00
updateCabal
2021-11-12 18:52:00 +00:00
patches
2021-11-12 00:13:57 +00:00
cabalArgs
2021-10-15 20:24:23 +00:00
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
2023-07-07 08:41:58 +00:00
let vi = getVersionInfo ( mkTVer targetVer ) HLS dls
2021-10-15 20:24:23 +00:00
when setCompile $ void $ liftE $
2022-02-09 17:57:59 +00:00
setHLS targetVer SetHLSOnly Nothing
2021-10-15 20:24:23 +00:00
pure ( vi , targetVer )
)
>>= \ case
VRight ( vi , tv ) -> do
runLogger $ logInfo
" HLS successfully compiled and installed "
forM_ ( _viPostInstall =<< vi ) $ \ msg ->
runLogger $ logInfo msg
liftIO $ putStr ( T . unpack $ prettyVer tv )
pure ExitSuccess
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 "
2021-10-15 20:24:23 +00:00
<> T . pack tmpdir <> " for more clues. " <> " \ n " <>
" Make sure to clean up " <> T . pack tmpdir <> " afterwards. " )
pure $ ExitFailure 9
VLeft e -> do
2022-12-19 16:10:19 +00:00
runLogger $ logError $ T . pack $ prettyHFError e
2021-10-15 20:24:23 +00:00
pure $ ExitFailure 9
( CompileGHC GHCCompileOptions { .. } ) ->
runCompileGHC runAppState ( do
case targetGhc of
2022-07-09 21:12:00 +00:00
GHC . SourceDist targetVer -> do
2021-10-15 20:24:23 +00:00
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
2023-07-07 08:41:58 +00:00
let vi = getVersionInfo ( mkTVer targetVer ) GHC dls
2021-10-15 20:24:23 +00:00
forM_ ( _viPreCompile =<< vi ) $ \ msg -> do
lift $ logInfo msg
lift $ logInfo
" ...waiting for 5 seconds, you can still abort... "
liftIO $ threadDelay 5000000 -- for compilation, give the user a sec to intervene
2022-07-09 21:12:00 +00:00
_ -> pure ()
2021-10-15 20:24:23 +00:00
targetVer <- liftE $ compileGHC
2023-07-04 14:06:03 +00:00
targetGhc
crossTarget
2021-10-15 20:24:23 +00:00
ovewrwiteVer
bootstrapGhc
jobs
buildConfig
2021-11-12 18:52:00 +00:00
patches
2021-10-15 20:24:23 +00:00
addConfArgs
buildFlavour
2023-07-15 11:07:21 +00:00
buildSystem
2022-05-11 13:47:08 +00:00
( maybe GHCupInternal IsolateDir isolateDir )
2021-10-15 20:24:23 +00:00
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
2023-07-07 08:41:58 +00:00
let vi = getVersionInfo targetVer GHC dls
2021-10-15 20:24:23 +00:00
when setCompile $ void $ liftE $
2022-02-09 17:57:59 +00:00
setGHC targetVer SetGHCOnly Nothing
2021-10-15 20:24:23 +00:00
pure ( vi , targetVer )
)
>>= \ case
VRight ( vi , tv ) -> do
runLogger $ logInfo
" GHC successfully compiled and installed "
forM_ ( _viPostInstall =<< vi ) $ \ msg ->
runLogger $ logInfo msg
liftIO $ putStr ( T . unpack $ tVerToText tv )
pure ExitSuccess
VLeft ( V ( AlreadyInstalled _ v ) ) -> do
runLogger $ logWarn $
2022-05-12 11:28:09 +00:00
" GHC ver " <> prettyVer v <> " already installed, remove it first to reinstall "
2021-10-15 20:24:23 +00:00
pure ExitSuccess
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
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 "
2021-10-15 20:24:23 +00:00
<> T . pack tmpdir <> " for more clues. " <> " \ n " <>
" Make sure to clean up " <> T . pack tmpdir <> " afterwards. " )
pure $ ExitFailure 9
VLeft e -> do
2022-12-19 16:10:19 +00:00
runLogger $ logError $ T . pack $ prettyHFError e
2021-10-15 20:24:23 +00:00
pure $ ExitFailure 9