Compare commits

...

2 Commits

Author SHA1 Message Date
ff60744cc6
WIP 2023-05-01 16:01:57 +08:00
e0222b4007
First draft of implementing revisions 2023-02-27 13:39:48 +08:00
22 changed files with 21995 additions and 21412 deletions

View File

@ -11,7 +11,6 @@ module BrickMain where
import GHCup import GHCup
import GHCup.Download import GHCup.Download
import GHCup.Errors import GHCup.Errors
import GHCup.Types.Optics ( getDirs )
import GHCup.Types hiding ( LeanAppState(..) ) import GHCup.Types hiding ( LeanAppState(..) )
import GHCup.Utils import GHCup.Utils
import GHCup.OptParse.Common (logGHCPostRm) import GHCup.OptParse.Common (logGHCPostRm)
@ -20,6 +19,7 @@ import GHCup.Prelude.File
import GHCup.Prelude.Logger import GHCup.Prelude.Logger
import GHCup.Prelude.Process import GHCup.Prelude.Process
import GHCup.Prompts import GHCup.Prompts
import GHCup.Types.Optics hiding ( getGHCupInfo )
import Brick import Brick
import Brick.Widgets.Border import Brick.Widgets.Border
@ -53,6 +53,7 @@ import System.Exit
import System.IO.Unsafe import System.IO.Unsafe
import Text.PrettyPrint.HughesPJClass ( prettyShow ) import Text.PrettyPrint.HughesPJClass ( prettyShow )
import URI.ByteString import URI.ByteString
import Optics ( view )
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Lazy.Builder as B import qualified Data.Text.Lazy.Builder as B
@ -477,7 +478,7 @@ install' _ (_, ListResult {..}) = do
) )
>>= \case >>= \case
VRight (vi, Dirs{..}, Just ce) -> do VRight (vi, Dirs{..}, Just ce) -> do
forM_ (_viPostInstall =<< vi) $ \msg -> logInfo msg forM_ (view viPostInstall =<< vi) $ \msg -> logInfo msg
case lTool of case lTool of
GHCup -> do GHCup -> do
up <- liftIO $ fmap (either (const Nothing) Just) up <- liftIO $ fmap (either (const Nothing) Just)
@ -489,7 +490,7 @@ install' _ (_, ListResult {..}) = do
_ -> pure () _ -> pure ()
pure $ Right () pure $ Right ()
VRight (vi, _, _) -> do VRight (vi, _, _) -> do
forM_ (_viPostInstall =<< vi) $ \msg -> logInfo msg forM_ (view viPostInstall =<< vi) $ \msg -> logInfo msg
logInfo "Please restart 'ghcup' for the changes to take effect" logInfo "Please restart 'ghcup' for the changes to take effect"
pure $ Right () pure $ Right ()
VLeft (V (AlreadyInstalled _ _)) -> pure $ Right () VLeft (V (AlreadyInstalled _ _)) -> pure $ Right ()
@ -564,7 +565,7 @@ del' _ (_, ListResult {..}) = do
>>= \case >>= \case
VRight vi -> do VRight vi -> do
logGHCPostRm (mkTVer lVer) logGHCPostRm (mkTVer lVer)
forM_ (_viPostRemove =<< vi) $ \msg -> forM_ (view viPostRemove =<< vi) $ \msg ->
logInfo msg logInfo msg
pure $ Right () pure $ Right ()
VLeft e -> pure $ Left (prettyHFError e) VLeft e -> pure $ Left (prettyHFError e)

View File

@ -57,6 +57,7 @@ import System.Process ( readProcess )
import System.FilePath import System.FilePath
import Text.HTML.TagSoup hiding ( Tag ) import Text.HTML.TagSoup hiding ( Tag )
import URI.ByteString import URI.ByteString
import Optics ( view )
import qualified Data.ByteString.UTF8 as UTF8 import qualified Data.ByteString.UTF8 as UTF8
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
@ -451,7 +452,7 @@ tagCompleter tool add = listIOCompleter $ do
case mGhcUpInfo of case mGhcUpInfo of
VRight ghcupInfo -> do VRight ghcupInfo -> do
let allTags = filter (/= Old) let allTags = filter (/= Old)
$ _viTags =<< M.elems (availableToolVersions (_ghcupDownloads ghcupInfo) tool) $ (view viTags) =<< M.elems (availableToolVersions (_ghcupDownloads ghcupInfo) tool)
pure $ nub $ (add ++) $ fmap tagToString allTags pure $ nub $ (add ++) $ fmap tagToString allTags
VLeft _ -> pure (nub $ ["recommended", "latest", "latest-prerelease"] ++ add) VLeft _ -> pure (nub $ ["recommended", "latest", "latest-prerelease"] ++ add)

View File

