Compare commits
5 Commits
hls-hackag
...
pwsh
| Author | SHA1 | Date | |
|---|---|---|---|
|
256e1942f2
|
|||
|
aa71f0dfa1
|
|||
|
04d527c98a
|
|||
|
7b59621179
|
|||
|
9d59463ded
|
@@ -440,11 +440,9 @@ tagCompleter tool add = listIOCompleter $ do
|
|||||||
pure $ nub $ (add ++) $ fmap tagToString allTags
|
pure $ nub $ (add ++) $ fmap tagToString allTags
|
||||||
VLeft _ -> pure (nub $ ["recommended", "latest"] ++ add)
|
VLeft _ -> pure (nub $ ["recommended", "latest"] ++ add)
|
||||||
|
|
||||||
versionCompleter :: Maybe ListCriteria -> Tool -> Completer
|
|
||||||
versionCompleter criteria tool = versionCompleter' criteria tool (const True)
|
|
||||||
|
|
||||||
versionCompleter' :: Maybe ListCriteria -> Tool -> (Version -> Bool) -> Completer
|
versionCompleter :: Maybe ListCriteria -> Tool -> Completer
|
||||||
versionCompleter' criteria tool filter' = listIOCompleter $ do
|
versionCompleter criteria tool = listIOCompleter $ do
|
||||||
dirs' <- liftIO getAllDirs
|
dirs' <- liftIO getAllDirs
|
||||||
let loggerConfig = LoggerConfig
|
let loggerConfig = LoggerConfig
|
||||||
{ lcPrintDebug = False
|
{ lcPrintDebug = False
|
||||||
@@ -473,7 +471,7 @@ versionCompleter' criteria tool filter' = listIOCompleter $ do
|
|||||||
runEnv = flip runReaderT appState
|
runEnv = flip runReaderT appState
|
||||||
|
|
||||||
installedVersions <- runEnv $ listVersions (Just tool) criteria
|
installedVersions <- runEnv $ listVersions (Just tool) criteria
|
||||||
return $ fmap (T.unpack . prettyVer) . filter filter' . fmap lVer $ installedVersions
|
return $ T.unpack . prettyVer . lVer <$> installedVersions
|
||||||
|
|
||||||
|
|
||||||
toolDlCompleter :: Tool -> Completer
|
toolDlCompleter :: Tool -> Completer
|
||||||
|
|||||||
@@ -12,8 +12,6 @@ module GHCup.OptParse.Compile where
|
|||||||
|
|
||||||
|
|
||||||
import GHCup
|
import GHCup
|
||||||
import qualified GHCup.GHC as GHC
|
|
||||||
import qualified GHCup.HLS as HLS
|
|
||||||
import GHCup.Errors
|
import GHCup.Errors
|
||||||
import GHCup.Types
|
import GHCup.Types
|
||||||
import GHCup.Types.Optics
|
import GHCup.Types.Optics
|
||||||
@@ -32,8 +30,7 @@ import Control.Monad.Trans.Resource
|
|||||||
import Data.Bifunctor
|
import Data.Bifunctor
|
||||||
import Data.Functor
|
import Data.Functor
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Versions ( Version, prettyVer, version, pvp )
|
import Data.Versions ( Version, prettyVer, version )
|
||||||
import qualified Data.Versions as V
|
|
||||||
import Data.Text ( Text )
|
import Data.Text ( Text )
|
||||||
import Haskus.Utils.Variant.Excepts
|
import Haskus.Utils.Variant.Excepts
|
||||||
import Options.Applicative hiding ( style )
|
import Options.Applicative hiding ( style )
|
||||||
@@ -44,7 +41,7 @@ import Text.PrettyPrint.HughesPJClass ( prettyShow )
|
|||||||
|
|
||||||
import URI.ByteString hiding ( uriParser )
|
import URI.ByteString hiding ( uriParser )
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Control.Exception.Safe (MonadMask, displayException)
|
import Control.Exception.Safe (MonadMask)
|
||||||
import System.FilePath (isPathSeparator)
|
import System.FilePath (isPathSeparator)
|
||||||
import Text.Read (readEither)
|
import Text.Read (readEither)
|
||||||
|
|
||||||
@@ -67,7 +64,7 @@ data CompileCommand = CompileGHC GHCCompileOptions
|
|||||||
|
|
||||||
|
|
||||||
data GHCCompileOptions = GHCCompileOptions
|
data GHCCompileOptions = GHCCompileOptions
|
||||||
{ targetGhc :: GHC.GHCVer Version
|
{ targetGhc :: Either Version GitBranch
|
||||||
, bootstrapGhc :: Either Version FilePath
|
, bootstrapGhc :: Either Version FilePath
|
||||||
, jobs :: Maybe Int
|
, jobs :: Maybe Int
|
||||||
, buildConfig :: Maybe FilePath
|
, buildConfig :: Maybe FilePath
|
||||||
@@ -81,12 +78,10 @@ data GHCCompileOptions = GHCCompileOptions
|
|||||||
, isolateDir :: Maybe FilePath
|
, isolateDir :: Maybe FilePath
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
data HLSCompileOptions = HLSCompileOptions
|
data HLSCompileOptions = HLSCompileOptions
|
||||||
{ targetHLS :: HLS.HLSVer
|
{ targetHLS :: Either Version GitBranch
|
||||||
, jobs :: Maybe Int
|
, jobs :: Maybe Int
|
||||||
, setCompile :: Bool
|
, setCompile :: Bool
|
||||||
, updateCabal :: Bool
|
|
||||||
, ovewrwiteVer :: Either Bool Version
|
, ovewrwiteVer :: Either Bool Version
|
||||||
, isolateDir :: Maybe FilePath
|
, isolateDir :: Maybe FilePath
|
||||||
, cabalProject :: Maybe (Either FilePath URI)
|
, cabalProject :: Maybe (Either FilePath URI)
|
||||||
@@ -154,10 +149,10 @@ Examples:
|
|||||||
These need to be available in PATH prior to compilation.
|
These need to be available in PATH prior to compilation.
|
||||||
|
|
||||||
Examples:
|
Examples:
|
||||||
# compile 1.7.0.0 from hackage for 8.10.7, running 'cabal update' before the build
|
# compile 1.7.0.0 for ghc 8.10.5 and 8.10.7, passing '--allow-newer' to cabal
|
||||||
ghcup compile hls --version 1.7.0.0 --ghc 8.10.7 --cabal-update
|
ghcup compile hls -v 1.7.0.0 -j 12 --ghc 8.10.5 --ghc 8.10.7 -- --allow-newer
|
||||||
# compile from master for ghc 9.2.3 using 'git describe' to name the binary and ignore the pinned index state
|
# compile from master for ghc 9.2.3 and use 'git describe' to name the binary
|
||||||
ghcup compile hls -g master --git-describe-version --ghc 9.2.3 -- --index-state=@(date '+%s')
|
ghcup compile hls -g master --git-describe-version --ghc 9.2.3
|
||||||
# compile a specific commit for ghc 9.2.3 and set a specifc version for the binary name
|
# compile a specific commit for ghc 9.2.3 and set a specifc version for the binary name
|
||||||
ghcup compile hls -g a32db0b -o 1.7.0.0-p1 --ghc 9.2.3|]
|
ghcup compile hls -g a32db0b -o 1.7.0.0-p1 --ghc 9.2.3|]
|
||||||
|
|
||||||
@@ -165,7 +160,7 @@ Examples:
|
|||||||
ghcCompileOpts :: Parser GHCCompileOptions
|
ghcCompileOpts :: Parser GHCCompileOptions
|
||||||
ghcCompileOpts =
|
ghcCompileOpts =
|
||||||
GHCCompileOptions
|
GHCCompileOptions
|
||||||
<$> ((GHC.SourceDist <$> option
|
<$> ((Left <$> option
|
||||||
(eitherReader
|
(eitherReader
|
||||||
(first (const "Not a valid version") . version . T.pack)
|
(first (const "Not a valid version") . version . T.pack)
|
||||||
)
|
)
|
||||||
@@ -174,7 +169,7 @@ ghcCompileOpts =
|
|||||||
<> (completer $ versionCompleter Nothing GHC)
|
<> (completer $ versionCompleter Nothing GHC)
|
||||||
)
|
)
|
||||||
) <|>
|
) <|>
|
||||||
(GHC.GitDist <$> (GitBranch <$> option
|
(Right <$> (GitBranch <$> option
|
||||||
str
|
str
|
||||||
(short 'g' <> long "git-ref" <> metavar "GIT_REFERENCE" <> help
|
(short 'g' <> long "git-ref" <> metavar "GIT_REFERENCE" <> help
|
||||||
"The git commit/branch/ref to build from"
|
"The git commit/branch/ref to build from"
|
||||||
@@ -183,18 +178,7 @@ ghcCompileOpts =
|
|||||||
short 'r' <> long "repository" <> metavar "GIT_REPOSITORY" <> help "The git repository to build from (defaults to GHC upstream)"
|
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"])
|
<> completer (gitFileUri ["https://gitlab.haskell.org/ghc/ghc.git"])
|
||||||
))
|
))
|
||||||
))
|
)))
|
||||||
<|>
|
|
||||||
(
|
|
||||||
GHC.RemoteDist <$> (option
|
|
||||||
(eitherReader uriParser)
|
|
||||||
(long "remote-source-dist" <> metavar "URI" <> help
|
|
||||||
"URI (https/http/file) to a GHC source distribution"
|
|
||||||
<> completer fileUri
|
|
||||||
)
|
|
||||||
)
|
|
||||||
)
|
|
||||||
)
|
|
||||||
<*> option
|
<*> option
|
||||||
(eitherReader
|
(eitherReader
|
||||||
(\x ->
|
(\x ->
|
||||||
@@ -286,17 +270,16 @@ ghcCompileOpts =
|
|||||||
hlsCompileOpts :: Parser HLSCompileOptions
|
hlsCompileOpts :: Parser HLSCompileOptions
|
||||||
hlsCompileOpts =
|
hlsCompileOpts =
|
||||||
HLSCompileOptions
|
HLSCompileOptions
|
||||||
<$> ((HLS.HackageDist <$> option
|
<$> ((Left <$> option
|
||||||
(eitherReader
|
(eitherReader
|
||||||
((>>= first displayException . V.version . V.prettyPVP) . first (const "Not a valid PVP version") . pvp . T.pack)
|
(first (const "Not a valid version") . version . T.pack)
|
||||||
)
|
)
|
||||||
(short 'v' <> long "version" <> metavar "VERSION" <> help
|
(short 'v' <> long "version" <> metavar "VERSION" <> help
|
||||||
"The version to compile (pulled from hackage)"
|
"The tool version to compile"
|
||||||
<> (completer $ versionCompleter' Nothing HLS (either (const False) (const True) . V.pvp . V.prettyVer))
|
<> (completer $ versionCompleter Nothing HLS)
|
||||||
)
|
)
|
||||||
)
|
) <|>
|
||||||
<|>
|
(Right <$> (GitBranch <$> option
|
||||||
(HLS.GitDist <$> (GitBranch <$> option
|
|
||||||
str
|
str
|
||||||
(short 'g' <> long "git-ref" <> metavar "GIT_REFERENCE" <> help
|
(short 'g' <> long "git-ref" <> metavar "GIT_REFERENCE" <> help
|
||||||
"The git commit/branch/ref to build from (accepts anything 'git checkout' accepts)"
|
"The git commit/branch/ref to build from (accepts anything 'git checkout' accepts)"
|
||||||
@@ -304,28 +287,7 @@ hlsCompileOpts =
|
|||||||
optional (option str (short 'r' <> long "repository" <> metavar "GIT_REPOSITORY" <> help "The git repository to build from (defaults to HLS upstream)"
|
optional (option str (short 'r' <> long "repository" <> metavar "GIT_REPOSITORY" <> help "The git repository to build from (defaults to HLS upstream)"
|
||||||
<> completer (gitFileUri ["https://github.com/haskell/haskell-language-server.git"])
|
<> completer (gitFileUri ["https://github.com/haskell/haskell-language-server.git"])
|
||||||
))
|
))
|
||||||
))
|
)))
|
||||||
<|>
|
|
||||||
(HLS.SourceDist <$> (option
|
|
||||||
(eitherReader
|
|
||||||
(first (const "Not a valid version") . version . T.pack)
|
|
||||||
)
|
|
||||||
(long "source-dist" <> metavar "VERSION" <> help
|
|
||||||
"The version to compile (pulled from packaged git sources)"
|
|
||||||
<> (completer $ versionCompleter Nothing HLS)
|
|
||||||
)
|
|
||||||
))
|
|
||||||
<|>
|
|
||||||
(
|
|
||||||
HLS.RemoteDist <$> (option
|
|
||||||
(eitherReader uriParser)
|
|
||||||
(long "remote-source-dist" <> metavar "URI" <> help
|
|
||||||
"URI (https/http/file) to a HLS source distribution"
|
|
||||||
<> completer fileUri
|
|
||||||
)
|
|
||||||
)
|
|
||||||
)
|
|
||||||
)
|
|
||||||
<*> optional
|
<*> optional
|
||||||
(option
|
(option
|
||||||
(eitherReader (readEither @Int))
|
(eitherReader (readEither @Int))
|
||||||
@@ -335,7 +297,6 @@ hlsCompileOpts =
|
|||||||
)
|
)
|
||||||
)
|
)
|
||||||
<*> fmap (fromMaybe True) (invertableSwitch "set" Nothing True (help "Don't set as active version after install"))
|
<*> fmap (fromMaybe True) (invertableSwitch "set" Nothing True (help "Don't set as active version after install"))
|
||||||
<*> switch (long "cabal-update" <> help "Run 'cabal update' before the build")
|
|
||||||
<*>
|
<*>
|
||||||
(
|
(
|
||||||
(Right <$> option
|
(Right <$> option
|
||||||
@@ -507,7 +468,7 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
|
|||||||
(CompileHLS HLSCompileOptions { .. }) -> do
|
(CompileHLS HLSCompileOptions { .. }) -> do
|
||||||
runCompileHLS runAppState (do
|
runCompileHLS runAppState (do
|
||||||
case targetHLS of
|
case targetHLS of
|
||||||
HLS.SourceDist targetVer -> do
|
Left targetVer -> do
|
||||||
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
||||||
let vi = getVersionInfo targetVer HLS dls
|
let vi = getVersionInfo targetVer HLS dls
|
||||||
forM_ (_viPreCompile =<< vi) $ \msg -> do
|
forM_ (_viPreCompile =<< vi) $ \msg -> do
|
||||||
@@ -515,7 +476,7 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
|
|||||||
lift $ logInfo
|
lift $ logInfo
|
||||||
"...waiting for 5 seconds, you can still abort..."
|
"...waiting for 5 seconds, you can still abort..."
|
||||||
liftIO $ threadDelay 5000000 -- for compilation, give the user a sec to intervene
|
liftIO $ threadDelay 5000000 -- for compilation, give the user a sec to intervene
|
||||||
_ -> pure ()
|
Right _ -> pure ()
|
||||||
ghcs <- liftE $ forM targetGHCs (\ghc -> fmap (_tvVersion . fst) . fromVersion (Just ghc) $ GHC)
|
ghcs <- liftE $ forM targetGHCs (\ghc -> fmap (_tvVersion . fst) . fromVersion (Just ghc) $ GHC)
|
||||||
targetVer <- liftE $ compileHLS
|
targetVer <- liftE $ compileHLS
|
||||||
targetHLS
|
targetHLS
|
||||||
@@ -525,7 +486,6 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
|
|||||||
(maybe GHCupInternal IsolateDir isolateDir)
|
(maybe GHCupInternal IsolateDir isolateDir)
|
||||||
cabalProject
|
cabalProject
|
||||||
cabalProjectLocal
|
cabalProjectLocal
|
||||||
updateCabal
|
|
||||||
patches
|
patches
|
||||||
cabalArgs
|
cabalArgs
|
||||||
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
||||||
@@ -559,7 +519,7 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
|
|||||||
(CompileGHC GHCCompileOptions {..}) ->
|
(CompileGHC GHCCompileOptions {..}) ->
|
||||||
runCompileGHC runAppState (do
|
runCompileGHC runAppState (do
|
||||||
case targetGhc of
|
case targetGhc of
|
||||||
GHC.SourceDist targetVer -> do
|
Left targetVer -> do
|
||||||
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
||||||
let vi = getVersionInfo targetVer GHC dls
|
let vi = getVersionInfo targetVer GHC dls
|
||||||
forM_ (_viPreCompile =<< vi) $ \msg -> do
|
forM_ (_viPreCompile =<< vi) $ \msg -> do
|
||||||
@@ -567,12 +527,9 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
|
|||||||
lift $ logInfo
|
lift $ logInfo
|
||||||
"...waiting for 5 seconds, you can still abort..."
|
"...waiting for 5 seconds, you can still abort..."
|
||||||
liftIO $ threadDelay 5000000 -- for compilation, give the user a sec to intervene
|
liftIO $ threadDelay 5000000 -- for compilation, give the user a sec to intervene
|
||||||
_ -> pure ()
|
Right _ -> pure ()
|
||||||
targetVer <- liftE $ compileGHC
|
targetVer <- liftE $ compileGHC
|
||||||
((\case
|
(first (GHCTargetVersion crossTarget) targetGhc)
|
||||||
GHC.SourceDist v -> GHC.SourceDist $ GHCTargetVersion crossTarget v
|
|
||||||
GHC.GitDist g -> GHC.GitDist g
|
|
||||||
GHC.RemoteDist r -> GHC.RemoteDist r) targetGhc)
|
|
||||||
ovewrwiteVer
|
ovewrwiteVer
|
||||||
bootstrapGhc
|
bootstrapGhc
|
||||||
jobs
|
jobs
|
||||||
|
|||||||
@@ -14,8 +14,6 @@ module Main where
|
|||||||
import BrickMain ( brickMain )
|
import BrickMain ( brickMain )
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
import qualified GHCup.GHC as GHC
|
|
||||||
import qualified GHCup.HLS as HLS
|
|
||||||
import GHCup.OptParse
|
import GHCup.OptParse
|
||||||
|
|
||||||
import GHCup.Download
|
import GHCup.Download
|
||||||
@@ -340,13 +338,11 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
|
|||||||
alreadyInstalling (Install (Left (InstallStack InstallOptions{..}))) (Stack, ver) = cmp' Stack instVer ver
|
alreadyInstalling (Install (Left (InstallStack InstallOptions{..}))) (Stack, ver) = cmp' Stack instVer ver
|
||||||
alreadyInstalling (Compile (CompileGHC GHCCompileOptions{ ovewrwiteVer = Just over }))
|
alreadyInstalling (Compile (CompileGHC GHCCompileOptions{ ovewrwiteVer = Just over }))
|
||||||
(GHC, ver) = cmp' GHC (Just $ ToolVersion (mkTVer over)) ver
|
(GHC, ver) = cmp' GHC (Just $ ToolVersion (mkTVer over)) ver
|
||||||
alreadyInstalling (Compile (CompileGHC GHCCompileOptions{ targetGhc = GHC.SourceDist tver }))
|
alreadyInstalling (Compile (CompileGHC GHCCompileOptions{ targetGhc = Left tver }))
|
||||||
(GHC, ver) = cmp' GHC (Just $ ToolVersion (mkTVer tver)) ver
|
(GHC, ver) = cmp' GHC (Just $ ToolVersion (mkTVer tver)) ver
|
||||||
alreadyInstalling (Compile (CompileHLS HLSCompileOptions{ ovewrwiteVer = Right over }))
|
alreadyInstalling (Compile (CompileHLS HLSCompileOptions{ ovewrwiteVer = Right over }))
|
||||||
(HLS, ver) = cmp' HLS (Just $ ToolVersion (mkTVer over)) ver
|
(HLS, ver) = cmp' HLS (Just $ ToolVersion (mkTVer over)) ver
|
||||||
alreadyInstalling (Compile (CompileHLS HLSCompileOptions{ targetHLS = HLS.SourceDist tver }))
|
alreadyInstalling (Compile (CompileHLS HLSCompileOptions{ targetHLS = Left tver }))
|
||||||
(HLS, ver) = cmp' HLS (Just $ ToolVersion (mkTVer tver)) ver
|
|
||||||
alreadyInstalling (Compile (CompileHLS HLSCompileOptions{ targetHLS = HLS.HackageDist tver }))
|
|
||||||
(HLS, ver) = cmp' HLS (Just $ ToolVersion (mkTVer tver)) ver
|
(HLS, ver) = cmp' HLS (Just $ ToolVersion (mkTVer tver)) ver
|
||||||
alreadyInstalling (Upgrade _ _ _) (GHCup, _) = pure True
|
alreadyInstalling (Upgrade _ _ _) (GHCup, _) = pure True
|
||||||
alreadyInstalling _ _ = pure False
|
alreadyInstalling _ _ = pure False
|
||||||
|
|||||||
@@ -202,9 +202,7 @@ and produce the binaries `ghc-8.10.2-eff` and `ghc-head` respectively.
|
|||||||
GHCup always needs to know which version the bindist corresponds to (this is not automatically
|
GHCup always needs to know which version the bindist corresponds to (this is not automatically
|
||||||
detected).
|
detected).
|
||||||
|
|
||||||
## Compiling from source
|
## Compiling GHC from source
|
||||||
|
|
||||||
### GHC
|
|
||||||
|
|
||||||
Compiling from source is supported for both source tarballs and arbitrary git refs. See `ghcup compile ghc --help`
|
Compiling from source is supported for both source tarballs and arbitrary git refs. See `ghcup compile ghc --help`
|
||||||
for a list of all available options.
|
for a list of all available options.
|
||||||
@@ -216,47 +214,6 @@ Common `build.mk` options are explained [here](https://gitlab.haskell.org/ghc/gh
|
|||||||
|
|
||||||
Make sure your system meets all the [prerequisites](https://gitlab.haskell.org/ghc/ghc/-/wikis/building/preparation).
|
Make sure your system meets all the [prerequisites](https://gitlab.haskell.org/ghc/ghc/-/wikis/building/preparation).
|
||||||
|
|
||||||
### HLS
|
|
||||||
|
|
||||||
There are 3 main ways to compile HLS from source.
|
|
||||||
|
|
||||||
1. from hackage (should have up to date version bounds)
|
|
||||||
- `ghcup compile hls --version 1.7.0.0 --ghc 9.2.3`
|
|
||||||
2. from git (allows to build latest sources and PRs)
|
|
||||||
- `ghcup compile hls --git-ref master --ghc 9.2.3`
|
|
||||||
- `ghcup compile hls --git-ref a32db0b --ghc 9.2.3`
|
|
||||||
- `ghcup compile hls --git-ref 1.7.0.0 --ghc 9.2.3`
|
|
||||||
3. from source distribution that's packaged during release from the corresponding git sources
|
|
||||||
- `ghcup compile hls --source-dist 1.7.0.0 --ghc 9.2.3`
|
|
||||||
|
|
||||||
All these use `cabal v2-install` under the hood, so all build components are cached.
|
|
||||||
You can pass arbitrary arguments to cabal, e.g. set the index state like so:
|
|
||||||
|
|
||||||
```sh
|
|
||||||
ghcup compile hls --git-ref master --ghc 9.2.3 -- --index-state=2022-06-12T00:00:00Z --allow-newer
|
|
||||||
```
|
|
||||||
|
|
||||||
You can pass `--ghc <ver>` multiple times to install for many GHCs at once.
|
|
||||||
|
|
||||||
When building from git sources, ghcup will auto-detect the HLS version that the git commit corresponds to
|
|
||||||
from the `haskell-language-server.cabal` file. This version might not have been updated since the last release.
|
|
||||||
If you want to avoid overwriting the existing installed HLS version, you can instruct ghcup to use `git describe`
|
|
||||||
to set the HLS version instead:
|
|
||||||
|
|
||||||
```sh
|
|
||||||
ghcup compile hls --git-ref master --ghc 9.2.3 --git-describe-version
|
|
||||||
```
|
|
||||||
|
|
||||||
You can also set the version explicitly:
|
|
||||||
|
|
||||||
```sh
|
|
||||||
ghcup compile hls --git-ref master --ghc 9.2.3 --overwrite-version 1.7.0.0-p1
|
|
||||||
```
|
|
||||||
|
|
||||||
To instruct cabal to run `cabal update` before building, run `ghcup compile hls --version 1.7.0.0 --ghc 9.2.3 --cabal-update`
|
|
||||||
|
|
||||||
As always, check `ghcup compile hls --help`.
|
|
||||||
|
|
||||||
### Cross support
|
### Cross support
|
||||||
|
|
||||||
ghcup can compile and install a cross GHC for any target. However, this
|
ghcup can compile and install a cross GHC for any target. However, this
|
||||||
@@ -353,7 +310,7 @@ gpg-setting: GPGLax # GPGStrict | GPGLax | GPGNone
|
|||||||
|
|
||||||
In `GPGStrict` mode, ghcup will fail if verification fails. In `GPGLax` mode it will just print a warning.
|
In `GPGStrict` mode, ghcup will fail if verification fails. In `GPGLax` mode it will just print a warning.
|
||||||
You can also pass the mode via `ghcup --gpg <strict|lax|none>`.
|
You can also pass the mode via `ghcup --gpg <strict|lax|none>`.
|
||||||
|
|
||||||
# Tips and tricks
|
# Tips and tricks
|
||||||
|
|
||||||
## ghcup run
|
## ghcup run
|
||||||
@@ -367,3 +324,34 @@ ghcup run --ghc 8.10.7 --cabal latest --hls latest --stack latest --install -- c
|
|||||||
```
|
```
|
||||||
|
|
||||||
This will execute vscode with GHC set to 8.10.7 and all other tools to their latest version.
|
This will execute vscode with GHC set to 8.10.7 and all other tools to their latest version.
|
||||||
|
|
||||||
|
# Troubleshooting
|
||||||
|
|
||||||
|
## Script immediately exits on windows
|
||||||
|
|
||||||
|
There are two possible reasons:
|
||||||
|
|
||||||
|
1. your company blocks the script (some have a whitelist)... ask your administrator
|
||||||
|
2. your Antivirus or Windows Defender interfere with the installation. Disable them temporarily.
|
||||||
|
|
||||||
|
## C compiler cannot create executables
|
||||||
|
|
||||||
|
### Darwin
|
||||||
|
|
||||||
|
You need to update your XCode command line tools, e.g. [like this](https://stackoverflow.com/questions/34617452/how-to-update-xcode-from-command-line).
|
||||||
|
|
||||||
|
## Certificate authority errors (curl)
|
||||||
|
|
||||||
|
If your certificates are outdated or improperly configured, curl may be unable
|
||||||
|
to download ghcup.
|
||||||
|
|
||||||
|
There are two known workarounds:
|
||||||
|
|
||||||
|
1. Tell curl to ignore certificate errors (dangerous): `curl -k https://gitlab.haskell.org/haskell/ghcup-hs/-/raw/master/scripts/bootstrap/bootstrap-haskell | GHCUP_CURL_OPTS="-k" sh`
|
||||||
|
2. Try to use wget instead: `wget -O /dev/stdout https://gitlab.haskell.org/haskell/ghcup-hs/-/raw/master/scripts/bootstrap/bootstrap-haskell | BOOTSTRAP_HASKELL_DOWNLOADER=wget sh`
|
||||||
|
|
||||||
|
On windows, you can disable curl like so:
|
||||||
|
|
||||||
|
```pwsh
|
||||||
|
Set-ExecutionPolicy Bypass -Scope Process -Force;[System.Net.ServicePointManager]::SecurityProtocol = [System.Net.ServicePointManager]::SecurityProtocol -bor 3072;Invoke-Command -ScriptBlock ([ScriptBlock]::Create((Invoke-WebRequest https://www.haskell.org/ghcup/sh/bootstrap-haskell.ps1 -UseBasicParsing))) -ArgumentList $true
|
||||||
|
```
|
||||||
|
|||||||
@@ -57,7 +57,7 @@ hide:
|
|||||||
</section>
|
</section>
|
||||||
|
|
||||||
<p id="help" class="ghcup-help">
|
<p id="help" class="ghcup-help">
|
||||||
Need help? Ask on
|
Need help? Check the <a href="guide/#troubleshooting">Troubleshooting section</a> or ask on
|
||||||
<span>
|
<span>
|
||||||
<a href="https://kiwiirc.com/nextclient/irc.libera.chat/?nick=Guest%7C?#haskell,#haskell-ghcup">
|
<a href="https://kiwiirc.com/nextclient/irc.libera.chat/?nick=Guest%7C?#haskell,#haskell-ghcup">
|
||||||
<img src="irc.svg" alt="" />
|
<img src="irc.svg" alt="" />
|
||||||
|
|||||||
@@ -33,8 +33,8 @@ module GHCup (
|
|||||||
|
|
||||||
|
|
||||||
import GHCup.Cabal
|
import GHCup.Cabal
|
||||||
import GHCup.GHC hiding ( GHCVer(..) )
|
import GHCup.GHC
|
||||||
import GHCup.HLS hiding ( HLSVer(..) )
|
import GHCup.HLS
|
||||||
import GHCup.Stack
|
import GHCup.Stack
|
||||||
import GHCup.List
|
import GHCup.List
|
||||||
import GHCup.Download
|
import GHCup.Download
|
||||||
@@ -206,8 +206,9 @@ rmGhcupDirs = do
|
|||||||
| isWindows = removeDirIfEmptyOrIsSymlink binDir
|
| isWindows = removeDirIfEmptyOrIsSymlink binDir
|
||||||
| otherwise = do
|
| otherwise = do
|
||||||
isXDGStyle <- liftIO useXDG
|
isXDGStyle <- liftIO useXDG
|
||||||
when (not isXDGStyle) $
|
if not isXDGStyle
|
||||||
removeDirIfEmptyOrIsSymlink binDir
|
then removeDirIfEmptyOrIsSymlink binDir
|
||||||
|
else pure ()
|
||||||
|
|
||||||
reportRemainingFiles :: (MonadMask m, MonadIO m) => FilePath -> m [FilePath]
|
reportRemainingFiles :: (MonadMask m, MonadIO m) => FilePath -> m [FilePath]
|
||||||
reportRemainingFiles dir = do
|
reportRemainingFiles dir = do
|
||||||
|
|||||||
@@ -80,12 +80,6 @@ import qualified Data.Text.Encoding as E
|
|||||||
import qualified Text.Megaparsec as MP
|
import qualified Text.Megaparsec as MP
|
||||||
|
|
||||||
|
|
||||||
data GHCVer v = SourceDist v
|
|
||||||
| GitDist GitBranch
|
|
||||||
| RemoteDist URI
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
---------------------
|
---------------------
|
||||||
--[ Tool fetching ]--
|
--[ Tool fetching ]--
|
||||||
---------------------
|
---------------------
|
||||||
@@ -613,7 +607,7 @@ compileGHC :: ( MonadMask m
|
|||||||
, MonadUnliftIO m
|
, MonadUnliftIO m
|
||||||
, MonadFail m
|
, MonadFail m
|
||||||
)
|
)
|
||||||
=> GHCVer GHCTargetVersion
|
=> Either GHCTargetVersion GitBranch -- ^ version to install
|
||||||
-> Maybe Version -- ^ overwrite version
|
-> Maybe Version -- ^ overwrite version
|
||||||
-> Either Version FilePath -- ^ version to bootstrap with
|
-> Either Version FilePath -- ^ version to bootstrap with
|
||||||
-> Maybe Int -- ^ jobs
|
-> Maybe Int -- ^ jobs
|
||||||
@@ -656,7 +650,7 @@ compileGHC targetGhc ov bstrap jobs mbuildConfig patches aargs buildFlavour hadr
|
|||||||
|
|
||||||
(workdir, tmpUnpack, tver) <- case targetGhc of
|
(workdir, tmpUnpack, tver) <- case targetGhc of
|
||||||
-- unpack from version tarball
|
-- unpack from version tarball
|
||||||
SourceDist tver -> do
|
Left tver -> do
|
||||||
lift $ logDebug $ "Requested to compile: " <> tVerToText tver <> " with " <> either prettyVer T.pack bstrap
|
lift $ logDebug $ "Requested to compile: " <> tVerToText tver <> " with " <> either prettyVer T.pack bstrap
|
||||||
|
|
||||||
-- download source tarball
|
-- download source tarball
|
||||||
@@ -677,31 +671,8 @@ compileGHC targetGhc ov bstrap jobs mbuildConfig patches aargs buildFlavour hadr
|
|||||||
|
|
||||||
pure (workdir, tmpUnpack, tver)
|
pure (workdir, tmpUnpack, tver)
|
||||||
|
|
||||||
RemoteDist uri -> do
|
|
||||||
lift $ logDebug $ "Requested to compile (from uri): " <> T.pack (show uri)
|
|
||||||
|
|
||||||
-- download source tarball
|
|
||||||
tmpDownload <- lift withGHCupTmpDir
|
|
||||||
tmpUnpack <- lift mkGhcupTmpDir
|
|
||||||
tar <- liftE $ download uri Nothing Nothing (fromGHCupPath tmpDownload) Nothing False
|
|
||||||
(bf, tver) <- liftE $ cleanUpOnError @'[UnknownArchive, ArchiveResult, ProcessError] tmpUnpack $ do
|
|
||||||
liftE $ unpackToDir (fromGHCupPath tmpUnpack) tar
|
|
||||||
let regex = [s|^(.*/)*boot$|] :: B.ByteString
|
|
||||||
[bootFile] <- liftIO $ findFilesDeep
|
|
||||||
tmpUnpack
|
|
||||||
(makeRegexOpts compExtended
|
|
||||||
execBlank
|
|
||||||
regex
|
|
||||||
)
|
|
||||||
tver <- liftE $ getGHCVer (appendGHCupPath tmpUnpack (takeDirectory bootFile))
|
|
||||||
pure (bootFile, tver)
|
|
||||||
|
|
||||||
let workdir = appendGHCupPath tmpUnpack (takeDirectory bf)
|
|
||||||
|
|
||||||
pure (workdir, tmpUnpack, mkTVer tver)
|
|
||||||
|
|
||||||
-- clone from git
|
-- clone from git
|
||||||
GitDist GitBranch{..} -> do
|
Right GitBranch{..} -> do
|
||||||
tmpUnpack <- lift mkGhcupTmpDir
|
tmpUnpack <- lift mkGhcupTmpDir
|
||||||
let git args = execLogged "git" ("--no-pager":args) (Just $ fromGHCupPath tmpUnpack) "git" Nothing
|
let git args = execLogged "git" ("--no-pager":args) (Just $ fromGHCupPath tmpUnpack) "git" Nothing
|
||||||
tver <- reThrowAll @_ @'[PatchFailed, ProcessError, NotFoundInPATH, DigestError, DownloadFailed, GPGError] DownloadFailed $ do
|
tver <- reThrowAll @_ @'[PatchFailed, ProcessError, NotFoundInPATH, DigestError, DownloadFailed, GPGError] DownloadFailed $ do
|
||||||
@@ -744,7 +715,14 @@ compileGHC targetGhc ov bstrap jobs mbuildConfig patches aargs buildFlavour hadr
|
|||||||
liftE $ applyAnyPatch patches (fromGHCupPath tmpUnpack)
|
liftE $ applyAnyPatch patches (fromGHCupPath tmpUnpack)
|
||||||
|
|
||||||
-- bootstrap
|
-- bootstrap
|
||||||
tver <- liftE $ getGHCVer tmpUnpack
|
lEM $ execWithGhcEnv "python3" ["./boot"] (Just $ fromGHCupPath tmpUnpack) "ghc-bootstrap"
|
||||||
|
lEM $ execWithGhcEnv "sh" ["./configure"] (Just $ fromGHCupPath tmpUnpack) "ghc-bootstrap"
|
||||||
|
CapturedProcess {..} <- lift $ makeOut
|
||||||
|
["show!", "--quiet", "VALUE=ProjectVersion" ] (Just $ fromGHCupPath tmpUnpack)
|
||||||
|
tver <- case _exitCode of
|
||||||
|
ExitSuccess -> throwEither . MP.parse ghcProjectVersion "" . T.pack . stripNewlineEnd . T.unpack . decUTF8Safe' $ _stdOut
|
||||||
|
ExitFailure c -> fail ("Could not figure out GHC project version. Exit code was: " <> show c <> ". Error was: " <> T.unpack (decUTF8Safe' _stdErr))
|
||||||
|
|
||||||
liftE $ catchWarn $ lEM @_ @'[ProcessError] $ darwinNotarization _rPlatform (fromGHCupPath tmpUnpack)
|
liftE $ catchWarn $ lEM @_ @'[ProcessError] $ darwinNotarization _rPlatform (fromGHCupPath tmpUnpack)
|
||||||
lift $ logInfo $ "Examining git ref " <> T.pack ref <> "\n " <>
|
lift $ logInfo $ "Examining git ref " <> T.pack ref <> "\n " <>
|
||||||
"GHC version (from Makefile): " <> prettyVer tver <>
|
"GHC version (from Makefile): " <> prettyVer tver <>
|
||||||
@@ -817,29 +795,11 @@ compileGHC targetGhc ov bstrap jobs mbuildConfig patches aargs buildFlavour hadr
|
|||||||
pure installVer
|
pure installVer
|
||||||
|
|
||||||
where
|
where
|
||||||
getGHCVer :: ( MonadReader env m
|
|
||||||
, HasSettings env
|
|
||||||
, HasDirs env
|
|
||||||
, HasLog env
|
|
||||||
, MonadIO m
|
|
||||||
, MonadThrow m
|
|
||||||
)
|
|
||||||
=> GHCupPath
|
|
||||||
-> Excepts '[ProcessError] m Version
|
|
||||||
getGHCVer tmpUnpack = do
|
|
||||||
lEM $ execWithGhcEnv "python3" ["./boot"] (Just $ fromGHCupPath tmpUnpack) "ghc-bootstrap"
|
|
||||||
lEM $ execWithGhcEnv "sh" ["./configure"] (Just $ fromGHCupPath tmpUnpack) "ghc-bootstrap"
|
|
||||||
CapturedProcess {..} <- lift $ makeOut
|
|
||||||
["show!", "--quiet", "VALUE=ProjectVersion" ] (Just $ fromGHCupPath tmpUnpack)
|
|
||||||
case _exitCode of
|
|
||||||
ExitSuccess -> throwEither . MP.parse ghcProjectVersion "" . T.pack . stripNewlineEnd . T.unpack . decUTF8Safe' $ _stdOut
|
|
||||||
ExitFailure c -> throwE $ NonZeroExit c "make" ["show!", "--quiet", "VALUE=ProjectVersion" ]
|
|
||||||
|
|
||||||
defaultConf =
|
defaultConf =
|
||||||
let cross_mk = $(LitE . StringL <$> (qAddDependentFile "data/build_mk/cross" >> runIO (readFile "data/build_mk/cross")))
|
let cross_mk = $(LitE . StringL <$> (qAddDependentFile "data/build_mk/cross" >> runIO (readFile "data/build_mk/cross")))
|
||||||
default_mk = $(LitE . StringL <$> (qAddDependentFile "data/build_mk/default" >> runIO (readFile "data/build_mk/default")))
|
default_mk = $(LitE . StringL <$> (qAddDependentFile "data/build_mk/default" >> runIO (readFile "data/build_mk/default")))
|
||||||
in case targetGhc of
|
in case targetGhc of
|
||||||
SourceDist (GHCTargetVersion (Just _) _) -> cross_mk
|
Left (GHCTargetVersion (Just _) _) -> cross_mk
|
||||||
_ -> default_mk
|
_ -> default_mk
|
||||||
|
|
||||||
compileHadrianBindist :: ( MonadReader env m
|
compileHadrianBindist :: ( MonadReader env m
|
||||||
@@ -1016,7 +976,7 @@ compileGHC targetGhc ov bstrap jobs mbuildConfig patches aargs buildFlavour hadr
|
|||||||
|
|
||||||
-- for cross, we need Stage1Only
|
-- for cross, we need Stage1Only
|
||||||
case targetGhc of
|
case targetGhc of
|
||||||
SourceDist (GHCTargetVersion (Just _) _) -> when ("Stage1Only = YES" `notElem` lines') $ throwE
|
Left (GHCTargetVersion (Just _) _) -> when ("Stage1Only = YES" `notElem` lines') $ throwE
|
||||||
(InvalidBuildConfig
|
(InvalidBuildConfig
|
||||||
[s|Cross compiling needs to be a Stage1 build, add "Stage1Only = YES" to your config!|]
|
[s|Cross compiling needs to be a Stage1 build, add "Stage1Only = YES" to your config!|]
|
||||||
)
|
)
|
||||||
|
|||||||
107
lib/GHCup/HLS.hs
107
lib/GHCup/HLS.hs
@@ -71,12 +71,6 @@ import qualified Text.Megaparsec as MP
|
|||||||
import Text.PrettyPrint.HughesPJClass (prettyShow)
|
import Text.PrettyPrint.HughesPJClass (prettyShow)
|
||||||
|
|
||||||
|
|
||||||
data HLSVer = SourceDist Version
|
|
||||||
| GitDist GitBranch
|
|
||||||
| HackageDist Version
|
|
||||||
| RemoteDist URI
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
--------------------
|
--------------------
|
||||||
--[ Installation ]--
|
--[ Installation ]--
|
||||||
@@ -330,14 +324,13 @@ compileHLS :: ( MonadMask m
|
|||||||
, MonadUnliftIO m
|
, MonadUnliftIO m
|
||||||
, MonadFail m
|
, MonadFail m
|
||||||
)
|
)
|
||||||
=> HLSVer
|
=> Either Version GitBranch
|
||||||
-> [Version]
|
-> [Version]
|
||||||
-> Maybe Int
|
-> Maybe Int
|
||||||
-> Either Bool Version
|
-> Either Bool Version
|
||||||
-> InstallDir
|
-> InstallDir
|
||||||
-> Maybe (Either FilePath URI)
|
-> Maybe (Either FilePath URI)
|
||||||
-> Maybe URI
|
-> Maybe URI
|
||||||
-> Bool
|
|
||||||
-> Maybe (Either FilePath [URI]) -- ^ patches
|
-> Maybe (Either FilePath [URI]) -- ^ patches
|
||||||
-> [Text] -- ^ additional args to cabal install
|
-> [Text] -- ^ additional args to cabal install
|
||||||
-> Excepts '[ NoDownload
|
-> Excepts '[ NoDownload
|
||||||
@@ -350,18 +343,15 @@ compileHLS :: ( MonadMask m
|
|||||||
, BuildFailed
|
, BuildFailed
|
||||||
, NotInstalled
|
, NotInstalled
|
||||||
] m Version
|
] m Version
|
||||||
compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal updateCabal patches cabalArgs = do
|
compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal patches cabalArgs = do
|
||||||
PlatformRequest { .. } <- lift getPlatformReq
|
PlatformRequest { .. } <- lift getPlatformReq
|
||||||
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
||||||
Dirs { .. } <- lift getDirs
|
Dirs { .. } <- lift getDirs
|
||||||
|
|
||||||
when updateCabal $ reThrowAll @_ @'[ProcessError] DownloadFailed $ do
|
|
||||||
lift $ logInfo "Updating cabal DB"
|
|
||||||
lEM $ exec "cabal" ["update"] (Just $ fromGHCupPath tmpDir) Nothing
|
|
||||||
|
|
||||||
(workdir, tmpUnpack, tver, git_describe) <- case targetHLS of
|
(workdir, tver, git_describe) <- case targetHLS of
|
||||||
-- unpack from version tarball
|
-- unpack from version tarball
|
||||||
SourceDist tver -> do
|
Left tver -> do
|
||||||
lift $ logDebug $ "Requested to compile: " <> prettyVer tver
|
lift $ logDebug $ "Requested to compile: " <> prettyVer tver
|
||||||
|
|
||||||
-- download source tarball
|
-- download source tarball
|
||||||
@@ -379,47 +369,10 @@ compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal upda
|
|||||||
(liftE . intoSubdir tmpUnpack)
|
(liftE . intoSubdir tmpUnpack)
|
||||||
(view dlSubdir dlInfo)
|
(view dlSubdir dlInfo)
|
||||||
|
|
||||||
pure (workdir, tmpUnpack, tver, Nothing)
|
pure (workdir, tver, Nothing)
|
||||||
|
|
||||||
HackageDist tver -> do
|
|
||||||
lift $ logDebug $ "Requested to compile (from hackage): " <> prettyVer tver
|
|
||||||
|
|
||||||
-- download source tarball
|
|
||||||
tmpUnpack <- lift mkGhcupTmpDir
|
|
||||||
let hls = "haskell-language-server-" <> T.unpack (prettyVer tver)
|
|
||||||
reThrowAll @_ @'[ProcessError] DownloadFailed $ do
|
|
||||||
-- unpack
|
|
||||||
lEM $ exec "cabal" ["unpack", hls] (Just $ fromGHCupPath tmpUnpack) Nothing
|
|
||||||
|
|
||||||
let workdir = appendGHCupPath tmpUnpack hls
|
|
||||||
|
|
||||||
pure (workdir, tmpUnpack, tver, Nothing)
|
|
||||||
|
|
||||||
RemoteDist uri -> do
|
|
||||||
lift $ logDebug $ "Requested to compile (from uri): " <> T.pack (show uri)
|
|
||||||
|
|
||||||
-- download source tarball
|
|
||||||
tmpDownload <- lift withGHCupTmpDir
|
|
||||||
tmpUnpack <- lift mkGhcupTmpDir
|
|
||||||
tar <- liftE $ download uri Nothing Nothing (fromGHCupPath tmpDownload) Nothing False
|
|
||||||
(cf, tver) <- liftE $ cleanUpOnError tmpUnpack $ do
|
|
||||||
unpackToDir (fromGHCupPath tmpUnpack) tar
|
|
||||||
let regex = [s|^(.*/)*haskell-language-server\.cabal$|] :: B.ByteString
|
|
||||||
[cabalFile] <- liftIO $ findFilesDeep
|
|
||||||
tmpUnpack
|
|
||||||
(makeRegexOpts compExtended
|
|
||||||
execBlank
|
|
||||||
regex
|
|
||||||
)
|
|
||||||
tver <- getCabalVersion (fromGHCupPath tmpUnpack </> cabalFile)
|
|
||||||
pure (cabalFile, tver)
|
|
||||||
|
|
||||||
let workdir = appendGHCupPath tmpUnpack (takeDirectory cf)
|
|
||||||
|
|
||||||
pure (workdir, tmpUnpack, tver, Nothing)
|
|
||||||
|
|
||||||
-- clone from git
|
-- clone from git
|
||||||
GitDist GitBranch{..} -> do
|
Right GitBranch{..} -> do
|
||||||
tmpUnpack <- lift mkGhcupTmpDir
|
tmpUnpack <- lift mkGhcupTmpDir
|
||||||
let git args = execLogged "git" ("--no-pager":args) (Just $ fromGHCupPath tmpUnpack) "git" Nothing
|
let git args = execLogged "git" ("--no-pager":args) (Just $ fromGHCupPath tmpUnpack) "git" Nothing
|
||||||
reThrowAll @_ @'[ProcessError] DownloadFailed $ do
|
reThrowAll @_ @'[ProcessError] DownloadFailed $ do
|
||||||
@@ -456,7 +409,15 @@ compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal upda
|
|||||||
then pure Nothing
|
then pure Nothing
|
||||||
else fmap Just $ gitOut ["describe", "--tags"] (fromGHCupPath tmpUnpack)
|
else fmap Just $ gitOut ["describe", "--tags"] (fromGHCupPath tmpUnpack)
|
||||||
chash <- gitOut ["rev-parse", "HEAD" ] (fromGHCupPath tmpUnpack)
|
chash <- gitOut ["rev-parse", "HEAD" ] (fromGHCupPath tmpUnpack)
|
||||||
tver <- getCabalVersion (fromGHCupPath tmpUnpack </> "haskell-language-server.cabal")
|
(Just gpd) <- parseGenericPackageDescriptionMaybe
|
||||||
|
<$> liftIO (B.readFile (fromGHCupPath tmpUnpack </> "haskell-language-server.cabal"))
|
||||||
|
let tver = (\c -> Version Nothing c [] Nothing)
|
||||||
|
. NE.fromList . fmap (NE.fromList . (:[]) . digits . fromIntegral)
|
||||||
|
. versionNumbers
|
||||||
|
. pkgVersion
|
||||||
|
. package
|
||||||
|
. packageDescription
|
||||||
|
$ gpd
|
||||||
|
|
||||||
liftE $ catchWarn $ lEM @_ @'[ProcessError] $ darwinNotarization _rPlatform (fromGHCupPath tmpUnpack)
|
liftE $ catchWarn $ lEM @_ @'[ProcessError] $ darwinNotarization _rPlatform (fromGHCupPath tmpUnpack)
|
||||||
lift $ logInfo $ "Examining git ref " <> T.pack ref <> "\n " <>
|
lift $ logInfo $ "Examining git ref " <> T.pack ref <> "\n " <>
|
||||||
@@ -464,7 +425,7 @@ compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal upda
|
|||||||
(if not shallow_clone then "\n " <> "'git describe' output: " <> fromJust git_describe else mempty) <>
|
(if not shallow_clone then "\n " <> "'git describe' output: " <> fromJust git_describe else mempty) <>
|
||||||
(if isCommitHash ref then mempty else "\n " <> "commit hash: " <> chash)
|
(if isCommitHash ref then mempty else "\n " <> "commit hash: " <> chash)
|
||||||
|
|
||||||
pure (tmpUnpack, tmpUnpack, tver, git_describe)
|
pure (tmpUnpack, tver, git_describe)
|
||||||
|
|
||||||
-- the version that's installed may differ from the
|
-- the version that's installed may differ from the
|
||||||
-- compiled version, so the user can overwrite it
|
-- compiled version, so the user can overwrite it
|
||||||
@@ -480,7 +441,7 @@ compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal upda
|
|||||||
Right v -> pure v
|
Right v -> pure v
|
||||||
|
|
||||||
liftE $ runBuildAction
|
liftE $ runBuildAction
|
||||||
tmpUnpack
|
workdir
|
||||||
(reThrowAll @_ @'[GPGError, DownloadFailed, DigestError, PatchFailed, ProcessError, FileAlreadyExistsError, CopyError] @'[BuildFailed] (BuildFailed $ fromGHCupPath workdir) $ do
|
(reThrowAll @_ @'[GPGError, DownloadFailed, DigestError, PatchFailed, ProcessError, FileAlreadyExistsError, CopyError] @'[BuildFailed] (BuildFailed $ fromGHCupPath workdir) $ do
|
||||||
let tmpInstallDir = fromGHCupPath workdir </> "out"
|
let tmpInstallDir = fromGHCupPath workdir </> "out"
|
||||||
liftIO $ createDirRecursive' tmpInstallDir
|
liftIO $ createDirRecursive' tmpInstallDir
|
||||||
@@ -496,22 +457,14 @@ compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal upda
|
|||||||
pure "cabal.project"
|
pure "cabal.project"
|
||||||
| otherwise -> pure (takeFileName cp)
|
| otherwise -> pure (takeFileName cp)
|
||||||
Just (Right uri) -> do
|
Just (Right uri) -> do
|
||||||
tmpUnpack' <- lift withGHCupTmpDir
|
tmpUnpack <- lift withGHCupTmpDir
|
||||||
cp <- liftE $ download uri Nothing Nothing (fromGHCupPath tmpUnpack') (Just "cabal.project") False
|
cp <- liftE $ download uri Nothing Nothing (fromGHCupPath tmpUnpack) (Just "cabal.project") False
|
||||||
copyFileE cp (fromGHCupPath workdir </> "cabal.project") False
|
copyFileE cp (fromGHCupPath workdir </> "cabal.project") False
|
||||||
pure "cabal.project"
|
pure "cabal.project"
|
||||||
Nothing
|
Nothing -> pure "cabal.project"
|
||||||
| HackageDist _ <- targetHLS -> do
|
|
||||||
liftIO $ B.writeFile (fromGHCupPath workdir </> "cabal.project") "packages: ./"
|
|
||||||
pure "cabal.project"
|
|
||||||
| RemoteDist _ <- targetHLS -> do
|
|
||||||
let cabalFile = fromGHCupPath workdir </> "cabal.project"
|
|
||||||
liftIO $ whenM (not <$> doesFileExist cabalFile) $ B.writeFile cabalFile "packages: ./"
|
|
||||||
pure "cabal.project"
|
|
||||||
| otherwise -> pure "cabal.project"
|
|
||||||
forM_ cabalProjectLocal $ \uri -> do
|
forM_ cabalProjectLocal $ \uri -> do
|
||||||
tmpUnpack' <- lift withGHCupTmpDir
|
tmpUnpack <- lift withGHCupTmpDir
|
||||||
cpl <- liftE $ download uri Nothing Nothing (fromGHCupPath tmpUnpack') (Just (cp <.> "local")) False
|
cpl <- liftE $ download uri Nothing Nothing (fromGHCupPath tmpUnpack) (Just (cp <.> "local")) False
|
||||||
copyFileE cpl (fromGHCupPath workdir </> cp <.> "local") False
|
copyFileE cpl (fromGHCupPath workdir </> cp <.> "local") False
|
||||||
artifacts <- forM (sort ghcs) $ \ghc -> do
|
artifacts <- forM (sort ghcs) $ \ghc -> do
|
||||||
let ghcInstallDir = tmpInstallDir </> T.unpack (prettyVer ghc)
|
let ghcInstallDir = tmpInstallDir </> T.unpack (prettyVer ghc)
|
||||||
@@ -705,19 +658,3 @@ rmHLSVer ver = do
|
|||||||
case headMay . reverse . sort $ hlsVers of
|
case headMay . reverse . sort $ hlsVers of
|
||||||
Just latestver -> liftE $ setHLS latestver SetHLSOnly Nothing
|
Just latestver -> liftE $ setHLS latestver SetHLSOnly Nothing
|
||||||
Nothing -> pure ()
|
Nothing -> pure ()
|
||||||
|
|
||||||
|
|
||||||
getCabalVersion :: (MonadIO m, MonadFail m) => FilePath -> m Version
|
|
||||||
getCabalVersion fp = do
|
|
||||||
contents <- liftIO $ B.readFile fp
|
|
||||||
gpd <- case parseGenericPackageDescriptionMaybe contents of
|
|
||||||
Nothing -> fail $ "could not parse cabal file: " <> fp
|
|
||||||
Just r -> pure r
|
|
||||||
let tver = (\c -> Version Nothing c [] Nothing)
|
|
||||||
. NE.fromList . fmap (NE.fromList . (:[]) . digits . fromIntegral)
|
|
||||||
. versionNumbers
|
|
||||||
. pkgVersion
|
|
||||||
. package
|
|
||||||
. packageDescription
|
|
||||||
$ gpd
|
|
||||||
pure tver
|
|
||||||
|
|||||||
@@ -654,3 +654,10 @@ isSafeDir (IsolateDirResolved _) = False
|
|||||||
isSafeDir (GHCupDir _) = True
|
isSafeDir (GHCupDir _) = True
|
||||||
isSafeDir (GHCupBinDir _) = False
|
isSafeDir (GHCupBinDir _) = False
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|||||||
@@ -1097,8 +1097,7 @@ runBuildAction bdir action = do
|
|||||||
|
|
||||||
-- | Clean up the given directory if the action fails,
|
-- | Clean up the given directory if the action fails,
|
||||||
-- depending on the Settings.
|
-- depending on the Settings.
|
||||||
cleanUpOnError :: forall e m a env .
|
cleanUpOnError :: ( MonadReader env m
|
||||||
( MonadReader env m
|
|
||||||
, HasDirs env
|
, HasDirs env
|
||||||
, HasSettings env
|
, HasSettings env
|
||||||
, MonadIO m
|
, MonadIO m
|
||||||
|
|||||||
@@ -16,6 +16,7 @@
|
|||||||
# * BOOTSTRAP_HASKELL_INSTALL_HLS - whether to install latest hls
|
# * BOOTSTRAP_HASKELL_INSTALL_HLS - whether to install latest hls
|
||||||
# * BOOTSTRAP_HASKELL_ADJUST_BASHRC - whether to adjust PATH in bashrc (prepend)
|
# * BOOTSTRAP_HASKELL_ADJUST_BASHRC - whether to adjust PATH in bashrc (prepend)
|
||||||
# * BOOTSTRAP_HASKELL_ADJUST_CABAL_CONFIG - whether to adjust mingw paths in cabal.config on windows
|
# * BOOTSTRAP_HASKELL_ADJUST_CABAL_CONFIG - whether to adjust mingw paths in cabal.config on windows
|
||||||
|
# * BOOTSTRAP_HASKELL_DOWNLOADER - which downloader to use (default: curl)
|
||||||
# * GHCUP_BASE_URL - the base url for ghcup binary download (use this to overwrite https://downloads.haskell.org/~ghcup with a mirror)
|
# * GHCUP_BASE_URL - the base url for ghcup binary download (use this to overwrite https://downloads.haskell.org/~ghcup with a mirror)
|
||||||
|
|
||||||
# License: LGPL-3.0
|
# License: LGPL-3.0
|
||||||
@@ -30,6 +31,7 @@ ghver="0.1.17.8"
|
|||||||
: "${GHCUP_BASE_URL:=https://downloads.haskell.org/~ghcup}"
|
: "${GHCUP_BASE_URL:=https://downloads.haskell.org/~ghcup}"
|
||||||
|
|
||||||
export GHCUP_SKIP_UPDATE_CHECK=yes
|
export GHCUP_SKIP_UPDATE_CHECK=yes
|
||||||
|
: "${BOOTSTRAP_HASKELL_DOWNLOADER:=curl}"
|
||||||
|
|
||||||
case "${plat}" in
|
case "${plat}" in
|
||||||
MSYS*|MINGW*)
|
MSYS*|MINGW*)
|
||||||
@@ -322,11 +324,35 @@ download_ghcup() {
|
|||||||
esac
|
esac
|
||||||
case "${plat}" in
|
case "${plat}" in
|
||||||
MSYS*|MINGW*)
|
MSYS*|MINGW*)
|
||||||
edo curl -Lf "${_url}" > "${GHCUP_BIN}"/ghcup.exe
|
case "${BOOTSTRAP_HASKELL_DOWNLOADER}" in
|
||||||
|
"curl")
|
||||||
|
# shellcheck disable=SC2086
|
||||||
|
edo curl -Lf ${GHCUP_CURL_OPTS} "${_url}" > "${GHCUP_BIN}"/ghcup.exe
|
||||||
|
;;
|
||||||
|
"wget")
|
||||||
|
# shellcheck disable=SC2086
|
||||||
|
edo wget -O /dev/stdout ${GHCUP_WGET_OPTS} "${_url}" > "${GHCUP_BIN}"/ghcup.exe
|
||||||
|
;;
|
||||||
|
*)
|
||||||
|
die "Unknown downloader: ${BOOTSTRAP_HASKELL_DOWNLOADER}"
|
||||||
|
;;
|
||||||
|
esac
|
||||||
edo chmod +x "${GHCUP_BIN}"/ghcup.exe
|
edo chmod +x "${GHCUP_BIN}"/ghcup.exe
|
||||||
;;
|
;;
|
||||||
*)
|
*)
|
||||||
edo curl -Lf "${_url}" > "${GHCUP_BIN}"/ghcup
|
case "${BOOTSTRAP_HASKELL_DOWNLOADER}" in
|
||||||
|
"curl")
|
||||||
|
# shellcheck disable=SC2086
|
||||||
|
edo curl -Lf ${GHCUP_CURL_OPTS} "${_url}" > "${GHCUP_BIN}"/ghcup
|
||||||
|
;;
|
||||||
|
"wget")
|
||||||
|
# shellcheck disable=SC2086
|
||||||
|
edo wget -O /dev/stdout ${GHCUP_WGET_OPTS} "${_url}" > "${GHCUP_BIN}"/ghcup
|
||||||
|
;;
|
||||||
|
*)
|
||||||
|
die "Unknown downloader: ${BOOTSTRAP_HASKELL_DOWNLOADER}"
|
||||||
|
;;
|
||||||
|
esac
|
||||||
edo chmod +x "${GHCUP_BIN}"/ghcup
|
edo chmod +x "${GHCUP_BIN}"/ghcup
|
||||||
;;
|
;;
|
||||||
esac
|
esac
|
||||||
@@ -353,6 +379,17 @@ download_ghcup() {
|
|||||||
|
|
||||||
# shellcheck disable=SC1090
|
# shellcheck disable=SC1090
|
||||||
edo . "${GHCUP_DIR}"/env
|
edo . "${GHCUP_DIR}"/env
|
||||||
|
case "${BOOTSTRAP_HASKELL_DOWNLOADER}" in
|
||||||
|
"curl")
|
||||||
|
eghcup config set downloader Curl
|
||||||
|
;;
|
||||||
|
"wget")
|
||||||
|
eghcup config set downloader Wget
|
||||||
|
;;
|
||||||
|
*)
|
||||||
|
die "Unknown downloader: ${BOOTSTRAP_HASKELL_DOWNLOADER}"
|
||||||
|
;;
|
||||||
|
esac
|
||||||
eghcup upgrade
|
eghcup upgrade
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@@ -36,7 +36,9 @@ param (
|
|||||||
# Instead of installing a new MSys2, use an existing installation
|
# Instead of installing a new MSys2, use an existing installation
|
||||||
[string]$ExistingMsys2Dir,
|
[string]$ExistingMsys2Dir,
|
||||||
# Specify the cabal root directory (default: '$InstallDir\cabal')
|
# Specify the cabal root directory (default: '$InstallDir\cabal')
|
||||||
[string]$CabalDir
|
[string]$CabalDir,
|
||||||
|
# Whether to disable use of curl.exe
|
||||||
|
[switch]$DisableCurl
|
||||||
)
|
)
|
||||||
|
|
||||||
$Silent = !$Interactive
|
$Silent = !$Interactive
|
||||||
@@ -425,7 +427,7 @@ if (!(Test-Path -Path ('{0}' -f $MsysDir))) {
|
|||||||
$archive = 'msys2-x86_64-latest.sfx.exe'
|
$archive = 'msys2-x86_64-latest.sfx.exe'
|
||||||
$archivePath = ('{0}\{1}' -f ([IO.Path]::GetTempPath()), "$archive")
|
$archivePath = ('{0}\{1}' -f ([IO.Path]::GetTempPath()), "$archive")
|
||||||
|
|
||||||
if (Get-Command -Name 'curl.exe' -ErrorAction SilentlyContinue) {
|
if ((Get-Command -Name 'curl.exe' -ErrorAction SilentlyContinue) -and !($DisableCurl)) {
|
||||||
Exec "curl.exe" '-o' "$archivePath" ('https://repo.msys2.org/distrib/{0}' -f "$archive")
|
Exec "curl.exe" '-o' "$archivePath" ('https://repo.msys2.org/distrib/{0}' -f "$archive")
|
||||||
} else {
|
} else {
|
||||||
Get-FileWCSynchronous -url ('https://repo.msys2.org/distrib/{0}' -f $archive) -destinationFolder ([IO.Path]::GetTempPath()) -includeStats
|
Get-FileWCSynchronous -url ('https://repo.msys2.org/distrib/{0}' -f $archive) -destinationFolder ([IO.Path]::GetTempPath()) -includeStats
|
||||||
@@ -591,10 +593,17 @@ if ($Minimal) {
|
|||||||
$MinimalExport = 'export BOOTSTRAP_HASKELL_MINIMAL=1 ;'
|
$MinimalExport = 'export BOOTSTRAP_HASKELL_MINIMAL=1 ;'
|
||||||
}
|
}
|
||||||
|
|
||||||
if ((Get-Process -ID $PID).ProcessName.StartsWith("bootstrap-haskell") -Or $InBash) {
|
if ($DisableCurl) {
|
||||||
Exec "$Bash" '-lc' ('{4} {6} {7} {8} {9} [ -n ''{1}'' ] && export GHCUP_MSYS2=$(cygpath -m ''{1}'') ; [ -n ''{2}'' ] && export GHCUP_INSTALL_BASE_PREFIX=$(cygpath -m ''{2}/'') ; export PATH=$(cygpath -u ''{3}/bin''):$PATH ; export CABAL_DIR=''{5}'' ; [[ ''{0}'' = https* ]] && curl --proto ''=https'' --tlsv1.2 -sSf {0} | bash || cat $(cygpath -m ''{0}'') | bash' -f $BootstrapUrl, $MsysDir, $GhcupBasePrefix, $GhcupDir, $SilentExport, $CabalDirFull, $StackInstallExport, $HLSInstallExport, $AdjustCabalConfigExport, $MinimalExport)
|
$BootstrapDownloader = 'export BOOTSTRAP_HASKELL_DOWNLOADER=wget ;'
|
||||||
|
$DownloadScript = 'wget -O /dev/stdout'
|
||||||
} else {
|
} else {
|
||||||
Exec "$Msys2Shell" '-mingw64' '-mintty' '-c' ('{4} {6} {7} {8} {9} [ -n ''{1}'' ] && export GHCUP_MSYS2=$(cygpath -m ''{1}'') ; [ -n ''{2}'' ] && export GHCUP_INSTALL_BASE_PREFIX=$(cygpath -m ''{2}/'') ; export PATH=$(cygpath -u ''{3}/bin''):$PATH ; export CABAL_DIR=''{5}'' ; trap ''echo Press any key to exit && read -n 1 && exit'' 2 ; [[ ''{0}'' = https* ]] && curl --proto ''=https'' --tlsv1.2 -sSf {0} | bash || cat $(cygpath -m ''{0}'') | bash ; echo ''Press any key to exit'' && read -n 1' -f $BootstrapUrl, $MsysDir, $GhcupBasePrefix, $GhcupDir, $SilentExport, $CabalDirFull, $StackInstallExport, $HLSInstallExport, $AdjustCabalConfigExport, $MinimalExport)
|
$DownloadScript = 'curl --proto ''=https'' --tlsv1.2 -sSf'
|
||||||
|
}
|
||||||
|
|
||||||
|
if ((Get-Process -ID $PID).ProcessName.StartsWith("bootstrap-haskell") -Or $InBash) {
|
||||||
|
Exec "$Bash" '-lc' ('{4} {6} {7} {8} {9} {10} [ -n ''{1}'' ] && export GHCUP_MSYS2=$(cygpath -m ''{1}'') ; [ -n ''{2}'' ] && export GHCUP_INSTALL_BASE_PREFIX=$(cygpath -m ''{2}/'') ; export PATH=$(cygpath -u ''{3}/bin''):$PATH ; export CABAL_DIR=''{5}'' ; [[ ''{0}'' = https* ]] && {11} {0} | bash || cat $(cygpath -m ''{0}'') | bash' -f $BootstrapUrl, $MsysDir, $GhcupBasePrefix, $GhcupDir, $SilentExport, $CabalDirFull, $StackInstallExport, $HLSInstallExport, $AdjustCabalConfigExport, $MinimalExport, $BootstrapDownloader, $DownloadScript)
|
||||||
|
} else {
|
||||||
|
Exec "$Msys2Shell" '-mingw64' '-mintty' '-c' ('{4} {6} {7} {8} {9} {10} [ -n ''{1}'' ] && export GHCUP_MSYS2=$(cygpath -m ''{1}'') ; [ -n ''{2}'' ] && export GHCUP_INSTALL_BASE_PREFIX=$(cygpath -m ''{2}/'') ; export PATH=$(cygpath -u ''{3}/bin''):$PATH ; export CABAL_DIR=''{5}'' ; trap ''echo Press any key to exit && read -n 1 && exit'' 2 ; [[ ''{0}'' = https* ]] && {11} {0} | bash || cat $(cygpath -m ''{0}'') | bash ; echo ''Press any key to exit'' && read -n 1' -f $BootstrapUrl, $MsysDir, $GhcupBasePrefix, $GhcupDir, $SilentExport, $CabalDirFull, $StackInstallExport, $HLSInstallExport, $AdjustCabalConfigExport, $MinimalExport, $BootstrapDownloader, $DownloadScript)
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
|
|||||||
Reference in New Issue
Block a user