ghcup-hs/lib/GHCup.hs

1376 lines
46 KiB
Haskell
Raw Normal View History

2020-04-09 17:53:22 +00:00
{-# LANGUAGE CPP #-}
2020-01-11 20:15:05 +00:00
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
2020-03-21 21:19:37 +00:00
{-# LANGUAGE OverloadedStrings #-}
2020-01-11 20:15:05 +00:00
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
2020-03-21 21:19:37 +00:00
{-# LANGUAGE TypeFamilies #-}
2020-04-21 21:37:48 +00:00
{-# LANGUAGE ViewPatterns #-}
2020-01-11 20:15:05 +00:00
2020-07-21 23:08:58 +00:00
{-|
Module : GHCup
Description : GHCup installation functions
Copyright : (c) Julian Ospald, 2020
2020-07-30 18:04:02 +00:00
License : LGPL-3.0
2020-07-21 23:08:58 +00:00
Maintainer : hasufell@hasufell.de
Stability : experimental
Portability : POSIX
This module contains the main functions that correspond
to the command line interface, like installation, listing versions
and so on.
These are the entry points.
-}
2020-01-11 20:15:05 +00:00
module GHCup where
import GHCup.Download
import GHCup.Errors
import GHCup.Platform
import GHCup.Types
import GHCup.Types.JSON ( )
import GHCup.Types.Optics
import GHCup.Utils
import GHCup.Utils.File
import GHCup.Utils.Prelude
import GHCup.Utils.String.QQ
import GHCup.Utils.Version.QQ
import GHCup.Version
#if !defined(TAR)
import Codec.Archive ( ArchiveResult )
#endif
2020-01-11 20:15:05 +00:00
import Control.Applicative
import Control.Exception.Safe
import Control.Monad
2020-04-09 17:53:22 +00:00
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail ( MonadFail )
#endif
2020-01-11 20:15:05 +00:00
import Control.Monad.Logger
import Control.Monad.Reader
import Control.Monad.Trans.Resource
hiding ( throwM )
import Data.ByteString ( ByteString )
import Data.Either
2020-01-11 20:15:05 +00:00
import Data.List
import Data.Maybe
import Data.String.Interpolate
2020-04-25 10:06:41 +00:00
import Data.Text ( Text )
import Data.Time.Clock
import Data.Time.Format.ISO8601
2020-01-11 20:15:05 +00:00
import Data.Versions
import Data.Word8
import GHC.IO.Exception
import HPath
import HPath.IO hiding ( hideError )
2020-01-11 20:15:05 +00:00
import Haskus.Utils.Variant.Excepts
import Optics
import Prelude hiding ( abs
, readFile
, writeFile
)
import Safe hiding ( at )
2020-01-11 20:15:05 +00:00
import System.IO.Error
2020-10-30 20:07:49 +00:00
import System.Posix.Env.ByteString ( getEnvironment, getEnv )
import System.Posix.FilePath ( getSearchPath, takeExtension )
2020-04-12 18:22:16 +00:00
import System.Posix.Files.ByteString
import Text.Regex.Posix
2020-01-11 20:15:05 +00:00
import qualified Crypto.Hash.SHA256 as SHA256
import qualified Data.ByteString.Base16 as B16
2020-01-11 20:15:05 +00:00
import qualified Data.ByteString as B
2020-04-25 10:06:41 +00:00
import qualified Data.ByteString.Lazy as BL
2020-01-11 20:15:05 +00:00
import qualified Data.Map.Strict as Map
2020-04-25 10:06:41 +00:00
import qualified Data.Text as T
2020-01-11 20:15:05 +00:00
import qualified Data.Text.Encoding as E
-------------------------
--[ Tool installation ]--
-------------------------
2020-07-21 23:08:58 +00:00
-- | Like 'installGHCBin', except takes the 'DownloadInfo' as
-- argument instead of looking it up from 'GHCupDownloads'.
installGHCBindist :: ( MonadFail m
2020-07-21 23:08:58 +00:00
, MonadMask m
, MonadCatch m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
2020-07-21 23:08:58 +00:00
, MonadLogger m
, MonadResource m
, MonadIO m
)
=> DownloadInfo -- ^ where/how to download
-> Version -- ^ the version to install
-> PlatformRequest -- ^ the platform to install on
-> Excepts
'[ AlreadyInstalled
, BuildFailed
, DigestError
, DownloadFailed
, NoDownload
, NotInstalled
, UnknownArchive
2020-08-06 11:28:20 +00:00
, TarDirDoesNotExist
#if !defined(TAR)
2020-07-21 23:08:58 +00:00
, ArchiveResult
#endif
2020-07-21 23:08:58 +00:00
]
m
()
installGHCBindist dlinfo ver pfreq = do
2021-03-11 16:03:51 +00:00
let tver = mkTVer ver
2020-01-11 20:15:05 +00:00
lift $ $(logDebug) [i|Requested to install GHC with #{ver}|]
2021-03-11 16:03:51 +00:00
whenM (lift $ ghcInstalled tver) (throwE $ AlreadyInstalled GHC ver)
2020-01-11 20:15:05 +00:00
-- download (or use cached version)
2020-04-22 16:12:40 +00:00
dl <- liftE $ downloadCached dlinfo Nothing
2020-01-11 20:15:05 +00:00
-- prepare paths
ghcdir <- lift $ ghcupGHCDir tver
2020-01-11 20:15:05 +00:00
2020-10-30 20:07:49 +00:00
toolchainSanityChecks
liftE $ installPackedGHC dl (view dlSubdir dlinfo) ghcdir ver pfreq
2020-01-11 20:15:05 +00:00
2020-04-25 10:06:41 +00:00
liftE $ postGHCInstall tver
2020-01-11 20:15:05 +00:00
2020-10-30 20:07:49 +00:00
where
toolchainSanityChecks = do
r <- forM ["CC", "LD"] (liftIO . getEnv)
case catMaybes r of
[] -> pure ()
_ -> do
lift $ $(logWarn) "CC/LD environment variable is set. This will change the compiler/linker"
lift $ $(logWarn) "GHC uses internally and can cause defunct GHC in some cases (e.g. in Anaconda"
lift $ $(logWarn) "environments). If you encounter problems, unset CC and LD and reinstall."
-- | Install a packed GHC distribution. This only deals with unpacking and the GHC
-- build system and nothing else.
installPackedGHC :: ( MonadMask m
, MonadCatch m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
, MonadThrow m
, MonadLogger m
, MonadIO m
)
=> Path Abs -- ^ Path to the packed GHC bindist
-> Maybe TarDir -- ^ Subdir of the archive
-> Path Abs -- ^ Path to install to
-> Version -- ^ The GHC version
-> PlatformRequest
-> Excepts
'[ BuildFailed
, UnknownArchive
, TarDirDoesNotExist
#if !defined(TAR)
, ArchiveResult
#endif
] m ()
2021-03-11 16:03:51 +00:00
installPackedGHC dl msubdir inst ver pfreq@PlatformRequest{..} = do
-- unpack
tmpUnpack <- lift mkGhcupTmpDir
liftE $ unpackToDir tmpUnpack dl
void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
2020-01-11 20:15:05 +00:00
-- the subdir of the archive where we do the work
workdir <- maybe (pure tmpUnpack)
(liftE . intoSubdir tmpUnpack)
2021-03-11 16:03:51 +00:00
msubdir
liftE $ runBuildAction tmpUnpack
(Just inst)
(installUnpackedGHC workdir inst ver pfreq)
-- | Install an unpacked GHC distribution. This only deals with the GHC
-- build system and nothing else.
2020-10-23 23:06:53 +00:00
installUnpackedGHC :: ( MonadReader AppState m
, MonadThrow m
, MonadLogger m
, MonadIO m
)
=> Path Abs -- ^ Path to the unpacked GHC bindist (where the configure script resides)
-> Path Abs -- ^ Path to install to
-> Version -- ^ The GHC version
-> PlatformRequest
-> Excepts '[ProcessError] m ()
2021-03-11 16:03:51 +00:00
installUnpackedGHC path inst ver PlatformRequest{..} = do
lift $ $(logInfo) "Installing GHC (this may take a while)"
lEM $ execLogged "./configure"
False
2021-03-11 16:03:51 +00:00
(("--prefix=" <> toFilePath inst) : alpineArgs)
[rel|ghc-configure|]
(Just path)
Nothing
lEM $ make ["install"] (Just path)
pure ()
where
alpineArgs
| ver >= [vver|8.2.2|], Linux Alpine <- _rPlatform
= ["--disable-ld-override"]
| otherwise
= []
2020-01-11 20:15:05 +00:00
2020-07-21 23:08:58 +00:00
-- | Installs GHC into @~\/.ghcup\/ghc/\<ver\>@ and places the
-- following symlinks in @~\/.ghcup\/bin@:
--
-- * @ghc-x.y.z -> ..\/ghc\/x.y.z\/bin/ghc@
-- * @ghc-x.y -> ..\/ghc\/x.y.z\/bin/ghc@ (if x.y.z is the latest x.y version)
installGHCBin :: ( MonadFail m
, MonadMask m
, MonadCatch m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
, MonadLogger m
, MonadResource m
, MonadIO m
)
2020-07-21 23:08:58 +00:00
=> GHCupDownloads -- ^ the download info to look up the tarball from
-> Version -- ^ the version to install
-> PlatformRequest -- ^ the platform to install on
-> Excepts
'[ AlreadyInstalled
, BuildFailed
, DigestError
, DownloadFailed
, NoDownload
, NotInstalled
, UnknownArchive
2020-08-06 11:28:20 +00:00
, TarDirDoesNotExist
#if !defined(TAR)
, ArchiveResult
#endif
]
m
()
installGHCBin bDls ver pfreq = do
dlinfo <- lE $ getDownloadInfo GHC ver pfreq bDls
installGHCBindist dlinfo ver pfreq
2020-07-21 23:08:58 +00:00
-- | Like 'installCabalBin', except takes the 'DownloadInfo' as
-- argument instead of looking it up from 'GHCupDownloads'.
installCabalBindist :: ( MonadMask m
, MonadCatch m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
, MonadLogger m
, MonadResource m
, MonadIO m
, MonadFail m
)
=> DownloadInfo
-> Version
-> PlatformRequest
-> Excepts
'[ AlreadyInstalled
, CopyError
, DigestError
, DownloadFailed
, NoDownload
, NotInstalled
, UnknownArchive
2020-08-06 11:28:20 +00:00
, TarDirDoesNotExist
#if !defined(TAR)
, ArchiveResult
#endif
]
m
()
2021-03-11 16:03:51 +00:00
installCabalBindist dlinfo ver PlatformRequest {..} = do
2020-01-11 20:15:05 +00:00
lift $ $(logDebug) [i|Requested to install cabal version #{ver}|]
2020-10-23 23:06:53 +00:00
AppState {dirs = Dirs {..}} <- lift ask
whenM
(lift (cabalInstalled ver) >>= \a -> liftIO $
handleIO (\_ -> pure False)
$ fmap (\x -> a && isSymbolicLink x)
-- ignore when the installation is a legacy cabal (binary, not symlink)
$ getSymbolicLinkStatus (toFilePath (binDir </> [rel|cabal|]))
)
2021-03-11 16:03:51 +00:00
(throwE $ AlreadyInstalled Cabal ver)
2020-01-11 20:15:05 +00:00
-- download (or use cached version)
2020-04-25 10:06:41 +00:00
dl <- liftE $ downloadCached dlinfo Nothing
2020-01-11 20:15:05 +00:00
-- unpack
2020-04-25 10:06:41 +00:00
tmpUnpack <- lift withGHCupTmpDir
2020-01-11 20:15:05 +00:00
liftE $ unpackToDir tmpUnpack dl
2020-04-10 17:27:17 +00:00
void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
2020-01-11 20:15:05 +00:00
-- the subdir of the archive where we do the work
2020-08-06 11:28:20 +00:00
workdir <- maybe (pure tmpUnpack) (liftE . intoSubdir tmpUnpack) (view dlSubdir dlinfo)
2020-01-11 20:15:05 +00:00
liftE $ installCabal' workdir binDir
-- create symlink if this is the latest version
2021-03-11 16:03:51 +00:00
cVers <- lift $ fmap rights getInstalledCabals
let lInstCabal = headMay . reverse . sort $ cVers
when (maybe True (ver >=) lInstCabal) $ liftE $ setCabal ver
2020-01-11 20:15:05 +00:00
where
2020-04-26 09:55:20 +00:00
-- | Install an unpacked cabal distribution.
2020-01-11 20:15:05 +00:00
installCabal' :: (MonadLogger m, MonadCatch m, MonadIO m)
=> Path Abs -- ^ Path to the unpacked cabal bindist (where the executable resides)
-> Path Abs -- ^ Path to install to
-> Excepts '[CopyError] m ()
installCabal' path inst = do
2020-03-21 21:19:37 +00:00
lift $ $(logInfo) "Installing cabal"
2020-03-16 09:47:09 +00:00
let cabalFile = [rel|cabal|]
liftIO $ createDirRecursive' inst
destFileName <- lift $ parseRel (toFilePath cabalFile <> "-" <> verToBS ver)
2020-08-14 20:07:39 +00:00
let destPath = inst </> destFileName
2020-01-11 20:15:05 +00:00
handleIO (throwE . CopyError . show) $ liftIO $ copyFile
(path </> cabalFile)
2021-03-11 16:03:51 +00:00
destPath
2020-01-11 20:15:05 +00:00
Overwrite
2020-12-19 17:27:27 +00:00
lift $ chmod_755 destPath
2020-01-11 20:15:05 +00:00
2020-07-22 00:34:17 +00:00
-- | Installs cabal into @~\/.ghcup\/bin/cabal-\<ver\>@ and
2020-07-21 23:08:58 +00:00
-- creates a default @cabal -> cabal-x.y.z.q@ symlink for
-- the latest installed version.
installCabalBin :: ( MonadMask m
, MonadCatch m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
, MonadLogger m
, MonadResource m
, MonadIO m
, MonadFail m
)
=> GHCupDownloads
-> Version
-> PlatformRequest
-> Excepts
'[ AlreadyInstalled
, CopyError
, DigestError
, DownloadFailed
, NoDownload
, NotInstalled
, UnknownArchive
2020-08-06 11:28:20 +00:00
, TarDirDoesNotExist
#if !defined(TAR)
, ArchiveResult
#endif
]
m
()
2020-07-21 20:42:39 +00:00
installCabalBin bDls ver pfreq = do
2020-07-21 21:10:47 +00:00
dlinfo <- lE $ getDownloadInfo Cabal ver pfreq bDls
installCabalBindist dlinfo ver pfreq
-- | Like 'installHLSBin, except takes the 'DownloadInfo' as
-- argument instead of looking it up from 'GHCupDownloads'.
installHLSBindist :: ( MonadMask m
, MonadCatch m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
, MonadLogger m
, MonadResource m
, MonadIO m
, MonadFail m
)
=> DownloadInfo
-> Version
-> PlatformRequest
-> Excepts
'[ AlreadyInstalled
, CopyError
, DigestError
, DownloadFailed
, NoDownload
, NotInstalled
, UnknownArchive
, TarDirDoesNotExist
#if !defined(TAR)
, ArchiveResult
#endif
]
m
()
2021-03-11 16:03:51 +00:00
installHLSBindist dlinfo ver PlatformRequest{..} = do
lift $ $(logDebug) [i|Requested to install hls version #{ver}|]
2020-10-23 23:06:53 +00:00
AppState {dirs = Dirs {..}} <- lift ask
whenM (lift (hlsInstalled ver))
2021-03-11 16:03:51 +00:00
(throwE $ AlreadyInstalled HLS ver)
-- download (or use cached version)
dl <- liftE $ downloadCached dlinfo Nothing
-- unpack
tmpUnpack <- lift withGHCupTmpDir
liftE $ unpackToDir tmpUnpack dl
void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
-- the subdir of the archive where we do the work
workdir <- maybe (pure tmpUnpack) (liftE . intoSubdir tmpUnpack) (view dlSubdir dlinfo)
liftE $ installHLS' workdir binDir
-- create symlink if this is the latest version
2021-03-11 16:03:51 +00:00
hlsVers <- lift $ fmap rights getInstalledHLSs
let lInstHLS = headMay . reverse . sort $ hlsVers
when (maybe True (ver >=) lInstHLS) $ liftE $ setHLS ver
where
-- | Install an unpacked hls distribution.
installHLS' :: (MonadFail m, MonadLogger m, MonadCatch m, MonadIO m)
=> Path Abs -- ^ Path to the unpacked hls bindist (where the executable resides)
-> Path Abs -- ^ Path to install to
-> Excepts '[CopyError] m ()
installHLS' path inst = do
lift $ $(logInfo) "Installing HLS"
liftIO $ createDirRecursive' inst
-- install haskell-language-server-<ghcver>
bins@(_:_) <- liftIO $ findFiles
path
(makeRegexOpts compExtended
execBlank
([s|^haskell-language-server-[0-9].*$|] :: ByteString)
)
forM_ bins $ \f -> do
toF <- parseRel (toFilePath f <> "~" <> verToBS ver)
handleIO (throwE . CopyError . show) $ liftIO $ copyFile
(path </> f)
(inst </> toF)
Overwrite
2020-12-19 17:27:27 +00:00
lift $ chmod_755 (inst </> toF)
-- install haskell-language-server-wrapper
let wrapper = [rel|haskell-language-server-wrapper|]
toF <- parseRel (toFilePath wrapper <> "-" <> verToBS ver)
handleIO (throwE . CopyError . show) $ liftIO $ copyFile
(path </> wrapper)
(inst </> toF)
Overwrite
2020-12-19 17:27:27 +00:00
lift $ chmod_755 (inst </> toF)
-- | Installs hls binaries @haskell-language-server-\<ghcver\>@
-- into @~\/.ghcup\/bin/@, as well as @haskell-languager-server-wrapper@.
installHLSBin :: ( MonadMask m
, MonadCatch m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
, MonadLogger m
, MonadResource m
, MonadIO m
, MonadFail m
)
=> GHCupDownloads
-> Version
-> PlatformRequest
-> Excepts
'[ AlreadyInstalled
, CopyError
, DigestError
, DownloadFailed
, NoDownload
, NotInstalled
, UnknownArchive
, TarDirDoesNotExist
#if !defined(TAR)
, ArchiveResult
#endif
]
m
()
installHLSBin bDls ver pfreq = do
dlinfo <- lE $ getDownloadInfo HLS ver pfreq bDls
installHLSBindist dlinfo ver pfreq
2020-01-11 20:15:05 +00:00
---------------------
--[ Set GHC/cabal ]--
---------------------
2020-01-11 20:15:05 +00:00
2020-07-21 23:08:58 +00:00
-- | Set GHC symlinks in @~\/.ghcup\/bin@ for the requested GHC version. The behavior depends
2020-01-11 20:15:05 +00:00
-- on `SetGHC`:
--
2020-07-21 23:08:58 +00:00
-- * SetGHCOnly: @~\/.ghcup\/bin\/ghc -> ~\/.ghcup\/ghc\/\<ver\>\/bin\/ghc@
-- * SetGHC_XY: @~\/.ghcup\/bin\/ghc-X.Y -> ~\/.ghcup\/ghc\/\<ver\>\/bin\/ghc@
-- * SetGHC_XYZ: @~\/.ghcup\/bin\/ghc-\<ver\> -> ~\/.ghcup\/ghc\/\<ver\>\/bin\/ghc@
2020-01-11 20:15:05 +00:00
--
2020-07-21 23:08:58 +00:00
-- Additionally creates a @~\/.ghcup\/share -> ~\/.ghcup\/ghc\/\<ver\>\/share symlink@
-- for 'SetGHCOnly' constructor.
2020-10-23 23:06:53 +00:00
setGHC :: ( MonadReader AppState m
2020-08-06 11:28:20 +00:00
, MonadLogger m
, MonadThrow m
, MonadFail m
, MonadIO m
, MonadCatch m
)
2020-04-25 10:06:41 +00:00
=> GHCTargetVersion
2020-01-11 20:15:05 +00:00
-> SetGHC
2020-04-25 10:06:41 +00:00
-> Excepts '[NotInstalled] m GHCTargetVersion
2020-01-11 20:15:05 +00:00
setGHC ver sghc = do
2020-04-25 10:06:41 +00:00
let verBS = verToBS (_tvVersion ver)
2020-08-06 11:28:20 +00:00
ghcdir <- lift $ ghcupGHCDir ver
2020-01-11 20:15:05 +00:00
2021-03-11 16:03:51 +00:00
whenM (lift $ not <$> ghcInstalled ver) (throwE (NotInstalled GHC ver))
2020-01-11 20:15:05 +00:00
-- symlink destination
2020-10-23 23:06:53 +00:00
AppState { dirs = Dirs {..} } <- lift ask
liftIO $ createDirRecursive' binDir
2020-01-11 20:15:05 +00:00
-- first delete the old symlinks (this fixes compatibility issues
-- with old ghcup)
case sghc of
2020-04-25 10:06:41 +00:00
SetGHCOnly -> liftE $ rmPlain (_tvTarget ver)
SetGHC_XY -> liftE $ rmMajorSymlinks ver
SetGHC_XYZ -> liftE $ rmMinorSymlinks ver
2020-01-11 20:15:05 +00:00
-- for ghc tools (ghc, ghci, haddock, ...)
verfiles <- ghcToolFiles ver
forM_ verfiles $ \file -> do
2020-08-06 11:28:20 +00:00
mTargetFile <- case sghc of
SetGHCOnly -> pure $ Just file
2020-01-11 20:15:05 +00:00
SetGHC_XY -> do
2020-08-06 11:28:20 +00:00
v' <-
handle
(\(e :: ParseError) -> lift $ $(logWarn) [i|#{e}|] >> pure Nothing)
$ fmap Just
$ getMajorMinorV (_tvVersion ver)
forM v' $ \(mj, mi) ->
let major' = E.encodeUtf8 $ intToText mj <> "." <> intToText mi
in parseRel (toFilePath file <> B.singleton _hyphen <> major')
SetGHC_XYZ ->
fmap Just $ parseRel (toFilePath file <> B.singleton _hyphen <> verBS)
2020-01-11 20:15:05 +00:00
-- create symlink
2020-08-06 11:28:20 +00:00
forM mTargetFile $ \targetFile -> do
let fullF = binDir </> targetFile
destL <- lift $ ghcLinkDestination (toFilePath file) ver
lift $ $(logDebug) [i|ln -s #{destL} #{toFilePath fullF}|]
liftIO $ createSymlink fullF destL
2020-01-11 20:15:05 +00:00
-- create symlink for share dir
2020-04-25 10:06:41 +00:00
when (isNothing . _tvTarget $ ver) $ lift $ symlinkShareDir ghcdir verBS
2020-01-11 20:15:05 +00:00
pure ver
2020-01-11 20:15:05 +00:00
where
2020-10-23 23:06:53 +00:00
symlinkShareDir :: (MonadReader AppState m, MonadIO m, MonadLogger m)
2020-01-11 20:15:05 +00:00
=> Path Abs
-> ByteString
-> m ()
symlinkShareDir ghcdir verBS = do
2020-10-23 23:06:53 +00:00
AppState { dirs = Dirs {..} } <- ask
let destdir = baseDir
2020-01-11 20:15:05 +00:00
case sghc of
SetGHCOnly -> do
2020-03-16 09:47:09 +00:00
let sharedir = [rel|share|]
2020-01-11 20:15:05 +00:00
let fullsharedir = ghcdir </> sharedir
whenM (liftIO $ doesDirectoryExist fullsharedir) $ do
let fullF = destdir </> sharedir
2020-03-21 21:19:37 +00:00
let targetF = "./ghc/" <> verBS <> "/" <> toFilePath sharedir
2020-01-11 20:15:05 +00:00
$(logDebug) [i|rm -f #{fullF}|]
liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
$(logDebug) [i|ln -s #{targetF} #{fullF}|]
liftIO $ createSymlink fullF targetF
_ -> pure ()
2020-07-21 23:08:58 +00:00
-- | Set the @~\/.ghcup\/bin\/cabal@ symlink.
2020-10-23 23:06:53 +00:00
setCabal :: (MonadReader AppState m, MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
=> Version
-> Excepts '[NotInstalled] m ()
setCabal ver = do
let verBS = verToBS ver
targetFile <- parseRel ("cabal-" <> verBS)
-- symlink destination
2020-10-23 23:06:53 +00:00
AppState {dirs = Dirs {..}} <- lift ask
liftIO $ createDirRecursive' binDir
2021-03-11 16:03:51 +00:00
whenM (liftIO $ not <$> doesFileExist (binDir </> targetFile))
$ throwE
$ NotInstalled Cabal (GHCTargetVersion Nothing ver)
let cabalbin = binDir </> [rel|cabal|]
-- delete old file (may be binary or symlink)
lift $ $(logDebug) [i|rm -f #{toFilePath cabalbin}|]
liftIO $ hideError doesNotExistErrorType $ deleteFile
cabalbin
-- create symlink
let destL = toFilePath targetFile
lift $ $(logDebug) [i|ln -s #{destL} #{toFilePath cabalbin}|]
liftIO $ createSymlink cabalbin destL
pure ()
-- | Set the haskell-language-server symlinks.
setHLS :: ( MonadCatch m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
, MonadLogger m
, MonadThrow m
, MonadFail m
, MonadIO m
)
=> Version
-> Excepts '[NotInstalled] m ()
setHLS ver = do
2020-10-23 23:06:53 +00:00
AppState { dirs = Dirs {..} } <- lift ask
liftIO $ createDirRecursive' binDir
-- Delete old symlinks, since these might have different ghc versions than the
-- selected version, so we could end up with stray or incorrect symlinks.
oldSyms <- lift hlsSymlinks
forM_ oldSyms $ \f -> do
lift $ $(logDebug) [i|rm #{toFilePath (binDir </> f)}|]
liftIO $ deleteFile (binDir </> f)
-- set haskell-language-server-<ghcver> symlinks
bins <- lift $ hlsServerBinaries ver
2021-03-11 16:03:51 +00:00
when (null bins) $ throwE $ NotInstalled HLS (GHCTargetVersion Nothing ver)
forM_ bins $ \f -> do
let destL = toFilePath f
target <- parseRel . head . B.split _tilde . toFilePath $ f
lift $ $(logDebug) [i|rm -f #{toFilePath (binDir </> target)}|]
liftIO $ hideError doesNotExistErrorType $ deleteFile (binDir </> target)
lift $ $(logDebug) [i|ln -s #{destL} #{toFilePath (binDir </> target)}|]
liftIO $ createSymlink (binDir </> target) destL
-- set haskell-language-server-wrapper symlink
let destL = "haskell-language-server-wrapper-" <> verToBS ver
let wrapper = binDir </> [rel|haskell-language-server-wrapper|]
lift $ $(logDebug) [i|rm -f #{toFilePath wrapper}|]
liftIO $ hideError doesNotExistErrorType $ deleteFile wrapper
lift $ $(logDebug) [i|ln -s #{destL} #{toFilePath wrapper}|]
liftIO $ createSymlink wrapper destL
pure ()
2020-01-11 20:15:05 +00:00
------------------
--[ List tools ]--
------------------
2020-07-21 23:08:58 +00:00
-- | Filter data type for 'listVersions'.
2020-01-11 20:15:05 +00:00
data ListCriteria = ListInstalled
| ListSet
deriving Show
2020-07-21 23:08:58 +00:00
-- | A list result describes a single tool version
-- and various of its properties.
2020-01-11 20:15:05 +00:00
data ListResult = ListResult
{ lTool :: Tool
, lVer :: Version
2020-04-25 10:06:41 +00:00
, lCross :: Maybe Text -- ^ currently only for GHC
2020-01-11 20:15:05 +00:00
, lTag :: [Tag]
, lInstalled :: Bool
2020-04-21 21:37:48 +00:00
, lSet :: Bool -- ^ currently active version
, fromSrc :: Bool -- ^ compiled from source
, lStray :: Bool -- ^ not in download info
, lNoBindist :: Bool -- ^ whether the version is available for this platform/arch
, hlsPowered :: Bool
2020-01-11 20:15:05 +00:00
}
2020-04-21 21:37:48 +00:00
deriving (Eq, Ord, Show)
2020-01-11 20:15:05 +00:00
2020-07-21 23:08:58 +00:00
-- | Extract all available tool versions and their tags.
2020-04-21 21:37:48 +00:00
availableToolVersions :: GHCupDownloads -> Tool -> Map.Map Version [Tag]
availableToolVersions av tool = view
2021-03-11 16:03:51 +00:00
(at tool % non Map.empty % to (fmap _viTags))
2020-01-11 20:15:05 +00:00
av
2020-04-21 21:37:48 +00:00
-- | List all versions from the download info, as well as stray
-- versions.
listVersions :: ( MonadCatch m
, MonadLogger m
, MonadThrow m
, MonadLogger m
, MonadIO m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
)
2020-04-21 21:37:48 +00:00
=> GHCupDownloads
2020-01-11 20:15:05 +00:00
-> Maybe Tool
-> Maybe ListCriteria
2020-07-13 16:27:21 +00:00
-> PlatformRequest
-> m [ListResult]
listVersions av lt' criteria pfreq = do
-- some annoying work to avoid too much repeated IO
cSet <- cabalSet
cabals <- getInstalledCabals' cSet
hlsSet' <- hlsSet
hlses <- getInstalledHLSs
go lt' cSet cabals hlsSet' hlses
2020-01-11 20:15:05 +00:00
where
go lt cSet cabals hlsSet' hlses = do
case lt of
Just t -> do
-- get versions from GHCupDownloads
let avTools = availableToolVersions av t
lr <- filter' <$> forM (Map.toList avTools) (toListResult t cSet cabals hlsSet' hlses)
case t of
GHC -> do
slr <- strayGHCs avTools
pure (sort (slr ++ lr))
Cabal -> do
slr <- strayCabals avTools cSet cabals
pure (sort (slr ++ lr))
HLS -> do
slr <- strayHLS avTools
pure (sort (slr ++ lr))
GHCup -> pure lr
Nothing -> do
ghcvers <- go (Just GHC) cSet cabals hlsSet' hlses
cabalvers <- go (Just Cabal) cSet cabals hlsSet' hlses
hlsvers <- go (Just HLS) cSet cabals hlsSet' hlses
ghcupvers <- go (Just GHCup) cSet cabals hlsSet' hlses
pure (ghcvers <> cabalvers <> hlsvers <> ghcupvers)
2020-10-23 23:06:53 +00:00
strayGHCs :: (MonadCatch m, MonadReader AppState m, MonadThrow m, MonadLogger m, MonadIO m)
2020-04-21 21:37:48 +00:00
=> Map.Map Version [Tag]
-> m [ListResult]
strayGHCs avTools = do
2020-04-25 10:06:41 +00:00
ghcs <- getInstalledGHCs
fmap catMaybes $ forM ghcs $ \case
Right tver@GHCTargetVersion{ _tvTarget = Nothing, .. } -> do
case Map.lookup _tvVersion avTools of
Just _ -> pure Nothing
Nothing -> do
lSet <- fmap (maybe False (\(GHCTargetVersion _ v ) -> v == _tvVersion)) $ ghcSet Nothing
fromSrc <- ghcSrcInstalled tver
2021-03-11 16:03:51 +00:00
hlsPowered <- fmap (elem _tvVersion) hlsGHCVersions
2020-04-25 10:06:41 +00:00
pure $ Just $ ListResult
{ lTool = GHC
, lVer = _tvVersion
, lCross = Nothing
, lTag = []
, lInstalled = True
2021-03-11 16:03:51 +00:00
, lStray = isNothing (Map.lookup _tvVersion avTools)
, lNoBindist = False
2020-04-25 10:06:41 +00:00
, ..
}
Right tver@GHCTargetVersion{ .. } -> do
lSet <- fmap (maybe False (\(GHCTargetVersion _ v ) -> v == _tvVersion)) $ ghcSet _tvTarget
fromSrc <- ghcSrcInstalled tver
2021-03-11 16:03:51 +00:00
hlsPowered <- fmap (elem _tvVersion) hlsGHCVersions
2020-04-25 10:06:41 +00:00
pure $ Just $ ListResult
{ lTool = GHC
, lVer = _tvVersion
, lCross = _tvTarget
, lTag = []
, lInstalled = True
, lStray = True -- NOTE: cross currently cannot be installed via bindist
, lNoBindist = False
2020-04-25 10:06:41 +00:00
, ..
}
Left e -> do
$(logWarn)
[i|Could not parse version of stray directory #{toFilePath e}|]
pure Nothing
2020-10-23 23:06:53 +00:00
strayCabals :: (MonadReader AppState m, MonadCatch m, MonadThrow m, MonadLogger m, MonadIO m)
2020-08-14 14:53:32 +00:00
=> Map.Map Version [Tag]
-> Maybe Version
-> [Either (Path Rel) Version]
2020-08-14 14:53:32 +00:00
-> m [ListResult]
strayCabals avTools cSet cabals = do
2020-08-14 14:53:32 +00:00
fmap catMaybes $ forM cabals $ \case
Right ver ->
case Map.lookup ver avTools of
Just _ -> pure Nothing
Nothing -> do
let lSet = cSet == Just ver
2020-08-14 14:53:32 +00:00
pure $ Just $ ListResult
{ lTool = Cabal
, lVer = ver
, lCross = Nothing
, lTag = []
, lInstalled = True
2021-03-11 16:03:51 +00:00
, lStray = isNothing (Map.lookup ver avTools)
2020-08-14 14:53:32 +00:00
, lNoBindist = False
, fromSrc = False -- actually, we don't know :>
, hlsPowered = False
, ..
}
Left e -> do
$(logWarn)
[i|Could not parse version of stray directory #{toFilePath e}|]
pure Nothing
2020-10-23 23:06:53 +00:00
strayHLS :: (MonadReader AppState m, MonadCatch m, MonadThrow m, MonadLogger m, MonadIO m)
=> Map.Map Version [Tag]
-> m [ListResult]
strayHLS avTools = do
hlss <- getInstalledHLSs
fmap catMaybes $ forM hlss $ \case
Right ver ->
case Map.lookup ver avTools of
Just _ -> pure Nothing
Nothing -> do
2021-03-11 16:03:51 +00:00
lSet <- fmap (== Just ver) hlsSet
pure $ Just $ ListResult
{ lTool = HLS
, lVer = ver
, lCross = Nothing
, lTag = []
, lInstalled = True
2021-03-11 16:03:51 +00:00
, lStray = isNothing (Map.lookup ver avTools)
, lNoBindist = False
, fromSrc = False -- actually, we don't know :>
, hlsPowered = False
2020-08-14 14:53:32 +00:00
, ..
}
Left e -> do
$(logWarn)
[i|Could not parse version of stray directory #{toFilePath e}|]
pure Nothing
2020-04-25 10:06:41 +00:00
-- NOTE: this are not cross ones, because no bindists
toListResult :: (MonadLogger m, MonadReader AppState m, MonadIO m, MonadCatch m)
=> Tool
-> Maybe Version
-> [Either (Path Rel) Version]
-> Maybe Version
-> [Either (Path Rel) Version]
-> (Version, [Tag])
-> m ListResult
toListResult t cSet cabals hlsSet' hlses (v, tags) = case t of
2020-01-11 20:15:05 +00:00
GHC -> do
let lNoBindist = isLeft $ getDownloadInfo GHC v pfreq av
2020-04-25 10:06:41 +00:00
let tver = mkTVer v
lSet <- fmap (maybe False (\(GHCTargetVersion _ v') -> v' == v)) $ ghcSet Nothing
lInstalled <- ghcInstalled tver
fromSrc <- ghcSrcInstalled tver
2021-03-11 16:03:51 +00:00
hlsPowered <- fmap (elem v) hlsGHCVersions
2020-04-25 10:06:41 +00:00
pure ListResult { lVer = v, lCross = Nothing , lTag = tags, lTool = t, lStray = False, .. }
2020-01-11 20:15:05 +00:00
Cabal -> do
let lNoBindist = isLeft $ getDownloadInfo Cabal v pfreq av
let lSet = cSet == Just v
let lInstalled = elem v $ rights cabals
2020-04-21 21:37:48 +00:00
pure ListResult { lVer = v
2020-04-25 10:06:41 +00:00
, lCross = Nothing
2020-04-21 21:37:48 +00:00
, lTag = tags
, lTool = t
, fromSrc = False
, lStray = False
, hlsPowered = False
2020-04-21 21:37:48 +00:00
, ..
}
2020-01-11 20:15:05 +00:00
GHCup -> do
let lSet = prettyPVP ghcUpVer == prettyVer v
2020-03-16 09:49:34 +00:00
let lInstalled = lSet
2020-04-21 21:37:48 +00:00
pure ListResult { lVer = v
, lTag = tags
2020-04-25 10:06:41 +00:00
, lCross = Nothing
2020-04-21 21:37:48 +00:00
, lTool = t
, fromSrc = False
, lStray = False
, lNoBindist = False
, hlsPowered = False
, ..
}
HLS -> do
let lNoBindist = isLeft $ getDownloadInfo HLS v pfreq av
let lSet = hlsSet' == Just v
let lInstalled = elem v $ rights hlses
pure ListResult { lVer = v
, lCross = Nothing
, lTag = tags
, lTool = t
, fromSrc = False
, lStray = False
, hlsPowered = False
2020-04-21 21:37:48 +00:00
, ..
}
2020-01-11 20:15:05 +00:00
filter' :: [ListResult] -> [ListResult]
filter' lr = case criteria of
Nothing -> lr
Just ListInstalled -> filter (\ListResult {..} -> lInstalled) lr
Just ListSet -> filter (\ListResult {..} -> lSet) lr
--------------------
--[ GHC/cabal rm ]--
--------------------
2020-01-11 20:15:05 +00:00
2020-07-21 23:08:58 +00:00
-- | Delete a ghc version and all its symlinks.
--
-- This may leave GHCup without a "set" version.
-- Will try to fix the ghc-x.y symlink after removal (e.g. to an
-- older version).
2020-10-23 23:06:53 +00:00
rmGHCVer :: ( MonadReader AppState m
2020-08-06 11:28:20 +00:00
, MonadThrow m
, MonadLogger m
, MonadIO m
, MonadFail m
, MonadCatch m
)
2020-04-25 10:06:41 +00:00
=> GHCTargetVersion
2020-01-11 20:15:05 +00:00
-> Excepts '[NotInstalled] m ()
rmGHCVer ver = do
2021-03-11 16:03:51 +00:00
isSetGHC <- lift $ fmap (== Just ver) $ ghcSet (_tvTarget ver)
whenM (lift $ fmap not $ ghcInstalled ver) (throwE (NotInstalled GHC ver))
dir <- lift $ ghcupGHCDir ver
-- this isn't atomic, order matters
when isSetGHC $ do
lift $ $(logInfo) [i|Removing ghc symlinks|]
liftE $ rmPlain (_tvTarget ver)
lift $ $(logInfo) [i|Removing ghc-x.y.z symlinks|]
liftE $ rmMinorSymlinks ver
lift $ $(logInfo) [i|Removing/rewiring ghc-x.y symlinks|]
-- first remove
handle (\(_ :: ParseError) -> pure ()) $ liftE $ rmMajorSymlinks ver
-- then fix them (e.g. with an earlier version)
lift $ $(logInfo) [i|Removing directory recursively: #{toFilePath dir}|]
liftIO $ deleteDirRecursive dir
v' <-
handle
(\(e :: ParseError) -> lift $ $(logWarn) [i|#{e}|] >> pure Nothing)
$ fmap Just
$ getMajorMinorV (_tvVersion ver)
forM_ v' $ \(mj, mi) -> lift (getGHCForMajor mj mi (_tvTarget ver))
>>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
2020-10-23 23:06:53 +00:00
AppState { dirs = Dirs {..} } <- lift ask
liftIO
$ hideError doesNotExistErrorType
2021-03-11 16:03:51 +00:00
$ deleteFile (baseDir </> [rel|share|])
2020-01-11 20:15:05 +00:00
2020-07-21 23:08:58 +00:00
-- | Delete a cabal version. Will try to fix the @cabal@ symlink
-- after removal (e.g. setting it to an older version).
2020-10-23 23:06:53 +00:00
rmCabalVer :: (MonadReader AppState m, MonadThrow m, MonadLogger m, MonadIO m, MonadFail m, MonadCatch m)
=> Version
-> Excepts '[NotInstalled] m ()
rmCabalVer ver = do
whenM (lift $ fmap not $ cabalInstalled ver) $ throwE (NotInstalled Cabal (GHCTargetVersion Nothing ver))
2021-03-11 16:03:51 +00:00
cSet <- lift cabalSet
2020-10-23 23:06:53 +00:00
AppState {dirs = Dirs {..}} <- lift ask
cabalFile <- lift $ parseRel ("cabal-" <> verToBS ver)
liftIO $ hideError doesNotExistErrorType $ deleteFile (binDir </> cabalFile)
2021-03-11 16:03:51 +00:00
when (Just ver == cSet) $ do
cVers <- lift $ fmap rights getInstalledCabals
case headMay . reverse . sort $ cVers of
Just latestver -> setCabal latestver
Nothing -> liftIO $ hideError doesNotExistErrorType $ deleteFile
(binDir </> [rel|cabal|])
2020-01-11 20:15:05 +00:00
-- | Delete a hls version. Will try to fix the hls symlinks
-- after removal (e.g. setting it to an older version).
2020-10-23 23:06:53 +00:00
rmHLSVer :: (MonadReader AppState m, MonadThrow m, MonadLogger m, MonadIO m, MonadFail m, MonadCatch m)
=> Version
-> Excepts '[NotInstalled] m ()
rmHLSVer ver = do
whenM (lift $ fmap not $ hlsInstalled ver) $ throwE (NotInstalled HLS (GHCTargetVersion Nothing ver))
2021-03-11 16:03:51 +00:00
isHlsSet <- lift hlsSet
2020-10-23 23:06:53 +00:00
AppState {dirs = Dirs {..}} <- lift ask
bins <- lift $ hlsAllBinaries ver
forM_ bins $ \f -> liftIO $ deleteFile (binDir </> f)
2021-03-11 16:03:51 +00:00
when (Just ver == isHlsSet) $ do
-- delete all set symlinks
oldSyms <- lift hlsSymlinks
forM_ oldSyms $ \f -> do
lift $ $(logDebug) [i|rm #{toFilePath (binDir </> f)}|]
liftIO $ deleteFile (binDir </> f)
-- set latest hls
2021-03-11 16:03:51 +00:00
hlsVers <- lift $ fmap rights getInstalledHLSs
case headMay . reverse . sort $ hlsVers of
Just latestver -> setHLS latestver
Nothing -> pure ()
2020-01-11 20:15:05 +00:00
------------------
--[ Debug info ]--
------------------
2020-10-23 23:06:53 +00:00
getDebugInfo :: (MonadReader AppState m, MonadLogger m, MonadCatch m, MonadIO m)
2020-01-11 20:15:05 +00:00
=> Excepts
'[NoCompatiblePlatform , NoCompatibleArch , DistroNotFound]
m
DebugInfo
getDebugInfo = do
2020-10-23 23:06:53 +00:00
AppState {dirs = Dirs {..}} <- lift ask
let diBaseDir = baseDir
let diBinDir = binDir
diGHCDir <- lift ghcupGHCBaseDir
let diCacheDir = cacheDir
diArch <- lE getArchitecture
2021-03-11 16:03:51 +00:00
diPlatform <- liftE getPlatform
2020-01-11 20:15:05 +00:00
pure $ DebugInfo { .. }
---------------
--[ Compile ]--
---------------
2020-07-22 00:34:17 +00:00
-- | Compile a GHC from source. This behaves wrt symlinks and installation
2020-07-21 23:08:58 +00:00
-- the same as 'installGHCBin'.
2020-01-11 20:15:05 +00:00
compileGHC :: ( MonadMask m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
2020-01-11 20:15:05 +00:00
, MonadThrow m
, MonadResource m
, MonadLogger m
, MonadIO m
, MonadFail m
)
=> GHCupDownloads
2020-04-25 10:06:41 +00:00
-> GHCTargetVersion -- ^ version to install
-> Either Version (Path Abs) -- ^ version to bootstrap with
-> Maybe Int -- ^ jobs
-> Maybe (Path Abs) -- ^ build config
2020-04-25 10:06:41 +00:00
-> Maybe (Path Abs) -- ^ patch directory
-> [Text] -- ^ additional args to ./configure
2020-07-13 16:27:21 +00:00
-> PlatformRequest
2020-01-11 20:15:05 +00:00
-> Excepts
'[ AlreadyInstalled
, BuildFailed
, DigestError
, DownloadFailed
, GHCupSetError
, NoDownload
2020-04-10 20:44:43 +00:00
, NotFoundInPATH
, PatchFailed
2020-01-11 20:15:05 +00:00
, UnknownArchive
2020-08-06 11:28:20 +00:00
, TarDirDoesNotExist
, NotInstalled
#if !defined(TAR)
, ArchiveResult
#endif
2020-01-11 20:15:05 +00:00
]
m
()
2021-03-11 16:03:51 +00:00
compileGHC dls tver bstrap jobs mbuildConfig patchdir aargs pfreq@PlatformRequest{..}
= do
lift $ $(logDebug) [i|Requested to compile: #{tver} with #{bstrap}|]
alreadyInstalled <- lift $ ghcInstalled tver
2021-03-11 16:03:51 +00:00
alreadySet <- fmap (== Just tver) $ lift $ ghcSet (_tvTarget tver)
-- download source tarball
dlInfo <-
preview (ix GHC % ix (tver ^. tvVersion) % viSourceDL % _Just) dls
?? NoDownload
dl <- liftE $ downloadCached dlInfo Nothing
-- unpack
tmpUnpack <- lift mkGhcupTmpDir
liftE $ unpackToDir tmpUnpack dl
void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
bghc <- case bstrap of
Right g -> pure $ Right g
Left bver -> Left <$> parseRel ("ghc-" <> verToBS bver)
workdir <- maybe (pure tmpUnpack)
(liftE . intoSubdir tmpUnpack)
(view dlSubdir dlInfo)
ghcdir <- lift $ ghcupGHCDir tver
(bindist, bmk) <- liftE $ runBuildAction
tmpUnpack
2020-09-17 19:20:38 +00:00
Nothing
(do
b <- compileBindist bghc ghcdir workdir
bmk <- liftIO $ readFileStrict (build_mk workdir)
pure (b, bmk)
)
2020-01-11 20:15:05 +00:00
when alreadyInstalled $ do
lift $ $(logInfo) [i|Deleting existing installation|]
liftE $ rmGHCVer tver
liftE $ installPackedGHC bindist
(view dlSubdir dlInfo)
ghcdir
(tver ^. tvVersion)
pfreq
2020-01-11 20:15:05 +00:00
liftIO $ writeFile (ghcdir </> ghcUpSrcBuiltFile) (Just newFilePerms) bmk
2020-01-11 20:15:05 +00:00
reThrowAll GHCupSetError $ postGHCInstall tver
-- restore
when alreadySet $ liftE $ void $ setGHC tver SetGHCOnly
2020-01-11 20:15:05 +00:00
where
2020-04-25 10:06:41 +00:00
defaultConf = case _tvTarget tver of
Nothing -> [s|
2020-04-25 10:06:41 +00:00
V=0
BUILD_MAN = NO
BUILD_SPHINX_HTML = NO
BUILD_SPHINX_PDF = NO
HADDOCK_DOCS = YES|]
Just _ -> [s|
2020-01-11 20:15:05 +00:00
V=0
BUILD_MAN = NO
BUILD_SPHINX_HTML = NO
BUILD_SPHINX_PDF = NO
2020-04-25 10:06:41 +00:00
HADDOCK_DOCS = NO
Stage1Only = YES|]
2020-01-11 20:15:05 +00:00
2020-10-23 23:06:53 +00:00
compileBindist :: ( MonadReader AppState m
, MonadThrow m
, MonadCatch m
, MonadLogger m
, MonadIO m
, MonadFail m
)
=> Either (Path Rel) (Path Abs)
-> Path Abs
-> Path Abs
-> Excepts
'[FileDoesNotExistError, InvalidBuildConfig, PatchFailed, ProcessError, NotFoundInPATH, CopyError]
m
(Path Abs) -- ^ output path of bindist
compileBindist bghc ghcdir workdir = do
2020-01-11 20:15:05 +00:00
lift $ $(logInfo) [i|configuring build|]
2021-03-11 16:03:51 +00:00
liftE checkBuildConfig
2020-03-18 16:31:17 +00:00
2020-10-23 23:06:53 +00:00
AppState { dirs = Dirs {..} } <- lift ask
forM_ patchdir $ \dir -> liftE $ applyPatches dir workdir
2021-03-11 16:03:51 +00:00
cEnv <- liftIO getEnvironment
2020-03-18 16:31:17 +00:00
2020-01-11 20:15:05 +00:00
if
2021-03-11 16:03:51 +00:00
| _tvVersion tver >= [vver|8.8.0|] -> do
bghcPath <- case bghc of
Right ghc' -> pure ghc'
Left bver -> do
spaths <- catMaybes . fmap parseAbs <$> liftIO getSearchPath
2021-03-11 16:03:51 +00:00
liftIO (searchPath spaths bver) !? NotFoundInPATH bver
2020-07-13 09:52:34 +00:00
lEM $ execLogged
2020-03-21 21:19:37 +00:00
"./configure"
2020-03-18 16:31:17 +00:00
False
2020-04-25 10:06:41 +00:00
( ["--prefix=" <> toFilePath ghcdir]
2021-03-11 16:03:51 +00:00
++ maybe mempty
2020-04-25 10:06:41 +00:00
(\x -> ["--target=" <> E.encodeUtf8 x])
(_tvTarget tver)
++ fmap E.encodeUtf8 aargs
)
2020-03-24 15:49:18 +00:00
[rel|ghc-conf|]
2020-03-18 16:31:17 +00:00
(Just workdir)
2020-04-25 10:06:41 +00:00
(Just (("GHC", toFilePath bghcPath) : cEnv))
2020-01-11 20:15:05 +00:00
| otherwise -> do
2020-07-13 09:52:34 +00:00
lEM $ execLogged
2020-03-21 21:19:37 +00:00
"./configure"
2020-01-11 20:15:05 +00:00
False
2020-04-25 10:06:41 +00:00
( [ "--prefix=" <> toFilePath ghcdir
, "--with-ghc=" <> either toFilePath toFilePath bghc
]
2021-03-11 16:03:51 +00:00
++ maybe mempty
(\x -> ["--target=" <> E.encodeUtf8 x])
(_tvTarget tver)
2020-04-25 10:06:41 +00:00
++ fmap E.encodeUtf8 aargs
)
2020-03-24 15:49:18 +00:00
[rel|ghc-conf|]
2020-01-11 20:15:05 +00:00
(Just workdir)
2020-04-25 10:06:41 +00:00
(Just cEnv)
2020-01-11 20:15:05 +00:00
case mbuildConfig of
Just bc -> liftIOException
doesNotExistErrorType
(FileDoesNotExistError $ toFilePath bc)
(liftIO $ copyFile bc (build_mk workdir) Overwrite)
Nothing ->
liftIO $ writeFile (build_mk workdir) (Just newFilePerms) defaultConf
lift $ $(logInfo) [i|Building (this may take a while)...|]
lEM $ make (maybe [] (\j -> ["-j" <> fS (show j)]) jobs) (Just workdir)
lift $ $(logInfo) [i|Creating bindist...|]
lEM $ make ["binary-dist"] (Just workdir)
[tar] <- liftIO $ findFiles
workdir
(makeRegexOpts compExtended
execBlank
([s|^ghc-.*\.tar\..*$|] :: ByteString)
)
c <- liftIO $ readFile (workdir </> tar)
cDigest <-
fmap (T.take 8)
. lift
. throwEither
. E.decodeUtf8'
. B16.encode
. SHA256.hashlazy
$ c
cTime <- liftIO getCurrentTime
tarName <-
parseRel
[i|ghc-#{tVerToText tver}-#{pfReqToString pfreq}-#{iso8601Show cTime}-#{cDigest}.tar#{takeExtension (toFilePath tar)}|]
let tarPath = cacheDir </> tarName
handleIO (throwE . CopyError . show) $ liftIO $ copyFile (workdir </> tar)
tarPath
Strict
lift $ $(logInfo) [i|Copied bindist to #{tarPath}|]
pure tarPath
2020-01-11 20:15:05 +00:00
2020-03-16 09:47:09 +00:00
build_mk workdir = workdir </> [rel|mk/build.mk|]
2020-01-11 20:15:05 +00:00
2020-04-25 10:06:41 +00:00
checkBuildConfig :: (MonadCatch m, MonadIO m)
=> Excepts
'[FileDoesNotExistError, InvalidBuildConfig]
2020-04-25 10:06:41 +00:00
m
()
checkBuildConfig = do
c <- case mbuildConfig of
Just bc -> do
BL.toStrict <$> liftIOException
doesNotExistErrorType
(FileDoesNotExistError $ toFilePath bc)
(liftIO $ readFile bc)
2020-04-25 10:06:41 +00:00
Nothing -> pure defaultConf
let lines' = fmap T.strip . T.lines $ decUTF8Safe c
-- for cross, we need Stage1Only
case _tvTarget tver of
2021-03-11 16:03:51 +00:00
Just _ -> when ("Stage1Only = YES" `notElem` lines') $ throwE
2020-04-25 10:06:41 +00:00
(InvalidBuildConfig
[s|Cross compiling needs to be a Stage1 build, add "Stage1Only = YES" to your config!|]
)
Nothing -> pure ()
2020-01-11 20:15:05 +00:00
---------------------
--[ Upgrade GHCup ]--
---------------------
2020-07-21 23:08:58 +00:00
-- | Upgrade ghcup and place it in @~\/.ghcup\/bin\/ghcup@,
-- if no path is provided.
2020-01-11 20:15:05 +00:00
upgradeGHCup :: ( MonadMask m
2020-10-23 23:06:53 +00:00
, MonadReader AppState m
2020-01-11 20:15:05 +00:00
, MonadCatch m
, MonadLogger m
, MonadThrow m
, MonadResource m
, MonadIO m
)
=> GHCupDownloads
-> Maybe (Path Abs) -- ^ full file destination to write ghcup into
-> Bool -- ^ whether to force update regardless
-- of currently installed version
2020-07-13 16:27:21 +00:00
-> PlatformRequest
2020-01-11 20:15:05 +00:00
-> Excepts
'[ CopyError
, DigestError
, DownloadFailed
, NoDownload
, NoUpdate
2020-01-11 20:15:05 +00:00
]
m
Version
2020-07-13 16:27:21 +00:00
upgradeGHCup dls mtarget force pfreq = do
2020-10-23 23:06:53 +00:00
AppState {dirs = Dirs {..}} <- lift ask
2020-01-11 20:15:05 +00:00
lift $ $(logInfo) [i|Upgrading GHCup...|]
let latestVer = fromJust $ fst <$> getLatest dls GHCup
2020-04-15 13:37:29 +00:00
when (not force && (latestVer <= pvpToVersion ghcUpVer)) $ throwE NoUpdate
dli <- lE $ getDownloadInfo GHCup latestVer pfreq dls
tmp <- lift withGHCupTmpDir
2020-03-16 09:47:09 +00:00
let fn = [rel|ghcup|]
2020-01-11 20:15:05 +00:00
p <- liftE $ download dli tmp (Just fn)
let destDir = dirname destFile
destFile = fromMaybe (binDir </> fn) mtarget
lift $ $(logDebug) [i|mkdir -p #{toFilePath destDir}|]
liftIO $ createDirRecursive' destDir
lift $ $(logDebug) [i|rm -f #{toFilePath destFile}|]
liftIO $ hideError NoSuchThing $ deleteFile destFile
lift $ $(logDebug) [i|cp #{toFilePath p} #{toFilePath destFile}|]
2020-07-07 17:39:58 +00:00
handleIO (throwE . CopyError . show) $ liftIO $ copyFile p
destFile
2020-07-07 17:39:58 +00:00
Overwrite
lift $ chmod_755 destFile
2021-03-11 16:03:51 +00:00
liftIO (isInPath destFile) >>= \b -> unless b $
lift $ $(logWarn) [i|"#{toFilePath (dirname destFile)}" is not in PATH! You have to add it in order to use ghcup.|]
liftIO (isShadowed destFile) >>= \case
Nothing -> pure ()
Just pa -> lift $ $(logWarn) [i|ghcup is shadowed by "#{toFilePath pa}". The upgrade will not be in effect, unless you remove "#{toFilePath pa}" or make sure "#{toFilePath destDir}" comes before "#{toFilePath (dirname pa)}" in PATH.|]
2020-01-11 20:15:05 +00:00
pure latestVer
-------------
--[ Other ]--
-------------
2020-07-21 23:08:58 +00:00
-- | Creates @ghc-x.y.z@ and @ghc-x.y@ symlinks. This is used for
2020-01-11 20:15:05 +00:00
-- both installing from source and bindist.
2020-10-23 23:06:53 +00:00
postGHCInstall :: ( MonadReader AppState m
2020-08-06 11:28:20 +00:00
, MonadLogger m
, MonadThrow m
, MonadFail m
, MonadIO m
, MonadCatch m
)
2020-04-25 10:06:41 +00:00
=> GHCTargetVersion
2020-01-11 20:15:05 +00:00
-> Excepts '[NotInstalled] m ()
2020-08-06 11:28:20 +00:00
postGHCInstall ver@GHCTargetVersion {..} = do
void $ liftE $ setGHC ver SetGHC_XYZ
2020-01-11 20:15:05 +00:00
-- Create ghc-x.y symlinks. This may not be the current
-- version, create it regardless.
2020-08-06 11:28:20 +00:00
v' <-
handle (\(e :: ParseError) -> lift $ $(logWarn) [i|#{e}|] >> pure Nothing)
$ fmap Just
$ getMajorMinorV _tvVersion
forM_ v' $ \(mj, mi) -> lift (getGHCForMajor mj mi _tvTarget)
>>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)