@ -16,11 +16,11 @@ import qualified GHCup.GHC as GHC
import qualified GHCup.HLS as HLS import qualified GHCup.HLS as HLS
import GHCup.Errors import GHCup.Errors
import GHCup.Types import GHCup.Types
import GHCup.Types.Optics
import GHCup.Utils import GHCup.Utils
import GHCup.Prelude.Logger import GHCup.Prelude.Logger
import GHCup.Prelude.String.QQ import GHCup.Prelude.String.QQ
import GHCup.OptParse.Common import GHCup.OptParse.Common
import GHCup.Types.Optics
#if !MIN_VERSION_base(4,13,0) #if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail ( MonadFail ) import Control.Monad.Fail ( MonadFail )
@ -36,6 +36,7 @@ import Data.Versions ( Version, prettyVer, version, p
import qualified Data.Versions as V 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 Optics
import Options.Applicative hiding ( style ) import Options.Applicative hiding ( style )
import Options.Applicative.Help.Pretty ( text ) import Options.Applicative.Help.Pretty ( text )
import Prelude hiding ( appendFile ) import Prelude hiding ( appendFile )
@ -511,7 +512,7 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
HLS.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_ (view viPreCompile =<< vi) $ \msg -> do
lift $ logInfo msg lift $ logInfo msg
lift $ logInfo lift $ logInfo
"...waiting for 5 seconds, you can still abort..." "...waiting for 5 seconds, you can still abort..."
@ -539,7 +540,7 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
VRight (vi, tv) -> do VRight (vi, tv) -> do
runLogger $ logInfo runLogger $ logInfo
"HLS successfully compiled and installed" "HLS successfully compiled and installed"
forM_ (_viPostInstall =<< vi) $ \msg -> forM_ (view viPostInstall =<< vi) $ \msg ->
runLogger $ logInfo msg runLogger $ logInfo msg
liftIO $ putStr (T.unpack $ prettyVer tv) liftIO $ putStr (T.unpack $ prettyVer tv)
pure ExitSuccess pure ExitSuccess
@ -563,7 +564,7 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
GHC.SourceDist 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_ (view viPreCompile =<< vi) $ \msg -> do
lift $ logInfo msg lift $ logInfo msg
lift $ logInfo lift $ logInfo
"...waiting for 5 seconds, you can still abort..." "...waiting for 5 seconds, you can still abort..."
@ -593,7 +594,7 @@ compile compileCommand settings Dirs{..} runAppState runLogger = do
VRight (vi, tv) -> do VRight (vi, tv) -> do
runLogger $ logInfo runLogger $ logInfo
"GHC successfully compiled and installed" "GHC successfully compiled and installed"
forM_ (_viPostInstall =<< vi) $ \msg -> forM_ (view viPostInstall =<< vi) $ \msg ->
runLogger $ logInfo msg runLogger $ logInfo msg
liftIO $ putStr (T.unpack $ tVerToText tv) liftIO $ putStr (T.unpack $ tVerToText tv)
pure ExitSuccess pure ExitSuccess

View File

@ -23,6 +23,7 @@ import GHCup.Utils.Dirs
import GHCup.Prelude import GHCup.Prelude
import GHCup.Prelude.Logger import GHCup.Prelude.Logger
import GHCup.Prelude.String.QQ import GHCup.Prelude.String.QQ
import GHCup.Types.Optics
import Codec.Archive import Codec.Archive
#if !MIN_VERSION_base(4,13,0) #if !MIN_VERSION_base(4,13,0)
@ -36,6 +37,7 @@ import Data.Maybe
import Haskus.Utils.Variant.Excepts import Haskus.Utils.Variant.Excepts
import Options.Applicative hiding ( style ) import Options.Applicative hiding ( style )
import Options.Applicative.Help.Pretty ( text ) import Options.Applicative.Help.Pretty ( text )
import Optics
import Prelude hiding ( appendFile ) import Prelude hiding ( appendFile )
import System.Exit import System.Exit
import URI.ByteString hiding ( uriParser ) import URI.ByteString hiding ( uriParser )
@ -345,7 +347,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
>>= \case >>= \case
VRight vi -> do VRight vi -> do
runLogger $ logInfo "GHC installation successful" runLogger $ logInfo "GHC installation successful"
forM_ (_viPostInstall =<< vi) $ \msg -> forM_ (view viPostInstall =<< vi) $ \msg ->
runLogger $ logInfo msg runLogger $ logInfo msg
pure ExitSuccess pure ExitSuccess
@ -413,7 +415,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
>>= \case >>= \case
VRight vi -> do VRight vi -> do
runLogger $ logInfo "Cabal installation successful" runLogger $ logInfo "Cabal installation successful"
forM_ (_viPostInstall =<< vi) $ \msg -> forM_ (view viPostInstall =<< vi) $ \msg ->
runLogger $ logInfo msg runLogger $ logInfo msg
pure ExitSuccess pure ExitSuccess
VLeft e@(V (AlreadyInstalled _ _)) -> do VLeft e@(V (AlreadyInstalled _ _)) -> do
@ -463,7 +465,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
>>= \case >>= \case
VRight vi -> do VRight vi -> do
runLogger $ logInfo "HLS installation successful" runLogger $ logInfo "HLS installation successful"
forM_ (_viPostInstall =<< vi) $ \msg -> forM_ (view viPostInstall =<< vi) $ \msg ->
runLogger $ logInfo msg runLogger $ logInfo msg
pure ExitSuccess pure ExitSuccess
VLeft e@(V (AlreadyInstalled _ _)) -> do VLeft e@(V (AlreadyInstalled _ _)) -> do
@ -512,7 +514,7 @@ install installCommand settings getAppState' runLogger = case installCommand of
>>= \case >>= \case
VRight vi -> do VRight vi -> do
runLogger $ logInfo "Stack installation successful" runLogger $ logInfo "Stack installation successful"
forM_ (_viPostInstall =<< vi) $ \msg -> forM_ (view viPostInstall =<< vi) $ \msg ->
runLogger $ logInfo msg runLogger $ logInfo msg
pure ExitSuccess pure ExitSuccess
VLeft e@(V (AlreadyInstalled _ _)) -> do VLeft e@(V (AlreadyInstalled _ _)) -> do

View File

@ -3,7 +3,6 @@
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
@ -34,6 +33,7 @@ import Haskus.Utils.Variant.Excepts
import Options.Applicative hiding ( style ) import Options.Applicative hiding ( style )
import Prelude hiding ( appendFile ) import Prelude hiding ( appendFile )
import System.Exit import System.Exit
import Optics
import qualified Data.Text as T import qualified Data.Text as T
import Control.Exception.Safe (MonadMask) import Control.Exception.Safe (MonadMask)
@ -227,5 +227,5 @@ rm rmCommand runAppState runLogger = case rmCommand of
pure $ ExitFailure 15 pure $ ExitFailure 15
postRmLog vi = postRmLog vi =
forM_ (_viPostRemove =<< vi) $ \msg -> forM_ (view viPostRemove =<< vi) $ \msg ->
runLogger $ logInfo msg runLogger $ logInfo msg

View File

@ -28,6 +28,7 @@ import Haskus.Utils.Variant.Excepts
import Options.Applicative hiding ( style ) import Options.Applicative hiding ( style )
import Prelude hiding ( appendFile ) import Prelude hiding ( appendFile )
import System.Exit import System.Exit
import Optics ( view )
import qualified Data.Text as T import qualified Data.Text as T
import Control.Exception.Safe (MonadMask) import Control.Exception.Safe (MonadMask)
@ -144,7 +145,7 @@ upgrade uOpts force' fatal Dirs{..} runAppState runLogger = do
let vi = fromJust $ snd <$> getLatest dls GHCup let vi = fromJust $ snd <$> getLatest dls GHCup
runLogger $ logInfo $ runLogger $ logInfo $
"Successfully upgraded GHCup to version " <> pretty_v "Successfully upgraded GHCup to version " <> pretty_v
forM_ (_viPostInstall vi) $ \msg -> forM_ (view viPostInstall vi) $ \msg ->
runLogger $ logInfo msg runLogger $ logInfo msg
pure ExitSuccess pure ExitSuccess
VLeft (V NoUpdate) -> do VLeft (V NoUpdate) -> do

View File

@ -9,7 +9,7 @@ constraints: http-io-streams -brotli,
any.aeson >= 2.0.1.0 any.aeson >= 2.0.1.0
package libarchive package libarchive
flags: -system-libarchive flags: +system-libarchive
package aeson-pretty package aeson-pretty
flags: +lib-only flags: +lib-only

View File

@ -258,6 +258,7 @@ executable ghcup
, libarchive ^>=3.0.3.0 , libarchive ^>=3.0.3.0
, megaparsec >=8.0.0 && <9.3 , megaparsec >=8.0.0 && <9.3
, mtl ^>=2.2 , mtl ^>=2.2
, optics ^>=0.4
, optparse-applicative >=0.15.1.0 && <0.18 , optparse-applicative >=0.15.1.0 && <0.18
, pretty ^>=1.1.3.1 , pretty ^>=1.1.3.1
, pretty-terminal ^>=0.1.0.0 , pretty-terminal ^>=0.1.0.0

View File

@ -177,7 +177,7 @@ installCabalBin :: ( MonadMask m
, MonadUnliftIO m , MonadUnliftIO m
, MonadFail m , MonadFail m
) )
=> Version => VersionRev
-> InstallDir -> InstallDir
-> Bool -- force install -> Bool -- force install
-> Excepts -> Excepts
@ -198,7 +198,7 @@ installCabalBin :: ( MonadMask m
() ()
installCabalBin ver installDir forceInstall = do installCabalBin ver installDir forceInstall = do
dlinfo <- liftE $ getDownloadInfo Cabal ver dlinfo <- liftE $ getDownloadInfo Cabal ver
installCabalBindist dlinfo ver installDir forceInstall installCabalBindist dlinfo (vVersion ver) installDir forceInstall
----------------- -----------------

View File

@ -277,19 +277,19 @@ getDownloadInfo :: ( MonadReader env m
, HasGHCupInfo env , HasGHCupInfo env
) )
=> Tool => Tool
-> Version -> VersionRev
-- ^ tool version -- ^ tool version
-> Excepts -> Excepts
'[NoDownload] '[NoDownload]
m m
DownloadInfo DownloadInfo
getDownloadInfo t v = do getDownloadInfo t (VersionRev v vr) = do
(PlatformRequest a p mv) <- lift getPlatformReq (PlatformRequest a p mv) <- lift getPlatformReq
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
let distro_preview f g = let distro_preview f g =
let platformVersionSpec = let platformVersionSpec =
preview (ix t % ix v % viArch % ix a % ix (f p)) dls preview (ix t % ix v % viDownload % ix vr % viArch % ix a % ix (f p)) dls
mv' = g mv mv' = g mv
in fmap snd in fmap snd
. find . find

