Allow to build from arbitrary GHC source dists
This commit is contained in:
parent
63f22b28d7
commit
9fb2889696
@ -12,6 +12,8 @@ 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
|
||||||
@ -64,7 +66,7 @@ data CompileCommand = CompileGHC GHCCompileOptions
|
|||||||
|
|
||||||
|
|
||||||
data GHCCompileOptions = GHCCompileOptions
|
data GHCCompileOptions = GHCCompileOptions
|
||||||
{ targetGhc :: Either Version GitBranch
|
{ targetGhc :: GHC.GHCVer Version
|
||||||
, bootstrapGhc :: Either Version FilePath
|
, bootstrapGhc :: Either Version FilePath
|
||||||
, jobs :: Maybe Int
|
, jobs :: Maybe Int
|
||||||
, buildConfig :: Maybe FilePath
|
, buildConfig :: Maybe FilePath
|
||||||
@ -80,7 +82,7 @@ data GHCCompileOptions = GHCCompileOptions
|
|||||||
|
|
||||||
|
|
||||||
data HLSCompileOptions = HLSCompileOptions
|
data HLSCompileOptions = HLSCompileOptions
|
||||||
{ targetHLS :: HLSVer
|
{ targetHLS :: HLS.HLSVer
|
||||||
, jobs :: Maybe Int
|
, jobs :: Maybe Int
|
||||||
, setCompile :: Bool
|
, setCompile :: Bool
|
||||||
, ovewrwiteVer :: Either Bool Version
|
, ovewrwiteVer :: Either Bool Version
|
||||||
@ -163,7 +165,7 @@ Examples:
|
|||||||
ghcCompileOpts :: Parser GHCCompileOptions
|
ghcCompileOpts :: Parser GHCCompileOptions
|
||||||
ghcCompileOpts =
|
ghcCompileOpts =
|
||||||
GHCCompileOptions
|
GHCCompileOptions
|
||||||
<$> ((Left <$> option
|
<$> ((GHC.SourceDist <$> option
|
||||||
(eitherReader
|
(eitherReader
|
||||||
(first (const "Not a valid version") . version . T.pack)
|
(first (const "Not a valid version") . version . T.pack)
|
||||||
)
|
)
|
||||||
@ -172,7 +174,7 @@ ghcCompileOpts =
|
|||||||
<> (completer $ versionCompleter Nothing GHC)
|
<> (completer $ versionCompleter Nothing GHC)
|
||||||
)
|
)
|
||||||
) <|>
|
) <|>
|
||||||
(Right <$> (GitBranch <$> option
|
(GHC.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"
|
"The git commit/branch/ref to build from"
|
||||||
@ -181,7 +183,18 @@ 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 ->
|
||||||
@ -273,7 +286,7 @@ ghcCompileOpts =
|
|||||||
hlsCompileOpts :: Parser HLSCompileOptions
|
hlsCompileOpts :: Parser HLSCompileOptions
|
||||||
hlsCompileOpts =
|
hlsCompileOpts =
|
||||||
HLSCompileOptions
|
HLSCompileOptions
|
||||||
<$> ((SourceDist <$> option
|
<$> ((HLS.SourceDist <$> option
|
||||||
(eitherReader
|
(eitherReader
|
||||||
(first (const "Not a valid version") . version . T.pack)
|
(first (const "Not a valid version") . version . T.pack)
|
||||||
)
|
)
|
||||||
@ -283,7 +296,7 @@ hlsCompileOpts =
|
|||||||
)
|
)
|
||||||
)
|
)
|
||||||
<|>
|
<|>
|
||||||
(GitDist <$> (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)"
|
||||||
@ -293,7 +306,7 @@ hlsCompileOpts =
|
|||||||
))
|
))
|
||||||
))
|
))
|
||||||
<|>
|
<|>
|
||||||
(HackageDist <$> (option
|
(HLS.HackageDist <$> (option
|
||||||
(eitherReader
|
(eitherReader
|
||||||
(first (const "Not a valid version") . version . T.pack)
|
(first (const "Not a valid version") . version . T.pack)
|
||||||
)
|
)
|
||||||
@ -304,7 +317,7 @@ hlsCompileOpts =
|
|||||||
))
|
))
|
||||||
<|>
|
<|>
|
||||||
(
|
(
|
||||||
RemoteDist <$> (option
|
HLS.RemoteDist <$> (option
|
||||||
(eitherReader uriParser)
|
(eitherReader uriParser)
|
||||||
(long "remote-source-dist" <> metavar "URI" <> help
|
(long "remote-source-dist" <> metavar "URI" <> help
|
||||||
"URI (https/http/file) to a HLS source distribution"
|
"URI (https/http/file) to a HLS source distribution"
|
||||||
@ -493,7 +506,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
|
||||||
SourceDist targetVer -> do
|
HLS.SourceDist 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
|
||||||
@ -544,7 +557,7 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
|
|||||||
(CompileGHC GHCCompileOptions {..}) ->
|
(CompileGHC GHCCompileOptions {..}) ->
|
||||||
runCompileGHC runAppState (do
|
runCompileGHC runAppState (do
|
||||||
case targetGhc of
|
case targetGhc of
|
||||||
Left targetVer -> do
|
GHC.SourceDist 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
|
||||||
@ -552,9 +565,12 @@ 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
|
||||||
Right _ -> pure ()
|
_ -> pure ()
|
||||||
targetVer <- liftE $ compileGHC
|
targetVer <- liftE $ compileGHC
|
||||||
(first (GHCTargetVersion crossTarget) targetGhc)
|
((\case
|
||||||
|
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,6 +14,8 @@ 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
|
||||||
@ -338,13 +340,13 @@ 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 = Left tver }))
|
alreadyInstalling (Compile (CompileGHC GHCCompileOptions{ targetGhc = GHC.SourceDist 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 = SourceDist tver }))
|
alreadyInstalling (Compile (CompileHLS HLSCompileOptions{ targetHLS = HLS.SourceDist tver }))
|
||||||
(HLS, ver) = cmp' HLS (Just $ ToolVersion (mkTVer tver)) ver
|
(HLS, ver) = cmp' HLS (Just $ ToolVersion (mkTVer tver)) ver
|
||||||
alreadyInstalling (Compile (CompileHLS HLSCompileOptions{ targetHLS = HackageDist tver }))
|
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
|
||||||
|
@ -33,8 +33,8 @@ module GHCup (
|
|||||||
|
|
||||||
|
|
||||||
import GHCup.Cabal
|
import GHCup.Cabal
|
||||||
import GHCup.GHC
|
import GHCup.GHC hiding ( GHCVer(..) )
|
||||||
import GHCup.HLS
|
import GHCup.HLS hiding ( HLSVer(..) )
|
||||||
import GHCup.Stack
|
import GHCup.Stack
|
||||||
import GHCup.List
|
import GHCup.List
|
||||||
import GHCup.Download
|
import GHCup.Download
|
||||||
|
@ -80,6 +80,12 @@ 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 ]--
|
||||||
---------------------
|
---------------------
|
||||||
@ -607,7 +613,7 @@ compileGHC :: ( MonadMask m
|
|||||||
, MonadUnliftIO m
|
, MonadUnliftIO m
|
||||||
, MonadFail m
|
, MonadFail m
|
||||||
)
|
)
|
||||||
=> Either GHCTargetVersion GitBranch -- ^ version to install
|
=> GHCVer GHCTargetVersion
|
||||||
-> 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
|
||||||
@ -650,7 +656,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
|
||||||
Left tver -> do
|
SourceDist 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
|
||||||
@ -671,8 +677,31 @@ 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
|
||||||
Right GitBranch{..} -> do
|
GitDist 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
|
||||||
@ -715,14 +744,7 @@ compileGHC targetGhc ov bstrap jobs mbuildConfig patches aargs buildFlavour hadr
|
|||||||
liftE $ applyAnyPatch patches (fromGHCupPath tmpUnpack)
|
liftE $ applyAnyPatch patches (fromGHCupPath tmpUnpack)
|
||||||
|
|
||||||
-- bootstrap
|
-- bootstrap
|
||||||
lEM $ execWithGhcEnv "python3" ["./boot"] (Just $ fromGHCupPath tmpUnpack) "ghc-bootstrap"
|
tver <- liftE $ getGHCVer tmpUnpack
|
||||||
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 <>
|
||||||
@ -795,11 +817,29 @@ 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
|
||||||
Left (GHCTargetVersion (Just _) _) -> cross_mk
|
SourceDist (GHCTargetVersion (Just _) _) -> cross_mk
|
||||||
_ -> default_mk
|
_ -> default_mk
|
||||||
|
|
||||||
compileHadrianBindist :: ( MonadReader env m
|
compileHadrianBindist :: ( MonadReader env m
|
||||||
@ -976,7 +1016,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
|
||||||
Left (GHCTargetVersion (Just _) _) -> when ("Stage1Only = YES" `notElem` lines') $ throwE
|
SourceDist (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!|]
|
||||||
)
|
)
|
||||||
|
@ -71,6 +71,12 @@ 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 ]--
|
||||||
@ -394,8 +400,8 @@ compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal patc
|
|||||||
tar <- liftE $ download uri Nothing Nothing (fromGHCupPath tmpDownload) Nothing False
|
tar <- liftE $ download uri Nothing Nothing (fromGHCupPath tmpDownload) Nothing False
|
||||||
(cf, tver) <- liftE $ cleanUpOnError tmpUnpack $ do
|
(cf, tver) <- liftE $ cleanUpOnError tmpUnpack $ do
|
||||||
unpackToDir (fromGHCupPath tmpUnpack) tar
|
unpackToDir (fromGHCupPath tmpUnpack) tar
|
||||||
let regex = [s|haskell-language-server\.cabal$|] :: B.ByteString
|
let regex = [s|^(.*/)*haskell-language-server\.cabal$|] :: B.ByteString
|
||||||
[cabalFile] <- liftIO $ handleIO (\_ -> pure []) $ findFilesDeep
|
[cabalFile] <- liftIO $ findFilesDeep
|
||||||
tmpUnpack
|
tmpUnpack
|
||||||
(makeRegexOpts compExtended
|
(makeRegexOpts compExtended
|
||||||
execBlank
|
execBlank
|
||||||
|
@ -654,12 +654,3 @@ isSafeDir (IsolateDirResolved _) = False
|
|||||||
isSafeDir (GHCupDir _) = True
|
isSafeDir (GHCupDir _) = True
|
||||||
isSafeDir (GHCupBinDir _) = False
|
isSafeDir (GHCupBinDir _) = False
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
data HLSVer = SourceDist Version
|
|
||||||
| GitDist GitBranch
|
|
||||||
| HackageDist Version
|
|
||||||
| RemoteDist URI
|
|
||||||
|
|
||||||
|
|
||||||
|
@ -1097,7 +1097,8 @@ 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 :: ( MonadReader env m
|
cleanUpOnError :: forall e m a env .
|
||||||
|
( MonadReader env m
|
||||||
, HasDirs env
|
, HasDirs env
|
||||||
, HasSettings env
|
, HasSettings env
|
||||||
, MonadIO m
|
, MonadIO m
|
||||||
|
Loading…
Reference in New Issue
Block a user