View File

@ -78,6 +78,7 @@ import qualified Data.Text as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
import qualified Data.Text.Encoding as E import qualified Data.Text.Encoding as E
import qualified Text.Megaparsec as MP import qualified Text.Megaparsec as MP
import qualified Data.Map.Strict as M
data GHCVer v = SourceDist v data GHCVer v = SourceDist v
@ -105,7 +106,7 @@ testGHCVer :: ( MonadFail m
, MonadIO m , MonadIO m
, MonadUnliftIO m , MonadUnliftIO m
) )
=> Version => VersionRev
-> [T.Text] -> [T.Text]
-> Excepts -> Excepts
'[ DigestError '[ DigestError
@ -120,11 +121,11 @@ testGHCVer :: ( MonadFail m
] ]
m m
() ()
testGHCVer ver addMakeArgs = do testGHCVer (VersionRev ver vr) addMakeArgs = do
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
dlInfo <- dlInfo <-
preview (ix GHC % ix ver % viTestDL % _Just) dls preview (ix GHC % ix ver % viDownload % to M.toAscList % maybe _last ix vr % to snd % viTestDL % _Just) dls
?? NoDownload ?? NoDownload
liftE $ testGHCBindist dlInfo ver addMakeArgs liftE $ testGHCBindist dlInfo ver addMakeArgs
@ -243,7 +244,7 @@ fetchGHCSrc :: ( MonadFail m
, MonadIO m , MonadIO m
, MonadUnliftIO m , MonadUnliftIO m
) )
=> Version => VersionRev
-> Maybe FilePath -> Maybe FilePath
-> Excepts -> Excepts
'[ DigestError '[ DigestError
@ -254,10 +255,10 @@ fetchGHCSrc :: ( MonadFail m
] ]
m m
FilePath FilePath
fetchGHCSrc v mfp = do fetchGHCSrc (VersionRev v vr) mfp = do
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
dlInfo <- dlInfo <-
preview (ix GHC % ix v % viSourceDL % _Just) dls preview (ix GHC % ix v % viDownload % to M.toAscList % maybe _last ix vr % to snd % viSourceDL % _Just) dls
?? NoDownload ?? NoDownload
liftE $ downloadCached' dlInfo Nothing mfp liftE $ downloadCached' dlInfo Nothing mfp
@ -804,7 +805,7 @@ compileGHC targetGhc ov bstrap jobs mbuildConfig patches aargs buildFlavour hadr
-- download source tarball -- download source tarball
dlInfo <- dlInfo <-
preview (ix GHC % ix (tver ^. tvVersion) % viSourceDL % _Just) dls preview (ix GHC % ix (tver ^. tvVersion) % viDownload % _last % viSourceDL % _Just) dls
?? NoDownload ?? NoDownload
dl <- liftE $ downloadCached dlInfo Nothing dl <- liftE $ downloadCached dlInfo Nothing

View File

@ -368,7 +368,7 @@ compileHLS targetHLS ghcs jobs ov installDir cabalProject cabalProjectLocal upda
-- download source tarball -- download source tarball
dlInfo <- dlInfo <-
preview (ix HLS % ix tver % viSourceDL % _Just) dls preview (ix HLS % ix tver % viDownload % _last % viSourceDL % _Just) dls
?? NoDownload ?? NoDownload
dl <- liftE $ downloadCached dlInfo Nothing dl <- liftE $ downloadCached dlInfo Nothing

View File

@ -308,7 +308,7 @@ listVersions lt' criteria = do
isOld = maybe True (> currentVer) latestVer && maybe True (> currentVer) recommendedVer isOld = maybe True (> currentVer) latestVer && maybe True (> currentVer) recommendedVer
in if | Map.member currentVer av -> Nothing in if | Map.member currentVer av -> Nothing
| otherwise -> Just $ ListResult { lVer = currentVer | otherwise -> Just $ ListResult { lVer = currentVer
, lTag = maybe (if isOld then [Old] else []) _viTags listVer , lTag = maybe (if isOld then [Old] else []) (view viTags) listVer
, lCross = Nothing , lCross = Nothing
, lTool = GHCup , lTool = GHCup
, fromSrc = False , fromSrc = False
@ -337,7 +337,8 @@ listVersions lt' criteria = do
-> [Either FilePath Version] -> [Either FilePath Version]
-> (Version, VersionInfo) -> (Version, VersionInfo)
-> m ListResult -> m ListResult
toListResult t cSet cabals hlsSet' hlses stackSet' stacks (v, _viTags -> tags) = do toListResult t cSet cabals hlsSet' hlses stackSet' stacks (v, vi) = do
let tags = view viTags vi
case t of case t of
GHC -> do GHC -> do
lNoBindist <- fmap (isLeft . veitherToEither) $ runE @'[NoDownload] $ getDownloadInfo GHC v lNoBindist <- fmap (isLeft . veitherToEither) $ runE @'[NoDownload] $ getDownloadInfo GHC v

View File

@ -28,6 +28,8 @@ import System.FilePath
import qualified Data.List.NonEmpty as NE import qualified Data.List.NonEmpty as NE
import qualified Data.Text as T import qualified Data.Text as T
import qualified Text.Megaparsec as MP import qualified Text.Megaparsec as MP
import Data.Char (digitToInt)
import Data.Data (Proxy(..))
choice' :: (MonadFail f, MP.MonadParsec e s f) => [f a] -> f a choice' :: (MonadFail f, MP.MonadParsec e s f) => [f a] -> f a
@ -86,7 +88,33 @@ ghcTargetVerP =
<$> (MP.try (Just <$> parseUntil1 (MP.chunk "-" *> verP') <* MP.chunk "-") <$> (MP.try (Just <$> parseUntil1 (MP.chunk "-" *> verP') <* MP.chunk "-")
<|> ((\ _ x -> x) Nothing <$> mempty) <|> ((\ _ x -> x) Nothing <$> mempty)
) )
<*> (version' <* MP.eof) <*> version'
where
verP' :: MP.Parsec Void Text Text
verP' = do
v <- version'
let startsWithDigists =
and
. take 3
. concatMap
(map
(\case
(Digits _) -> True
(Str _) -> False
) . NE.toList)
. NE.toList
$ _vChunks v
if startsWithDigists && isNothing (_vEpoch v)
then pure $ prettyVer v
else fail "Oh"
ghcTargetVerRevP :: MP.Parsec Void Text GHCTargetVersionRev
ghcTargetVerRevP =
(\x y -> GHCTargetVersionRev x y)
<$> (MP.try (Just <$> parseUntil1 (MP.chunk "-" *> verP') <* MP.chunk "-")
<|> ((\ _ x -> x) Nothing <$> mempty)
)
<*> versionRevP
where where
verP' :: MP.Parsec Void Text Text verP' :: MP.Parsec Void Text Text
verP' = do verP' = do
@ -122,3 +150,44 @@ verP suffix = do
pathSep :: MP.Parsec Void Text Char pathSep :: MP.Parsec Void Text Char
pathSep = MP.oneOf pathSeparators pathSep = MP.oneOf pathSeparators
versionRevP :: MP.Parsec Void Text VersionRev
versionRevP = MP.label "versionRev" $
MP.try (parseUntil (MP.try (MP.chunk "-r")) >>= versionWithRev) <|> ((`VersionRev` 0) <$> version')
where
versionWithRev ver = do
rest <- MP.getInput
MP.setInput ver
v <- version'
MP.setInput rest
_ <- MP.chunk "-r"
rev <- parseInt
pure $ VersionRev v rev
digit = MP.oneOf ['0'..'9'] MP.<?> "digit"
parseInt :: MP.Parsec Void Text Int
parseInt = MP.label "parseInt" $ do
i <- MP.tokensToChunk (Proxy :: Proxy Text) <$> some digit
pure $ numberValue 10 $ T.unpack i
numberValue :: Int -> String -> Int
numberValue base = foldl (\ x -> ((fromIntegral base * x) +) . fromIntegral . digitToInt) 0
userVersionRevP :: MP.Parsec Void Text UserVersionRev
userVersionRevP = MP.label "userVersionRev" $
((\(VersionRev v r) -> UserVersionRev v (Just r)) <$> MP.try versionRevP) <|> ((`UserVersionRev` Nothing) <$> version')
-- | Read a @VersionRev@ from a String.
--
-- - 3.3.2 -> VersionRev { vVersion = 3.3.3, vRev = 0 }
-- - 2.3.4-r3 -> VersionRev { vVersion = 2.3.4, vRev = 3 }
versionRev :: Text -> Either (MP.ParseErrorBundle Text Void) VersionRev
versionRev = MP.parse versionRevP ""
-- | Read a @UserVersionRev@ from a String.
--
-- - 3.3.2 -> UserVersionRev { vVersion = 3.3.3, vRev = Nothing }
-- - 2.3.4-r3 -> UserVersionRev { vVersion = 2.3.4, vRev = Just 3 }
userVersionRev :: Text -> Either (MP.ParseErrorBundle Text Void) UserVersionRev
userVersionRev = MP.parse userVersionRevP ""

View File

@ -44,6 +44,8 @@ import Graphics.Vty ( Key(..) )
import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T import qualified Data.Text as T
import qualified GHC.Generics as GHC import qualified GHC.Generics as GHC
import qualified Data.Map.Strict as M
#if !defined(BRICK) #if !defined(BRICK)
@ -135,6 +137,19 @@ instance NFData GlobalTool
-- | All necessary information of a tool version, including -- | All necessary information of a tool version, including
-- source download and per-architecture downloads. -- source download and per-architecture downloads.
data VersionInfo = VersionInfo data VersionInfo = VersionInfo
{ _viTags :: [Tag] -- ^ version specific tag
, _viChangeLog :: Maybe URI
, _viDownload :: Map Int VersionDownload
-- informative messages
, _viPostInstall :: Maybe Text
, _viPostRemove :: Maybe Text
, _viPreCompile :: Maybe Text
}
deriving (Eq, GHC.Generic, Show)
instance NFData VersionInfo
data VersionInfoLegacy = VersionInfoLegacy
{ _viTags :: [Tag] -- ^ version specific tag { _viTags :: [Tag] -- ^ version specific tag
, _viChangeLog :: Maybe URI , _viChangeLog :: Maybe URI
, _viSourceDL :: Maybe DownloadInfo -- ^ source tarball , _viSourceDL :: Maybe DownloadInfo -- ^ source tarball
@ -147,7 +162,47 @@ data VersionInfo = VersionInfo
} }
deriving (Eq, GHC.Generic, Show) deriving (Eq, GHC.Generic, Show)
instance NFData VersionInfo data VersionDownload = VersionDownload
{ _viSourceDL :: Maybe DownloadInfo -- ^ source tarball
, _viTestDL :: Maybe DownloadInfo -- ^ test tarball
, _viArch :: ArchitectureSpec -- ^ descend for binary downloads per arch
}
deriving (Eq, GHC.Generic, Show)
instance NFData VersionDownload
fromVersionInfoLegacy :: VersionInfoLegacy -> VersionInfo
fromVersionInfoLegacy VersionInfoLegacy{..} =
VersionInfo {_viDownload = M.singleton 0 $ VersionDownload { _viSourceDL = _viSourceDL
, _viTestDL = _viTestDL
, _viArch = _viArch
}
, ..}
-- | A version with a revision, denoting bindist 'versions' that are purely distribution specific.
--
-- The revision starts at 0.
data VersionRev = VersionRev { vVersion :: Version, vRev :: Int }
deriving (Ord, Eq, GHC.Generic, Show)
showVersionRev :: VersionRev -> Text
showVersionRev (VersionRev v 0) = prettyVer v
showVersionRev (VersionRev v r) = prettyVer v <> "-r" <> T.pack (show r)
-- | Similar to @VersionRev@, except that revision is optional. The absence of a revision has
-- a particular meaning:
--
-- * for install/prefetch: we want the latest available revision
-- * for compile: it depends
-- * for rm/set/unset/whereis/changelog: we want the revision that is installed (there can be only one)
--
-- Translating @UserVersionRev@ to @VersionRev@ requires context of the GHCup metadata,
-- installed versions and the to be executed command.
data UserVersionRev = UserVersionRev { uvVersion :: Version, uvRev :: Maybe Int }
deriving (Ord, Eq, GHC.Generic, Show)
-- | A tag. These are currently attached to a version of a tool. -- | A tag. These are currently attached to a version of a tool.
@ -586,12 +641,6 @@ data GHCTargetVersion = GHCTargetVersion
} }
deriving (Ord, Eq, Show) deriving (Ord, Eq, Show)
data GitBranch = GitBranch
{ ref :: String
, repo :: Maybe String
}
deriving (Ord, Eq, Show)
mkTVer :: Version -> GHCTargetVersion mkTVer :: Version -> GHCTargetVersion
mkTVer = GHCTargetVersion Nothing mkTVer = GHCTargetVersion Nothing
@ -599,10 +648,30 @@ tVerToText :: GHCTargetVersion -> Text
tVerToText (GHCTargetVersion (Just t) v') = t <> "-" <> prettyVer v' tVerToText (GHCTargetVersion (Just t) v') = t <> "-" <> prettyVer v'
tVerToText (GHCTargetVersion Nothing v') = prettyVer v' tVerToText (GHCTargetVersion Nothing v') = prettyVer v'
-- | A GHC identified by the target platform triple
-- and the version.
data GHCTargetVersionRev = GHCTargetVersionRev
{ _tvTargetRev :: Maybe Text
, _tvVersionRev :: VersionRev
}
deriving (Ord, Eq, Show)
mkTVerRev :: VersionRev -> GHCTargetVersionRev
mkTVerRev = GHCTargetVersionRev Nothing
tVerRevToText :: GHCTargetVersionRev -> Text
tVerRevToText (GHCTargetVersionRev (Just t) v') = t <> "-" <> showVersionRev v'
tVerRevToText (GHCTargetVersionRev Nothing v') = showVersionRev v'
-- | Assembles a path of the form: <target-triple>-<version> -- | Assembles a path of the form: <target-triple>-<version>
instance Pretty GHCTargetVersion where instance Pretty GHCTargetVersion where
pPrint = text . T.unpack . tVerToText pPrint = text . T.unpack . tVerToText
data GitBranch = GitBranch
{ ref :: String
, repo :: Maybe String
}
deriving (Ord, Eq, Show)
-- | A comparator and a version. -- | A comparator and a version.
data VersionCmp = VR_gt Versioning data VersionCmp = VR_gt Versioning

View File

@ -320,11 +320,18 @@ instance FromJSONKey (Maybe VersionRange) where
Right x -> pure $ Just x Right x -> pure $ Just x
Left e -> fail $ "Failure in (Maybe VersionRange) (FromJSONKey)" <> MP.errorBundlePretty e Left e -> fail $ "Failure in (Maybe VersionRange) (FromJSONKey)" <> MP.errorBundlePretty e
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''Requirements deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''Requirements
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''DownloadInfo deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''DownloadInfo
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VersionInfo deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VersionInfoLegacy
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VersionDownload
instance FromJSON VersionInfo where
parseJSON v = parseLegacy v <|> parseNew v
where
parseLegacy = fmap fromVersionInfoLegacy . parseJSON @VersionInfoLegacy
parseNew = genericParseJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel }
deriveToJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VersionInfo
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''GHCupInfo deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''GHCupInfo
deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''URLSource deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''URLSource
deriveJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''Key deriveJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''Key

View File

@ -37,6 +37,7 @@ makeLenses ''PlatformResult
makeLenses ''DownloadInfo makeLenses ''DownloadInfo
makeLenses ''Tag makeLenses ''Tag
makeLenses ''VersionInfo makeLenses ''VersionInfo
makeLenses ''VersionDownload
makeLenses ''GHCTargetVersion makeLenses ''GHCTargetVersion

View File

@ -228,7 +228,7 @@ rmMinorHLSSymlinks :: ( MonadReader env m
, MonadFail m , MonadFail m
, MonadMask m , MonadMask m
) )
=> Version => VersionRev
-> Excepts '[NotInstalled] m () -> Excepts '[NotInstalled] m ()
rmMinorHLSSymlinks ver = do rmMinorHLSSymlinks ver = do
Dirs {..} <- lift getDirs Dirs {..} <- lift getDirs
@ -281,7 +281,7 @@ rmPlainHLS = do
----------------------------------- -----------------------------------
-- | Whether the given GHC versin is installed. -- | Whether the given GHC version is installed.
ghcInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadThrow m) => GHCTargetVersion -> m Bool ghcInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadThrow m) => GHCTargetVersion -> m Bool
ghcInstalled ver = do ghcInstalled ver = do
ghcdir <- ghcupGHCDir ver ghcdir <- ghcupGHCDir ver
@ -299,7 +299,7 @@ ghcSrcInstalled ver = do
ghcSet :: (MonadReader env m, HasDirs env, MonadThrow m, MonadIO m) ghcSet :: (MonadReader env m, HasDirs env, MonadThrow m, MonadIO m)
=> Maybe Text -- ^ the target of the GHC version, if any => Maybe Text -- ^ the target of the GHC version, if any
-- (e.g. armv7-unknown-linux-gnueabihf) -- (e.g. armv7-unknown-linux-gnueabihf)
-> m (Maybe GHCTargetVersion) -> m (Maybe GHCTargetVersionRev)
ghcSet mtarget = do ghcSet mtarget = do
Dirs {..} <- getDirs Dirs {..} <- getDirs
let ghc = maybe "ghc" (\t -> T.unpack t <> "-ghc") mtarget let ghc = maybe "ghc" (\t -> T.unpack t <> "-ghc") mtarget
@ -311,7 +311,7 @@ ghcSet mtarget = do
link <- liftIO $ getLinkTarget ghcBin link <- liftIO $ getLinkTarget ghcBin
Just <$> ghcLinkVersion link Just <$> ghcLinkVersion link
where where
ghcLinkVersion :: MonadThrow m => FilePath -> m GHCTargetVersion ghcLinkVersion :: MonadThrow m => FilePath -> m GHCTargetVersionRev
ghcLinkVersion (T.pack . dropSuffix exeExt -> t) = throwEither $ MP.parse parser "ghcLinkVersion" t ghcLinkVersion (T.pack . dropSuffix exeExt -> t) = throwEither $ MP.parse parser "ghcLinkVersion" t
where where
parser = parser =
@ -321,7 +321,7 @@ ghcSet mtarget = do
r <- parseUntil1 pathSep r <- parseUntil1 pathSep
rest <- MP.getInput rest <- MP.getInput
MP.setInput r MP.setInput r
x <- ghcTargetVerP x <- ghcTargetVerRevP
MP.setInput rest MP.setInput rest
pure x pure x
) )
@ -347,13 +347,13 @@ getInstalledCabals :: ( MonadReader env m
, MonadIO m , MonadIO m
, MonadCatch m , MonadCatch m
) )
=> m [Either FilePath Version] => m [Either FilePath VersionRev]
getInstalledCabals = do getInstalledCabals = do
Dirs {..} <- getDirs Dirs {..} <- getDirs
bins <- liftIO $ handleIO (\_ -> pure []) $ findFiles bins <- liftIO $ handleIO (\_ -> pure []) $ findFiles
binDir binDir
(makeRegexOpts compExtended execBlank ([s|^cabal-.*$|] :: ByteString)) (makeRegexOpts compExtended execBlank ([s|^cabal-.*$|] :: ByteString))
vs <- forM bins $ \f -> case version . T.pack <$> (stripSuffix exeExt =<< stripPrefix "cabal-" f) of vs <- forM bins $ \f -> case versionRev . T.pack <$> (stripSuffix exeExt =<< stripPrefix "cabal-" f) of
Just (Right r) -> pure $ Right r Just (Right r) -> pure $ Right r
Just (Left _) -> pure $ Left f Just (Left _) -> pure $ Left f
Nothing -> pure $ Left f Nothing -> pure $ Left f
@ -361,14 +361,14 @@ getInstalledCabals = do
-- | Whether the given cabal version is installed. -- | Whether the given cabal version is installed.
cabalInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => Version -> m Bool cabalInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => VersionRev -> m Bool
cabalInstalled ver = do cabalInstalled ver = do
vers <- fmap rights getInstalledCabals vers <- fmap rights getInstalledCabals
pure $ elem ver vers pure $ elem ver vers
-- Return the currently set cabal version, if any. -- Return the currently set cabal version, if any.
cabalSet :: (HasLog env, MonadReader env m, HasDirs env, MonadIO m, MonadThrow m, MonadCatch m) => m (Maybe Version) cabalSet :: (HasLog env, MonadReader env m, HasDirs env, MonadIO m, MonadThrow m, MonadCatch m) => m (Maybe VersionRev)
cabalSet = do cabalSet = do
Dirs {..} <- getDirs Dirs {..} <- getDirs
let cabalbin = binDir </> "cabal" <> exeExt let cabalbin = binDir </> "cabal" <> exeExt
@ -395,7 +395,7 @@ cabalSet = do
-- We try to be extra permissive with link destination parsing, -- We try to be extra permissive with link destination parsing,
-- because of: -- because of:
-- https://gitlab.haskell.org/haskell/ghcup-hs/-/issues/119 -- https://gitlab.haskell.org/haskell/ghcup-hs/-/issues/119
linkVersion :: MonadThrow m => FilePath -> m Version linkVersion :: MonadThrow m => FilePath -> m VersionRev
linkVersion = throwEither . MP.parse parser "linkVersion" . T.pack . dropSuffix exeExt linkVersion = throwEither . MP.parse parser "linkVersion" . T.pack . dropSuffix exeExt
parser parser
@ -403,7 +403,7 @@ cabalSet = do
<|> MP.try (stripRelativePath *> cabalParse) <|> MP.try (stripRelativePath *> cabalParse)
<|> cabalParse <|> cabalParse
-- parses the version of "cabal-3.2.0.0" -> "3.2.0.0" -- parses the version of "cabal-3.2.0.0" -> "3.2.0.0"
cabalParse = MP.chunk "cabal-" *> version' cabalParse = MP.chunk "cabal-" *> versionRevP
-- parses any path component ending with path separator, -- parses any path component ending with path separator,
-- e.g. "foo/" -- e.g. "foo/"
stripPathComponet = parseUntil1 pathSep *> MP.some pathSep stripPathComponet = parseUntil1 pathSep *> MP.some pathSep
@ -420,7 +420,7 @@ cabalSet = do
-- @~\/.ghcup\/bin/haskell-language-server-wrapper-<\hlsver\>@, -- @~\/.ghcup\/bin/haskell-language-server-wrapper-<\hlsver\>@,
-- as well as @~\/.ghcup\/hls\/<\hlsver\>@ -- as well as @~\/.ghcup\/hls\/<\hlsver\>@
getInstalledHLSs :: (MonadReader env m, HasDirs env, MonadIO m, MonadCatch m) getInstalledHLSs :: (MonadReader env m, HasDirs env, MonadIO m, MonadCatch m)
=> m [Either FilePath Version] => m [Either FilePath VersionRev]
getInstalledHLSs = do getInstalledHLSs = do
Dirs {..} <- getDirs Dirs {..} <- getDirs
bins <- liftIO $ handleIO (\_ -> pure []) $ findFiles bins <- liftIO $ handleIO (\_ -> pure []) $ findFiles
@ -431,7 +431,7 @@ getInstalledHLSs = do
) )
legacy <- forM bins $ \f -> legacy <- forM bins $ \f ->
case case
version . T.pack <$> (stripSuffix exeExt =<< stripPrefix "haskell-language-server-wrapper-" f) versionRev . T.pack <$> (stripSuffix exeExt =<< stripPrefix "haskell-language-server-wrapper-" f)
of of
Just (Right r) -> pure $ Right r Just (Right r) -> pure $ Right r
Just (Left _) -> pure $ Left f Just (Left _) -> pure $ Left f
@ -448,7 +448,7 @@ getInstalledHLSs = do
-- | Get all installed stacks, by matching on -- | Get all installed stacks, by matching on
-- @~\/.ghcup\/bin/stack-<\stackver\>@. -- @~\/.ghcup\/bin/stack-<\stackver\>@.
getInstalledStacks :: (MonadReader env m, HasDirs env, MonadIO m, MonadCatch m) getInstalledStacks :: (MonadReader env m, HasDirs env, MonadIO m, MonadCatch m)
=> m [Either FilePath Version] => m [Either FilePath VersionRev]
getInstalledStacks = do getInstalledStacks = do
Dirs {..} <- getDirs Dirs {..} <- getDirs
bins <- liftIO $ handleIO (\_ -> pure []) $ findFiles bins <- liftIO $ handleIO (\_ -> pure []) $ findFiles
@ -458,7 +458,7 @@ getInstalledStacks = do
([s|^stack-.*$|] :: ByteString) ([s|^stack-.*$|] :: ByteString)
) )
forM bins $ \f -> forM bins $ \f ->
case version . T.pack <$> (stripSuffix exeExt =<< stripPrefix "stack-" f) of case versionRev . T.pack <$> (stripSuffix exeExt =<< stripPrefix "stack-" f) of
Just (Right r) -> pure $ Right r Just (Right r) -> pure $ Right r
Just (Left _) -> pure $ Left f Just (Left _) -> pure $ Left f
Nothing -> pure $ Left f Nothing -> pure $ Left f
@ -509,13 +509,13 @@ stackSet = do
stripRelativePath = MP.many (MP.try stripPathComponet) stripRelativePath = MP.many (MP.try stripPathComponet)
-- | Whether the given Stack version is installed. -- | Whether the given Stack version is installed.
stackInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => Version -> m Bool stackInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => VersionRev -> m Bool
stackInstalled ver = do stackInstalled ver = do
vers <- fmap rights getInstalledStacks vers <- fmap rights getInstalledStacks
pure $ elem ver vers pure $ elem ver vers
-- | Whether the given HLS version is installed. -- | Whether the given HLS version is installed.
hlsInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => Version -> m Bool hlsInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => VersionRev -> m Bool
hlsInstalled ver = do hlsInstalled ver = do
vers <- fmap rights getInstalledHLSs vers <- fmap rights getInstalledHLSs
pure $ elem ver vers pure $ elem ver vers
@ -527,7 +527,7 @@ isLegacyHLS ver = do
-- Return the currently set hls version, if any. -- Return the currently set hls version, if any.
hlsSet :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m, MonadCatch m) => m (Maybe Version) hlsSet :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m, MonadCatch m) => m (Maybe VersionRev)
hlsSet = do hlsSet = do
Dirs {..} <- getDirs Dirs {..} <- getDirs
let hlsBin = binDir </> "haskell-language-server-wrapper" <> exeExt let hlsBin = binDir </> "haskell-language-server-wrapper" <> exeExt
@ -540,7 +540,7 @@ hlsSet = do
link <- liftIO $ getLinkTarget hlsBin link <- liftIO $ getLinkTarget hlsBin
Just <$> linkVersion link Just <$> linkVersion link
where where
linkVersion :: MonadThrow m => FilePath -> m Version linkVersion :: MonadThrow m => FilePath -> m VersionRev
linkVersion = throwEither . MP.parse parser "" . T.pack . dropSuffix exeExt linkVersion = throwEither . MP.parse parser "" . T.pack . dropSuffix exeExt
where where
parser parser
@ -548,7 +548,7 @@ hlsSet = do
<|> MP.try (stripRelativePath *> cabalParse) <|> MP.try (stripRelativePath *> cabalParse)
<|> cabalParse <|> cabalParse
-- parses the version of "haskell-language-server-wrapper-1.1.0" -> "1.1.0" -- parses the version of "haskell-language-server-wrapper-1.1.0" -> "1.1.0"
cabalParse = MP.chunk "haskell-language-server-wrapper-" *> version' cabalParse = MP.chunk "haskell-language-server-wrapper-" *> versionRevP
-- parses any path component ending with path separator, -- parses any path component ending with path separator,
-- e.g. "foo/" -- e.g. "foo/"
stripPathComponet = parseUntil1 pathSep *> MP.some pathSep stripPathComponet = parseUntil1 pathSep *> MP.some pathSep
@ -567,7 +567,7 @@ hlsGHCVersions :: ( MonadReader env m
, MonadThrow m , MonadThrow m
, MonadCatch m , MonadCatch m
) )
=> m [Version] => m [VersionRev]
hlsGHCVersions = do hlsGHCVersions = do
h <- hlsSet h <- hlsSet
fromMaybe [] <$> forM h hlsGHCVersions' fromMaybe [] <$> forM h hlsGHCVersions'
@ -579,12 +579,12 @@ hlsGHCVersions' :: ( MonadReader env m
, MonadThrow m , MonadThrow m
, MonadCatch m , MonadCatch m
) )
=> Version => VersionRev
-> m [Version] -> m [VersionRev]
hlsGHCVersions' v' = do hlsGHCVersions' v' = do
bins <- hlsServerBinaries v' Nothing bins <- hlsServerBinaries v' Nothing
let vers = fmap let vers = fmap
(version (versionRev
. T.pack . T.pack
. fromJust . fromJust
. stripPrefix "haskell-language-server-" . stripPrefix "haskell-language-server-"
@ -597,10 +597,10 @@ hlsGHCVersions' v' = do
-- | Get all server binaries for an hls version from the ~/.ghcup/bin directory, if any. -- | Get all server binaries for an hls version from the ~/.ghcup/bin directory, if any.
hlsServerBinaries :: (MonadReader env m, HasDirs env, MonadIO m) hlsServerBinaries :: (MonadReader env m, HasDirs env, MonadIO m)
=> Version => VersionRev
-> Maybe Version -- ^ optional GHC version -> Maybe Version -- ^ optional GHC version
-> m [FilePath] -> m [FilePath]
hlsServerBinaries ver mghcVer = do hlsServerBinaries (VersionRev ver rv) mghcVer = do
Dirs {..} <- getDirs Dirs {..} <- getDirs
liftIO $ handleIO (\_ -> pure []) $ findFiles liftIO $ handleIO (\_ -> pure []) $ findFiles
binDir binDir
@ -611,6 +611,7 @@ hlsServerBinaries ver mghcVer = do
<> maybe [s|.*|] escapeVerRex mghcVer <> maybe [s|.*|] escapeVerRex mghcVer
<> [s|~|] <> [s|~|]
<> escapeVerRex ver <> escapeVerRex ver
<> E.encodeUtf8 (T.pack ("-r" <> show rv))
<> E.encodeUtf8 (T.pack exeExt) <> E.encodeUtf8 (T.pack exeExt)
<> [s|$|] :: ByteString <> [s|$|] :: ByteString
) )
@ -657,16 +658,20 @@ hlsInternalServerLibs ver ghcVer = do
-- | Get the wrapper binary for an hls version, if any. -- | Get the wrapper binary for an hls version, if any.
hlsWrapperBinary :: (MonadReader env m, HasDirs env, MonadThrow m, MonadIO m) hlsWrapperBinary :: (MonadReader env m, HasDirs env, MonadThrow m, MonadIO m)
=> Version => VersionRev
-> m (Maybe FilePath) -> m (Maybe FilePath)
hlsWrapperBinary ver = do hlsWrapperBinary (VersionRev ver rv) = do
Dirs {..} <- getDirs Dirs {..} <- getDirs
wrapper <- liftIO $ handleIO (\_ -> pure []) $ findFiles wrapper <- liftIO $ handleIO (\_ -> pure []) $ findFiles
binDir binDir
(makeRegexOpts (makeRegexOpts
compExtended compExtended
execBlank execBlank
([s|^haskell-language-server-wrapper-|] <> escapeVerRex ver <> E.encodeUtf8 (T.pack exeExt) <> [s|$|] :: ByteString ([s|^haskell-language-server-wrapper-|]
<> escapeVerRex ver
<> E.encodeUtf8 (T.pack ("-r" <> show rv))
<> E.encodeUtf8 (T.pack exeExt)
<> [s|$|] :: ByteString
) )
) )
case wrapper of case wrapper of
@ -677,7 +682,7 @@ hlsWrapperBinary ver = do
-- | Get all binaries for an hls version, if any. -- | Get all binaries for an hls version, if any.
hlsAllBinaries :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m) => Version -> m [FilePath] hlsAllBinaries :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m) => VersionRev -> m [FilePath]
hlsAllBinaries ver = do hlsAllBinaries ver = do
hls <- hlsServerBinaries ver Nothing hls <- hlsServerBinaries ver Nothing
wrapper <- hlsWrapperBinary ver wrapper <- hlsWrapperBinary ver
@ -781,6 +786,9 @@ getLatestToolFor tool pvpIn dls = do
let ps = catMaybes $ fmap (\(v, vi) -> (,vi) <$> versionToPVP v) ls let ps = catMaybes $ fmap (\(v, vi) -> (,vi) <$> versionToPVP v) ls
pure . fmap (first fst) . headMay . filter (\((v, _), _) -> matchPVPrefix pvpIn v) $ ps pure . fmap (first fst) . headMay . filter (\((v, _), _) -> matchPVPrefix pvpIn v) $ ps
-- type ToolVersionSpec = Map Version ToolRevisionSpec
-- type ToolRevisionSpec = Map Int VersionInfo
@ -927,7 +935,7 @@ ghcInternalBinDir ver = do
-- --
-- - @["hsc2hs","haddock","hpc","runhaskell","ghc","ghc-pkg","ghci","runghc","hp2ps"]@ -- - @["hsc2hs","haddock","hpc","runhaskell","ghc","ghc-pkg","ghci","runghc","hp2ps"]@
ghcToolFiles :: (MonadReader env m, HasDirs env, MonadThrow m, MonadFail m, MonadIO m) ghcToolFiles :: (MonadReader env m, HasDirs env, MonadThrow m, MonadFail m, MonadIO m)
=> GHCTargetVersion => GHCTargetVersionRev
-> Excepts '[NotInstalled] m [FilePath] -> Excepts '[NotInstalled] m [FilePath]
ghcToolFiles ver = do ghcToolFiles ver = do
bindir <- ghcInternalBinDir ver bindir <- ghcInternalBinDir ver
@ -1285,7 +1293,7 @@ warnAboutHlsCompatibility :: ( MonadReader env m
=> m () => m ()
warnAboutHlsCompatibility = do warnAboutHlsCompatibility = do
supportedGHC <- hlsGHCVersions supportedGHC <- hlsGHCVersions
currentGHC <- fmap _tvVersion <$> ghcSet Nothing currentGHC <- fmap _tvVersionRev <$> ghcSet Nothing
currentHLS <- hlsSet currentHLS <- hlsSet
case (currentGHC, currentHLS) of case (currentGHC, currentHLS) of

View File

@ -417,9 +417,9 @@ parseGHCupGHCDir :: MonadThrow m => FilePath -> m GHCTargetVersion
parseGHCupGHCDir (T.pack -> fp) = parseGHCupGHCDir (T.pack -> fp) =
throwEither $ MP.parse ghcTargetVerP "" fp throwEither $ MP.parse ghcTargetVerP "" fp
parseGHCupHLSDir :: MonadThrow m => FilePath -> m Version parseGHCupHLSDir :: MonadThrow m => FilePath -> m VersionRev
parseGHCupHLSDir (T.pack -> fp) = parseGHCupHLSDir (T.pack -> fp) =
throwEither $ MP.parse version' "" fp throwEither $ versionRev fp
-- TODO: inlined from GHCup.Prelude -- TODO: inlined from GHCup.Prelude
throwEither :: (Exception a, MonadThrow m) => Either a b -> m b throwEither :: (Exception a, MonadThrow m) => Either a b -> m b

View File

@ -147,6 +147,10 @@ instance Arbitrary Architecture where
arbitrary = genericArbitrary arbitrary = genericArbitrary
shrink = genericShrink shrink = genericShrink
instance Arbitrary VersionDownload where
arbitrary = genericArbitrary
shrink = genericShrink
instance Arbitrary VersionInfo where instance Arbitrary VersionInfo where
arbitrary = genericArbitrary arbitrary = genericArbitrary
shrink = genericShrink shrink = genericShrink

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff